************************************************** J3/04-239 Date: 11 February 2004 To: J3 From: Aleksandar Donev Subject: Extending Genericity in Fortran ************************************************** Extending Genericity in Fortran Aleksandar Donev (adonev@princeton.edu) Princeton University Now that Fortran 2003 is well on its way to becoming the new standard, it is time to consider ideas for future extensions of the language. In this paper I will discuss what I consider to be a topic of major interest to many Fortran programmers: generic programming. Generic code is one that applies to a variety of specific types and/or type parameters. Fortran already has some degree of genericity, mostly due to generic interfaces and parameterized types. However, what is lacking is the ability to write the body of the procedures that enter in the generic interfaces or operate on objects of parameterized type. In most cases this body is independent of the actual type and type parameters of the generic resolution parameters. Because the term generic programming is somewhat general, let me give the reader an idea of what I mean by it. First, it helps to look at the history of C++, a widely used language, and rich in (often badly designed) functionality. The cornerstone of version 1 of the language was single inheritance and dynamic polymorphism, which we now also have in Fortran. In version 2, multiple inheritance was the major innovation, followed by templates in version 3. It is widely agreed that templates are in fact a lot more important and useful than multiple inheritance, and maybe even than single inheritance. Templates are a form of generic programming. Another related familiar concept is that of a (preprocessor) macro. Macros can be thought of procedures that produce Fortran code to be then compiled by the compiler, and templates are in fact a fancy (and safer) form of built-in macros. I like the term "template" and may occasionally use it, however, this will not refer to C++ templates unless explicitly indicated. Although I will try to start from basics, I will assume some familiarity with macros (with parameters) and/or C++ templates and/or Ada generic packages and/or Eiffel generic classes. Before I describe features for generic programming in other programming languages, let me give four prototypical problems/tasks that I am trying to address: 1. Develop a parameterized derived type and associated procedures that work for any kind parameter. 2. Develop a (pointer-less) generic data-structure, and in particular, a generic array-based stack. 3. Develop a generic array procedure like the intrinsic MAXVAL purely in Fortran. 4. Develop a generic procedure to sort an array of an arbitrary (ordered) type. These tasks are ordered in what I consider to be increasing complexity in design and description. Most of them can already be improvised by using: a) Cut and Paste and endless repetition of code. This is very error prone and wastes programmer's effort and time. Sometimes INCLUDE files are used to avoid some repetition. c) Macros, through a preprocessor such as cpp/CoCo/m4/FWEB etc. and include files. This is not only non-standard, but also difficult for the non-expert, and is also not safe and easily leads to programming errors. I propose that basic Fortran provide this functionality, to do away with the need to distribute things like Perl scripts or macro languages with Fortran libraries. Background Generic code is one that applies to multiple specific types, i.e., specification and executable code that is parameterized by a certain (possibly itself parameterized) type T and/or an (integer) type parameter K, which I will refer to as the generic parameters. I will call T the generic type parameter and K the generic kind parameter. Other programming languages typically do not have type parameters like Fortran does, and so in this section we will temporarily forget about K. Genericity is closely related to inheritance, however, I want to stress that it is in fact complementary to it, and I hope to illustrate this here. The main difference is that generic code, as I consider it here, cannot be compiled until the exact type T and kind K are known (compile-time polymorphism), whereas code using inheritance is compiled only once and then it works for multiple types (runtime polymorphism). The key to dynamic polymorphism is the use of pointers, which help avoid knowing the exact type of an object. This has a significant run time cost, like dynamic dispatch, memory indirection, aliasing, etc. Genericity on the other hand will enable us to avoid pointers and even enable inlining of the generic code. Additionally, using inheritance requires designing complex type hierarchies, which is often a difficult process, especially when only single inheritance is provided. Genericity on the other hand does not require such rigid hierarchies, and is thus easier to use. The reader familiar with macros can think of generic code as a kind of macro for generating specific code (meaning code for a specific T and K) that is then compiled in the usual way. However, I am not describing or proposing a Fortran-aware macro system in this proposal! The relation between macros and generic code is similar to that of macro constants (#define's) and Fortran PARAMETERs. The former provide the functionality of Fortran constants, but without the appropriate scoping or type-checking abilities. In the above sense, the generic code is the macro, or template. When this macro is used (with specific T and K), the compiler compiles the specific code. The last step, which I will call instantiation (C++ terminology), is unavoidable since T and K must be known before executable object code can be produced. There are 3 main kinds of genericity, as found in different languages: unlimited unconstrained, limited unconstrained, and unlimited constrained. I describe these in turn. Unlimited Unconstrained Genericity C++ templates provide unlimited unconstrained genericity, and for this kind of genericity there are no a priori (meaning prior to instantiation) requirements or restrictions on the generic parameters. Templates are basically macros with basic language awareness, such as syntax awareness (balancing braces and parenthesis, for example) and scope. They do not provide proper type checking. To illustrate this, here is a C++ function template for a function that returns the smaller of two values: template T minimum(T A, T B) { if(A; function minimum(x,y: T) return T is begin if x { public boolean gt (A that); } class SortedObjects> { public A minimum (A first, A second) { if(first.gt(second)) return second else return first } So far, I have illustrated the kind of decisions that need to be made when implementing genericity in a statically typed language, and the diversity of solutions in various programming languages. I next tackle four typical Fortran programming tasks that are best done using genericity, as given the introduction, and propose specific solutions. Specific Examples and Proposed Solutions Parameterized Types and their Operations Take the following parameterized type that defines a point in three-dimensional (3D) space whose position is stored using single or double precision REALs, and has one type bound procedure that translates the point: INTEGER, PARAMETER :: r_sp=KIND(1.0E0), r_dp=KIND(1.0D0) ! Single and double precision real kinds TYPE :: Euclidian_Point(kind) PUBLIC INTEGER, KIND :: kind REAL(KIND=kind) :: position(3) CONTAINS PUBLIC PROCEDURE, PASS(point), PRIVATE :: Translate_sp, Translate_dp GENERIC :: Translate=>Translate_sp, Translate_dp END TYPE Euclidian_Point and we have the following bodies for the translation procedure: SUBROUTINE Translate_sp(point, translation) CLASS(Euclidian_Point(r_sp)), INTENT(INOUT) :: point REAL(KIND=r_sp) :: translation(3) point%position = point%position + translation END SUBROUTINE SUBROUTINE Translate_dp(point, translation) CLASS(Euclidian_Point(r_dp)), INTENT(INOUT) :: point REAL(KIND=r_dp) :: translation(3) point%position = point%position + translation END SUBROUTINE Notice how the single and double precision versions of Translate are identical save for the kind-type parameter, r_sp in one, r_dp in the other. This is needless repetition of code. Furthermore, if later the compiler is extended to provide quadruple precision, one needs to go back and add yet another duplicate version of Translate. Clearly this is undesirable. For all the extensibility/reusability we have provided with Fortran 2003's OOP features we have forced the programmer to duplicate code and also fix the future usage at the design stage. Instead, one should be able to write something like (this is proposed, not proper syntax): TYPE :: Euclidian_Point(kind) INTEGER, KIND :: kind REAL(KIND=kind) :: position(3) CONTAINS GENERIC, PASS(point) :: Translate END TYPE Euclidian_Point GENERIC SUBROUTINE Translate(point, translation) CLASS(Euclidian_Point(KIND=*)), INTENT(INOUT) :: point ! Works for any KIND (the kind is "assumed") REAL(KIND=point%kind) :: translation(3) point%position = point%position + translation END SUBROUTINE and then simply use this type for any desired precision (generic parameter): TYPE(Euclidian_Point(r_sp)) :: point CALL point%Translate((/1.0_r_sp,1.0_r_sp,1.0_r_sp/)) Full type-safety has been preserved and the simplification and ease-of-use is amazing! How will the compiler do this? There are two main options: 1. When the compiler compiles the procedure Translate, it will compile a separate version for each real precision it supports, and also decorate the procedure names itself. It is exactly what the user has to do manually today by replicating code and changing an sp into a dp. 2. The compiler waits until it encounters code that uses a Euclidian_Point(r_sp) and then it compiles a specific version of Translate for single precision real numbers. In order not to recompile the same translation procedure too frequently, the compiler may maintain some kind of database (cache) or already compiled specific versions of the generic code. In the particular example above, strategy 1 clearly seems preferable. However, there is a problem: What if there are 3 different kind parameters, and 3 possible values for each. Does the compiler compile all 27 versions of the generic procedure? Furthermore, what if the compiler does not know what the possible values for the generic kind parameters are? For example, what if I wanted to provide points in both 2 and 3 dimensions (or even 4 dimensions) using another kind parameter dim: TYPE :: Euclidian_Point(kind, dim) INTEGER, KIND :: kind, dim REAL(KIND=kind), DIMENSION(dim) :: position CONTAINS GENERIC, PASS(point) :: Translate END TYPE Euclidian_Point The compiler does not know that I will only use points in 2 and 3D (i.e., dim=2 and dim=3). So how do I tell it that? Do I even need to say that explicitly, or not. The main question exposed with this example, important for all examples of genericity discussed in this paper, is whether generic procedure (or code in general) needs to be instantiated for specific generic parameters before it can be used. The answer to this question is a major design choice. In this proposal, I will adopt an affirmative answer, i.e., I propose that explicit instantiation be required, as in Ada. The main reason for my choice is that I do not see much harm or burden to the programmer in such a requirement, whereas adopting the requirement solves some important problems. For example, what if a generic procedure has a SAVEd local variable? Is this saved value shared between different copies of the procedure? Furthermore, the manipulation of a database of instantiations can be difficult practically and lead to unnecessarily long computation times (as supported by experiences in, for example, g++ compilations of C++ codes rich with templates). Before proposing specific syntax for instantiation, however, I will explore further the types of problems that genericity should address. The basic gist of the above example is that the generic type parameter is fixed (in this case to Euclidian_Point), and only the generic kind parameter is varied. Next we want to get more demanding and ask that the type parameter also be allowed to change, but we can predict a-priori what (intrinsic) type parameters we want to use. User-Defined Array Operations In the first section I mentioned as an example writing something like the intrinsic MAXVAL in Fortran, without repetition of code. If one looks at what the current standard specifies for this intrinsic procedure, it can be seen that the standard allows array arguments of any intrinsic INTEGER or REAL type, and of any rank. For now, let's focus on rank-1 arrays (I will address the problem of rank genericity shortly). How can we extend Fortran so that the user can develop his own generic array operation; for example, develop a parallel PMAXVAL reduction subroutine? A possible syntax to write such a parallel reduction procedure is: GENERIC FUNCTION PMAXVAL(array) RESULT(global_max) ! Distributed MAXVAL (MPI Based) USE MPI TYPE(INTEGER(*), REAL(*)), DIMENSION(:), INTENT(IN) :: array ! Must be of integer or real type TYPE(TYPE_OF(array)) :: global_max ! The same type and type parameters as array TYPE(TYPE_OF(array)) :: local_max local_maxval=MAXVAL(array) ! Use the serial intrinsic ! I will silently assume that there is generic MPI_Allreduce CALL MPI_Allreduce(sendbuf=local_max, recvbuf=global_max, & count=1, op=MPI_MAX, comm=MPI_COMM_WORLD) END FUNCTION In the above example, we specified that the argument be of some intrinsic INTEGER or REAL type, of any kind. We needed to do this because we used the MAXVAL intrinsic procedure. An important point here is that we fixed the rank to one. It would be desirable if genericity in Fortran also includes the ability to write rank-independent code, i.e., to add rank to the list of generic parameters. In the above example, there is no real substance to the fact that array is rank-1. By only changing the DIMENSION declaration the same code would work for any rank. The main purpose of this work is to avoid repetition of code. However, rank genericity is not an easy problem to tackle. For example, assume we had added the DIM parameter, as in the intrinsic MAXVAL. The result would then have been of different rank. How do we express that in syntax? Although an important subject, I will forget about generic rank parameters and continue to focus on code that is parameterized by a type and possibly a type parameter. The two examples tackled so far have illustrated that there are two relatively non-controversial cases where genericity is needed, and these are already widely used among Fortran programmers (where cut/paste, macros, Perl scripts, and other external machinery is used to generate the body of the procedures above): 1) When only a kind parameter changes and the type is fixed. 2) When the type also changes but the set of types is known a-priori. Both 1 and 2 are easy to compile if the set of kind parameters is also fixed, especially if the compiler can determine it. Namely, the compiler can just pre-compile all possible combinations of types/type-parameters. The above system maintains a clear separation between types, which we can already parameterize with integers, and procedures, which I propose we allow to be parameterized by integers and also work for several different types of arguments. However, I believe it is better to design a system that unifies both and allows one to parameterize a whole generic package, i.e., parameterize a collection of type definitions, variables, constants and procedures. I next give an example that invents a new GENERIC scoping unit to achieve this. Generic Stack Package Fortran has many intrinsics that work with any type. For example, CSHIFT will shift an array of any type. Can we allow the user to write code which works efficiently for any type (and yet does not use CLASS(*) pointers)? This is the case of unconstrained limited genericity. To illustrate how one can provide unconstrained limited genericity that works on any type and yet is completely statically typed and checkable at compile type, I will use a generic stack as an example. This would be a typical kind of data-structure found in the widely used Standard Template Library in C++. One can already code "generic" stacks in Fortran using polymorphic (especially CLASS(*)) pointers. By using generic code as illustrated below one can avoid the use of pointers, and implement a generic stack using a simple array, just as if one were writing a stack of integers or reals. The example code below uses no pointers or dynamic dispatch and can easily be inlined without global program analysis. In this example I introduce a new scoping unit GENERIC, which contains type definitions, variable and constant declarations, and procedures parameterized by an arbitrary type T, which must be a specific type, i.e., have all its type parameters specified. It is useful to refer to this as a generic package. A generic package is much like a module scope-wise. It may be decided that in fact MODULEs themselves can be parameterized and that a new concept is not needed. However, I view modules as static constructs, of which there is one and only one instance. Clearly this is not true for generic packages, which can have many instances for different types. I therefore believe introducing a new concept is warranted. MODULE GenericStacks GENERIC, PUBLIC :: GenericStack(T) ! A new programming unit ! This can be used with any type TYPE :: T ! Generic type parameter (any type) TYPE, PUBLIC :: Generic_Stack ! Type definition PUBLIC INTEGER :: n_elements=0, n_max_elements=100 TYPE(T), ALLOCATABLE, DIMENSION(:), PRIVATE :: storage CONTAINS PUBLIC PROCEDURE, PASS(stack) :: Initialize, Pop ... END TYPE CONTAINS SUBROUTINE Initialize(stack) ! Allocate stack storage CLASS(Generic_Stack), INTENT(INOUT) :: stack ALLOCATE(stack%storage(n_max_elements)) ! No need for SOURCE in this allocation END SUBROUTINE FUNCTION Pop(stack) RESULT(top) CLASS(Generic_Stack), INTENT(INOUT) :: stack TYPE(T) :: TOP ! No POINTER or CLASS needed IF(stack%n_elements<=0) RETURN ! No value to pop top=stack%storage(n_elements) stack%n_elements=stack%n_elements-1 END FUNCTION ... END GENERIC END MODULE Now, the generic GenericStack cannot really be compiled until the type T is known. To use a generic stack, one must specifically instantiate the generic with a specific type. This instance can be given a name and notation similar to type selection used to refer to the specific types and procedures it defines. I illustrate this with an example: PROGRAM RealStacks USE GenericStacks GENERIC(GenericStack(REAL)) :: real_stack ! Now actually compile the code ! To get a generic stack of single-precision REALs TYPE(real_stack%generic_stack) :: stack ! Declare a stack of reals ! Now use this stack: CALL stack.Initialize() ! Or "CALL real_stack%Initialize(stack)" ... WRITE(*,*) "Top element is:", stack%pop() END PROGRAM What exactly can go inside a GENERIC block parameterized by an unknown type T? Well, anything that according to the current standard would work no matter what specific type T is used to instantiate the generic package. For example, if inside the GENERIC we have: TYPE(T), TARGET :: x TYPE(T), POINTER :: y TYPE(T), DIMENSION(:), ALLOCATABLE :: z then any of these are OK: ALLOCATE(z(5)) y=>x z(5)=x but not this: x=1.0 Additionally, I believe we should allow the type parameter T or a variable of parameterized type to be used in a SELECT TYPE construct, for example, with the syntax: SELECT TYPE(T) CASE (INTEGER(sp)) WRITE(*,*) "Stack of integers" CASE DEFAULT WRITE(*,*) "Stack of something???" END SELECT TYPE In C++ terminology, this is related to the concept of "specialization". Namely, though most generic code is completely type-independent, there may be small pieces of code where it is necessary to be more specific, either for optimization, or for correctness. Also, it should be allowed to call a procedure whose dummy is declared with CLASS(*) with an actual whose type is the generic type parameter T. Thus far I have given examples of a special kind of unlimited constrained genericity (where the constraint is that the type T belong to a specific set of types), and of limited unconstrained genericity. Next I tackle the most challenging (but arguably also the most powerful) unlimited constrained genericity, namely, where the type T is constrained to have certain properties (i.e., to belong to certain class of types, which James Giles has called genera). Sorting Data of Unknown Type Take the simple example of a sorting routine for objects of an arbitrary type. Any sorting routine would have to compare two quantities of this type, so inside the generic code there might be something like: GENERIC QuickSort(T) ... TYPE(T), ... :: A, B IF(A