On 2015-09-30 10:59 AM, FortranFan wrote:
> On Tuesday, September 29, 2015 at 7:12:44 PM UTC-4, Ian Harvey
> wrote:
>
>> .. I think you want to very much avoid the need to specify the
>> actual types in the generic source code. A fundamental principle
>> of this sort of feature should be that you specify the minimum
>> required characteristics of the dummy type that the generic code
>> supports (and some of those characteristics may be things that you
>> cannot express in the current type definition syntax), but
>> provision of the actual type (or actual procedure, or actual
>> constant, or whatever the parameterisation is based around) happens
>> later.
>
> That might be true from a purist point-of-view for an OO language
> seeking rigorous support for generics.
>
> But most of the recommended practices with practical implementations
> such as Java and Microsoft C# suggest including constraints as much
> as possible to inform the compiler what types go along with the
> method, interface, class, etc. e.g., "extends" keyword in Java and
> where in C#. So my thought has been why not setup Fortran generic
> types with constraints from the get-go. However, this needn't come
> in the way of further discussions and progress in ideas for generic
> types. If need be, the suggestion can be changed to a syntax such
> as
I think we are talking at cross purposes. Having the ability to
"specify the minimum required characteristics of the dummy type" - i.e.
constraints on the types that can be used - was one of my points.
The examples you quote from other languages are mechanisms to do just
that. But you don't specify the entire list of *actual* types - you
specify that "these procedures work with types that look like this".
Specification of the actual type occurs later, when the generic code is
actually used.
In your original example code, you defined three types, my
interpretation of your syntax was that the procedures were for working
with those three types (and perhaps types and specified kinds), and
those three types (and perhaps specified kinds) alone.
You had a type(*) specifier that appeared to stand for "some type to be
specified in future", but I did not see any explicit constraints on the
characteristics of that type. Implicit constraints would have existed
based on the generic code (e.g. objects of this unspecified type are
appearing in an expression on the left hand side of the multiplication
operator, therefore the unspecified type must support its objects being
used on the left hand side of the multiplication operator) but if
possible I think it best to avoid implicit statement of the requirements
on actual types, otherwise you end up with the "confusing error message"
situation that you can occasionally get with C++ templates.
> -- begin pseudo code -- module m
>
> .. type, deferred :: T, U .. contains
>
> function mult( foo, bar ) result(prod) type(T), intent(in) :: foo
> type(U). intent(in) :: bar .. end function mult
>
> end module m
I don't follow what you are trying to illustrate with that syntax.
Permit me to now confuse you by trying to illustrate some of my ideas
with syntax (and perhaps the odd comment). This is woefully incomplete
- I can shoot holes in it too.
Given their existing role in the language, I think modules represent the
natural unit for packaging together generic code (I have seen referenced
to parameterised modules in discussions around the feature set for
Fortran 2003, but I have not yet read any details about what
specifically was proposed). That lets you provide client code with
types, procedures and variables that are all based off the same
parameterisation. Contrast this with the approach taken with kind
parameterisation of types in Fortran 2003 - you can provide a
parameterised type, but providing a matching set of parameterised
procedures and variables requires things like INCLUDE hacks and the like.
(Given the existence of parameterised types in the language it may well
be useful to consider parameterisation at a level finer than a module -
perhaps at the procedure level.)
! The module m has two "dummy" parameters, identified as t and u.
MODULE m(t,u)
IMPLICIT NONE
PRIVATE
! This specifies that the identifier `t` is a type. When
! the generic module is used the name of a type must be
! associated with this parameter.
!
! Further, the "actual" type must match the interface
! of this type. I have tried to write things below such
! that an extension of `t` would always be a suitable match,
! but being an extension should not be a requirement.
!
! The abstract keyword is here to make it clear that this
! is not an actual type definition, it defines a template
! for the module parameter t. Perhaps this is unnecessary,
! perhaps it should be a different keyword, perhaps we want
! to separate specification of the characteristics of the type
! from the specification that the dummy parameter must match
! those characteristics.
TYPE, ABSTRACT :: t
! The actual type must have an integer component named `comp`.
INTEGER :: comp
CONTAINS
! The actual type must have a generic binding for OPERATOR(+).
GENERIC :: OPERATOR(+) => plus
! The actual type must have a specific binding called `plus`.
! That binding must match the given interface.
!
! The deferred keyword is here to maintain consistency with
! current syntax rules.
PROCEDURE(plus_intf), DEFERRED :: plus
END TYPE t
! This is the interface specification for the plus specific, and
! hence the OPERATOR(+) generic.
ABSTRACT INTERFACE
FUNCTION plus_intf(lhs, rhs)
IMPORT :: t
TYPE(t), INTENT(IN) :: lhs, rhs
TYPE(t) :: plus_intf
END FUNCTION plus_intf
END INTERFACE
! There is some nonsense in the above, in that all I want to
! do is state that operator (+) with the interface given by
! plus_intf must be accessible (I don't care about the
! name of the specific interface, perhaps the generic doesn't
! even need to be type bound).
! The identifier `u` is a value parameter of the module, and
! the associated actual value must be a default integer.
!
! In the current scope this identifier can be considered a
! named constant - as per KIND parameter of parameterised
! derived types in Fortran 2003. Perhaps we could allow
! for default values for value parameters that are unspecified
! at the point of use.
INTEGER, KIND :: u
! As you suggest, it would be nice (I think it a required
! feature) to be able to constrain the actual values of `u`
! in some way - combinations of value ranges and value lists.
!
! This aspect (and how it interacts with use of `u` as a
! kind parameter in the subprogram below) requires
! further thought.
! INTEGER, KIND, ONLY(INTEGER_KINDS) :: u
! INTEGER, KIND, ONLY(WHERE(x,x > 0)) :: u
! You might also want to parameterise on procedures.
! PROCEDURE(must_match_some_intf) :: u
! We can define module variables - these are common to all
! instances (all USE's) with the *same* parameters. Different
! parameters - different variables.
!
! (Being clear about when things are the same and when things
! are different may limit value parameters to being of type
! integer, otherwise you get into nonsense such as whether
! 0.0999999999999 is the same as 0.10000000000001.)
!
! In this case, the characteristics of the module variable
! depend on a value parameter.
INTEGER :: array(u)
! Specific procedure provided by this module. This procedure
! is not a generic interface, but it contains generic code.
PUBLIC :: Multiply
CONTAINS
FUNCTION Multiply(lhs, rhs) RESULT(r)
! Argument is of the dummy type.
TYPE(t), INTENT(IN) :: lhs
! Again, use of the value parameter, here as a kind
! parameter. In the absence of a constraint on the
! permitted values of `u` the requirement that the actual
! value of `u` be a valid integer kind value becomes
! implicit - I don't like this, so perhaps to permit use
! as a kind parameter a value parameter must be
! appropriately constrained.
INTEGER(u), INTENT(IN) :: rhs
! Function result is of the dummy type.
TYPE(t) :: r
INTEGER(u) :: i
! There are some common operations such as "construct with
! zero value" that you might want to specify as being
! available. In the absence of that, I just hope that
! client code never calls this with `rhs` less than one.
r = lhs
DO i = 2_u, rhs
! The dummy type `t` was constrained by the definition above
! to support OPERATOR(+) on two objects of `t`, returning
! a `t`, consequently this compiles.
r = r + lhs
! Implicitly in the above I am assuming that it is possible
! to assign one `t` object to another, but I don't think
! it is possible to prevent that in the current language.
! Because the dummy type definition did not specify
! any other generic identifiers, this would result in
! a diagnostic when attempting to compile this module.
! r = r - lhs
! We can do this... comp is a required component.
array(1) = array(1) + lhs%comp
! Referencing other components is a compile error.
! array(1) = array(1) + lhs%foo
END DO
END FUNCTION Multiple
END MODULE m
MODULE example_use
! Instantiate module m with the given actual parameters.
!
! There is a forward reference to the actual type definition
! here. Some thought is required as to whether this is
! problematic.
!
! The `array` module variable behind this instantiation
! is the same as the `array` module variable behind any
! other instantiation that uses the same type for t and same
! integer value for u. Because `type_a` is not a sequence or
! BIND(C) type, that means that it must be the `type_a` defined
! by this module (perhaps being used in a different module).
!
! How that would practically work with sequence types and
! BIND(C) types as actual types requires further thought!
!
! Actual value parameters must always be specified by
! constant expressions.
USE m(type_a, KIND(1))
! This would result in a compile error - you are trying to
! use associate two non-generic things with the same
! identifier (two instances of Multiply) and reference
! them in a scope. If you want to have two instances
! of the parameterised module active, you have to use
! the rename feature.
! USE m(type_b, KIND(1))
IMPLICIT NONE
! The actual type.
TYPE :: type_a
! We have our integer component, as required. Component
! order is not pertinent.
INTEGER :: comp
! We can have other components too...
REAL :: r
CONTAINS
! We have the required generic binding (and specific)
GENERIC :: OPERATOR(+) => plus
PROCEDURE :: plus => a_plus
! We can have other bindings too...
PROCEDURE :: a_multiply
END TYPE type_a
CONTAINS
FUNCTION a_plus(lhs, rhs)
TYPE(type_a), INTENT(IN) :: lhs, rhs
TYPE(type_a) :: a_plus
! ...
END FUNCTION a_plus
FUNCTION a_multiply(lhs, v)
TYPE(type_a), INTENT(IN) :: lhs
INTEGER, INTENT(IN) :: v
! Here is a reference to the specific procedure provided by
! the generic module, with that specific procedure instantiated
! for type a and the integer kind parameter value for default
! integer.
a_multiply = Multiply(lhs, v)
END FUNCTION a_multiply
END MODULE example_use