Object-Oriented Features in 2003

Reinhold Bader

Leibniz Supercomputing Centre Munich December 2007

©2006-8 LRZ 1 Characterization of object-oriented (OO) programming (1)

Following the Wikipedia entry http://en.wikipedia.org/wiki/Object-oriented_programming the following properties are relevant: 1. Class: Unit of definition of data and behaviour (=methods) of some-kind-of- thing; the basis of modularity and structure in an object oriented program. Fortran 95 support: type definitions contained subroutines within a module (re-use)

Fortran 2003 support: by compatibility class keyword refers to inheritance/polymorphism improves abstraction

©2006-8 LRZ 2 Characterization of object-oriented programming (2)

2. Object: An instance of a class, an object is a run-time manifestation of an exemplar of a class. Each object has its own (separate) data, which characterize the state of the object Fortran 95 support: type(...) :: object declaration default initialization dynamically via pointer attribute array support dynamic arrays via allocatable attribute intrinsics for array manipulation structure constructor

Fortran 2003 support: by compatibility allocate is much more powerful

©2006-8 LRZ 3 Characterization of object-oriented programming (3)

3. Encapsulation: protection of the internal structure of objects against manipulation, unless via the objects' exposed .

Fortran 95 support: module concept module (not class) is unit of encapsulation impose access limits: public and private attributes type definitions, type components global variables and contained subroutines Fortran 2003 support: by compatibility more fine-grained required because of type extensibility new attribute protected global objects only

©2006-8 LRZ 4 Characterization of object-oriented programming (4)

4. (Interfacing): the by which an object sends data to another object or asks the other object to invoke a method. Fortran 95 support: not on type/object level indirectly via explicit and named (“generic”) interfaces check object TKR Fortran 2003 support: by compatibility type-bound procedures bind method to a type definition procedure pointer components bind subroutine call to an object abstract interfaces

©2006-8 LRZ 5 Characterization of object-oriented programming (5)

5. Inheritance: mechanism for creating sub-classes, by specialization (, extending) another class. All data and functions of the superclass(es) are acquired, but data/methods may be added/changed. “Is- a” relationship, as opposed to “has-a” relationship induced by composition.

Fortran 95 support: no emulate by combining composition, delegation and generic interfaces Fortran 2003 support: type extension inherit type components (including procedure pointer components) inherit type bound procedures, or override them multiple inheritance is unsupported

©2006-8 LRZ 6 Characterization of object-oriented programming (6)

6. Abstraction: Ability of a program to ignore the details of an objects' (sub)class and work at a more generic level when appropriate.

Fortran 95 support: derived data types, type composition , self-defined operators generic interfaces

Fortran 2003 support: by compatibility generic type-bound procedures

©2006-8 LRZ 7 Characterization of object-oriented programming (7)

7. Polymorphism: Behaviour of methods that varies depending on the class membership of objects worked upon. static polymorphism: all method calls are fixed at compilation time. dynamic polymorphism: delay method calling determination to run- time. parametric polymorphism: parameterize functions and data structures over arbitrary values. Fortran 95 support: static polymorphism via generic interfaces (limited) emulation of dynamic polymorphism Fortran 2003 support: dynamic polymorphism dynamic objects subroutine interface parametric polymorphism very limited: kind and length parameters allowed

©2006-8 LRZ 8 Characterization of object-oriented programming (8)

Problems with terminology terms and their meaning vary between languages danger of misunderstandings will use Fortran-specific jargon but will also compare with ++ from time to time Aims of OO paradigm: improvements in re-usability abstraction moving from procedural to data-centric programming reducing software development effort, improving productivity indiscriminate usage of OO however may be (very) counterproductive identify abstract “software patterns” which have proven useful

©2006-8 LRZ 9 of OO within Fortran

Fortran 95 supports object-based programming Fortran 2003 supports object-oriented programming specific intentions of Fortran object model: backward compatibility with Fortran 95 broken essentially only with respect to semantic change in treatment of allocatable variables allow extensive correctness and consistency checking by the module remains the unit of encapsulation design more reminiscent of Ada than C++

©2006-8 LRZ 10 Part I

Type Extension and Polymorphism

©2006-8 LRZ 11 Defining inheritance: Type extension (1)

Type definitions Fortran concept: date, datetime type extension single inheritance only mod_date type :: date private date datetime integer :: yr, mon, day yr, mon, day hr, min, sec end type : type, extends(date) :: datetime : : private integer :: hr, min, sec end type : type(datetime) :: o_dt re-use date definition datetime a specialization (or instantiation of objects subclass) of date can be performed as with “standard” date more general than derived types datetime other possibilities discussed later

©2006-8 LRZ 12 Defining inheritance: Type extension (2)

Accessing component data Can have zero additional inherited components components o_dt%day, o_dt%mon, o_dt%yr use only for type differentiation additional components o_dt%hr, o_dt%min, o_dt%sec or additional type bound procedures not available parent component(s) to parent type object of parent type Type parameters are also recursive references possible inherited is itself inherited Which types can be extended? o_dt%date must be derived type Parent type can be empty may not have the bind or will discuss abstract types sequence attribute later

©2006-8 LRZ 13 Extending component accessibility

Fortran 2003 allows setting accessibility for each type component individually

type :: date private integer :: yr, mon, day character(len=5), public :: tag = 'none ' end type type, extends(date) :: datetime private integer :: hr, min, sec end type

all accessibility attributes are also inherited extended type in different module cannot access private components of parent type this is the same as in Fortran 95 need accessor methods

©2006-8 LRZ 14 Polymorphism (1)

Polymorphic objects: Example: class(date), ... :: o_poly_dt declared type is date class(date), pointer :: p_d type(date), target :: o_d dynamic type may vary at type(datetime), target :: o_dt run time : may be declared type and all its p_d => o_dt (known) extensions ... = p_d%hr ! illegal p_d => o_d type compatibility ... = p_d%hr ! worse than illegal direct access only possible ... = p_d%mon ! OK to components of declared dynamic type changes at type run time compiler lacks knowledge Data item can be pointer or allocatable variable dummy data object

©2006-8 LRZ 15 Polymorphism (2): Dynamic creation of polymorphic entities

Typed allocation Sourced allocation class(x), pointer :: p class(xx) :: src class(x), allocatable :: q class(x), allocatable :: cpy : : ! define src allocate(xx :: p, q) allocate(cpy, source = src) xx of type x or an xx of type x or an extension of x extension of x note that allocatable produces a clone of src scalars are allowed in deep copy for allocatable components shallow copy for pointer components usual difference between pointer and allocatable

For disassociated pointer/unallocated allocatable objects: dynamic type is equal to declared type

©2006-8 LRZ 16 Polymorphism (3): Dynamic type/class resolution

select type construct Execution sequence: provides access to at most one block is dynamic parts executed executes alternative code selection of block: depending on dynamic 1. find type guard exactly type matching the dynamic type class(date), ... :: dt 2. if none exists, select class : guard which most closely select type(dt) matches dynamic type and is type is (date) still type compatible : at most one exists type is (datetime) 3. if none exists, execute block ... = dt%hr ! this is OK of class default (if it exists) class is (...) : Access to components class default in accordance with : resolved type (or class) end select

©2006-8 LRZ 17 Polymorphism (4): Additional remarks on dynamic type resolution

Can introduce an associate Recommendations: name to abbreviate referencing: test each guard for each select type(o => x%dt) new subclass separately type is (date) use class default to : check for incompletely type is (datetime) covered inheritance DAG ... = o%hr : end select

assumption: subobject dt of x is of class date Type selection allows both run time type identification run time class identification It is necessary to ensure type safety in the Fortran object model

©2006-8 LRZ 18 Polymorphism (5): Type inquiry intrinsics

Compare dynamic types: extends_type_of(a, mold) same_type_as(a,b)

functions returning a logical value require extensible types as arguments arguments can be polymorphic or non-polymorphic

©2006-8 LRZ 19 Polymorphism (6): Dummy arguments

Example: Example continued: subroutine inc_day(dt, inc) subroutine inc_sec(dt, inc) class(date), intent(inout) :: dt class(datetime), & integer, intent(in) :: inc intent(inout) :: dt : ! implementation omitted integer, intent(in) :: inc end subroutine : ! implementation omitted end subroutine increment date object by a given number of days increment datetime object Inheritance mechanism by a given number of actual argument can be seconds polymorphic or non-polymorphic, of cannot take objects of type date as declared type of dummy or an actual argument extension type compatibility dynamic type of actual argument is assumed by dummy

©2006-8 LRZ 20 Polymorphism (7): Unlimited polymorphic (UP) objects

An object capable of being no declared type of any of type compatible with all 1. intrinsic entities 2. extensible An UP pointer can point to 3. non-extensible anything: type is called unlimited type(datetime), target :: o_dt polymorphic real, pointer :: rval : Example: poly_pt => o_dt allocate(rval) ; rval = 3.0 class(*), pointer :: poly_pt poly_pt => rval

Properties: Dereferencing is illegal type information is only poly_pt => o_dt maintained for 1.+2. write(6, *) poly_pt%yr case 3: types with the same structure ! will not compile are considered the same type

©2006-8 LRZ 21 Polymorphism (8): Dereferencing an unlimited polymorphic object

Need to perform dynamic type Non-extensible target resolution can de-reference type(datetime), pointer :: pt : type, bind(c) :: cvec select type (poly_pt) real(c_float) :: x(3) type is (datetime) end type write(6, *) poly_pt%yr type :: ivec pt => poly_pt sequence ; integer :: i(3) type is (real) end type write(6, '(f12.5)') poly_pt type(cvec), target :: ov class default type(cvec), pointer :: pv write(6, *) 'unknown type' type(ivec), pointer :: iv end select ov = cvec( (/1.1,2.2,3.3/) ) Use of intrinsic type guard poly_pt => ov allowed in this situation pv => poly_pt iv => poly_pt Allocation of UP object: but is not type-safe must use typed or sourced allocation also allowed for lhs: and specify type parameters (another) unlimited polymorphic if applicable pointer

©2006-8 LRZ 22 Polymorphism (9) UP object as subroutine argument

UP dummy argument subroutine can be used to subroutine upt(this, ...) establish pointer association, or class(*) :: this allocate pointer (depend on : intent), or end subroutine (de)allocate allocatable entity actual argument can be of resolve dynamic type via select any type type UP pointer or allocatable hand on to another subroutine dummy argument class(*), pointer :: pp subroutine upt_pt(this, ...) : class(*), pointer :: this ! client usage : call upt_pt(pp, ...) end subroutine Not allowed: type compatibility hand UP actual argument to non-UP dummy argument implies that the actual argument must also be UP and have same attribute

©2006-8 LRZ 23 Part II

Types and Procedures

©2006-8 LRZ 24 Type bound procedures (1): Binding a subroutine to a type

added to type definition Properties: type :: date name mapping private to existing subroutine, or integer :: yr, mon, day implement subroutine of given name contains procedure :: inc => inc_day passed object procedure :: set_date type compatible end type first argument by default (this can be and used by client as changed) must be scalar, non-pointer, non- type(date) :: dt allocatable : call dt%set_date(2006,12,12) Semantic intent for inc call dt%inc(12) ! Christmas want smallest granularity

type(datetime) :: dtt private clause does not : extend to TBPs call dtt%inc(120) ! by seconds? unless separately specified in contains part of type definition works, but not as intended

©2006-8 LRZ 25 Diagrammatic representation of type bound procedures

Fortran 95 Fortran 2003

mod_date mod_date

date date yr, mon, day yr, mon, day

inc_day() %inc()

inc_day()

implementation assumed “%” indicates TBP accessible implementation may not be accessible

©2006-8 LRZ 26 Type bound procedures (2): Overriding TBPs in subclasses

type :: date Not every subclass needs : ! as before contains to define an override procedure :: inc => inc_day inheritance mechanism procedure :: set_date goes upward in DAG until end type a TBP is found type datetime match is with dynamic type : ! as before contains module procedure does not allow this procedure :: inc => inc_sec uniquely defined end type If an overriding TBP is With the overriding TBP defined code (previous slide) will each must have same now work as intended interface as the original Note: even same argument keywords! uniform call mechanism except no name conflicts with passed object dummy, which must be unrelated class declared class(extension)

©2006-8 LRZ 27 Diagrammatic representation for overriding TBPs

mod_date

date datetime yr, mon, day hr, min, sec

%set_date() %inc() %inc()

inc_day() inc_sec()

non-overridden procedures: need not replicate since inherited

©2006-8 LRZ 28 Type bound procedures (3): Enforcing base type inheritance

Passive (by client) Implementation: invoke method on parent subroutine set_date(this, & type yr, mon, day, hr, min, sec) class(date), intent(out) :: & type(datetime) :: dtt this : integer(ik), intent(in) :: & call dtt%date%inc(120) ! by days yr, mon, day Active (enforced by integer(ik), intent(in), & optional :: hr, min, sec compiler) : set_date as example: select type(this) type is (date) type :: date : ! further type guards : ! as before end select contains end subroutine procedure :: inc => inc_day already treats all cases procedure, non_overridable :: & set_date Other rationales are end type possible

©2006-8 LRZ 29 Type bound procedures (4): Variations on passed object dummy

1. Have method 2. Module procedure is bound to subroutine old_meth(a,b,..., & multiple types this, ...) need to explicitly specify classtype(xx) :: this non-default pass in at least : one of the type definitions want to modernize: 3. Method does not involve type :: xx object itself at all ! unchanged possible reason: manipulating module globals contains procedure, pass(this) :: & type :: yy m_tbp => old_meth ! whatever end type xx contains only 1 change to old_meth procedure, nopass :: tbp unless additional component end type yy references needed for extensions need explicit interface omit this on TBP call

©2006-8 LRZ 30 Type bound procedures (5): Generic TBPs

Lift restriction of only Only generic name varying passed object available in example Example: Resolution of generic TBP's add increment by date For all non-passed dummy arguments type :: date : ! as before type incompatible contains TKR based on declared type (!) private number can vary procedure :: inc_day, inc_date generic, public :: inc => passed object dummy inc_day, inc_date as for TBP (deferred to run-time) : Standard generic resolution end type requires type incompatibility interface of : inc_date for at least one non-optional arg. subroutine inc_date(this, diffd) subclassing only cannot be resolved class(date) :: this type(date), intent(in) :: diffd (non)generic TBPs are therefore qualitatively different!

©2006-8 LRZ 31 Type bound procedures (6): Generic overriding and overloading

Subclasses may Operator overloading: need to override a specific operator, assignment, derived to get correct semantics, type I/O specification or can be defined as unnamed need to add a specific generic TBP not blocked by use, only type :: datetime usual resolution rules apply : ! as before contains type foo private : ! override for granularity contains procedure :: inc_day => inc_sec procedure :: plus_1 ! add new method to generic set procedure :: plus_2 procedure :: inc_datetime generic, operator(+) => & generic, public :: inc => & plus_1, plus_2 inc_datetime end type ! beware TKR resolution end type specific TBP may not have the nopass attribute

©2006-8 LRZ 32 Diagrammatic representation of generic TBPs

mod_foo

foo :

operator(+): %plus_1() %plus_2()

plus_1() plus_2()

use italics to indicate generic-ness provide list of specific TBPs as usual overriding in subclasses can then be indicated as previously shown

©2006-8 LRZ 33 Type-bound procedures (7): Finalization (aka Destruction)

Have a class or object associated with additional state open files unfinished non-blocking network (MPI) calls allocated pointer components Imagine object goes out of scope unrecoverable I/O unit communication breakdown memory leak ➢ Solution: auto-destruct provide type with a method which is called as soon as object of type goes out of scope, is deallocated, is passed to an intent(out) dummy argument, or is the left hand side of an intrinsic assignment

©2006-8 LRZ 34 Type-bound procedures (8): Defining a final TBP

Differences to “normal” TPBs: Type definition not normally invoked by user type tp automatically executed as described on real, pointer :: (:) previous slide contains final :: cleanup must have a single dummy end type argument of type to be finalized Finalizer implementation non-polymorphic subroutine cleanup(this) non-pointer, non-allocatable type(tp) :: this all length type parameters assumed if (associated(this%r)) then ! assume target was generic set of finalizers is ! dynamically allocated possible: deallocate(this) rank end if kind parameter values end subroutine multiple execution order processor- dependent

©2006-8 LRZ 35 Diagrammatic representation of Finalizers

Layering of finalizers

mod_tp mod_tp

tp tp contd : : :

~tp() ~tp() ~contd()

cleanup() cleanup() destroy()

Finalizer is not inherited If an object of type tp goes out by extensions of scope reflected in first cleanup() is called nonpolymorphic then destroy() argument unless contd is a pointer component, which exact type match needs to be accounted for in cleanup()

©2006-8 LRZ 36 Type-bound procedures (9): Finalization of type extensions

mod_tp

tp base : :

~tp() ~base()

cleanup() destroy()

If tp is a subclass of base, and an object of type tp goes out of scope first cleanup() is called then destroy() this applies recursively in the case of more than one inheritance level

©2006-8 LRZ 37 Pointers to procedures

Procedure pointer variables: Up to : interface pointer can only point at subroutine subr(x) data object with target real, intent(inout) :: x attribute end subroutine New in : end interface subr procedure(subr), pointer :: pr associate pointer with a ! implicit interface pointers: procedure procedure(), pointer :: pr_2 explicit or implicit external, pointer :: pr_3 => null() interface real :: y target may be a function ! client use: pr => subr; call pr(y) or subroutine target is a procedure known by association with target explicit interface analogous to dummy procedure or implicit interface no generic or elemental interface avoid if possible possible implementation of subr() only needed if dereferenced (?)

©2006-8 LRZ 38 Procedure pointers as type components: object-bound procedures

type xx subroutine foo(this, ...) : class(xx) :: this procedure(foo), pointer :: & ! must be polymorphic p => null() : contains end subroutine : ! TBPs come here! end type or alternatively use [no]pass attribute in type definition Properties as for variables nopass must be specified if for explicit interface, interface is implicit component can point to any Client use in this example: procedure with the same interface type(xx) :: o_xx Important difference: procedure(foo) :: bar by default, the calling object : is passed as 1st argument o_xx%p => bar need to have interface like call o_xx%p(...) (see foo above right)

©2006-8 LRZ 39 Part III

Interfaces

©2006-8 LRZ 40 Dummy argument association for (non-) polymorphic objects

Dummy argument Actual class (...), & argument type (...) class (...) [pointer | allocatable]

Fortran 95 Actual argument type (...) type matching must have same No rules apply declared type as dummy or be an extension

(type compatibility) Actual argument must have same Actual argument [passed object: must have same declared type + class(...) auto-selects declared type as suitable TBP attribute as dummy at run time] dummy. [passed object dummy: No]

©2006-8 LRZ 41 Function results and polymorphism

Remember - polymorphic object must be either a dummy argument not the case for a function result or have the pointer or allocatable attributes Hence, a function result can only be polymorphic if it additionally has either the pointer or allocatable attributes However, default assignment of function result to a polymorphic object not allowed Hence, assignment must occur to a non-polymorphic object, with respect to which the function results' declared type is the same or an extension, or sourced allocation must be used to transfer the result to a polymorphic object

©2006-8 LRZ 42 Extensions to the interface concept (1): The import statement

Interfaces in module For this was fixed: specification section module mod_foo module mod_foo type :: foo type :: foo : : end type end type interface interface subroutine m_foo(this, ...) subroutine m_foo(this, ...) import :: foo type(foo) :: this type(foo) :: this ! OK : ! illegal in : end subroutine end subroutine end interface end interface end module end module access to host entities is not possible from interfaces can import any module entity need to specify interface in no argument: all entities available separate module also applicable to interfaces for access by use association dummy procedure arguments break encapsulation of contained subroutines

©2006-8 LRZ 43 Extensions to the interface concept (2): Abstract interfaces

Scenario: Solution: subroutines with same provide an explicit interface function as dummy argument for which no actual implementation must exist : subroutine foo_23(x, f, y) module mod_interf real, intent(in) :: x abstract interface real, intent(out) :: y real function fun(x) interface real, intent(in) :: x real function f(x) end function real, intent(in) :: x end interface end function : end interface end module : subroutine foo_23(x, f, y) end subroutine foo_23 use mod_interf subroutine foo_24(a, b, f, res) : : procedure(fun) :: f : requires replication of end subroutine foo_23 interface

©2006-8 LRZ 44 Extensions to the interface concept (3): Interface classes

Abstract type abstract interface no object of such a type can subroutine open_handle(this,...) exist import :: handle can have components or not class(handle) :: this : can have TBPs end subroutine may enforce client override in end interface subclass typically specified via an abstract interface if no implementation Declaration fixes interface available Polymorphic variable can have abstract type as type, abstract :: handle : declared type contains but not as dynamic type procedure(open_handle), & deferred attribute only deferred :: open : allowed in abstract types end type handle

©2006-8 LRZ 45 Extensions to the interface concept (4): Subclassing an interface class

module mystuff use mod_handle type, extends(handle) :: & fhandle program client contains use mystuff, only : fhandle procedure :: open => fopen ! nothing else is needed ! will not compile without above implicit none end type fhandle type(fhandle) :: my_fhandle contains : subroutine fopen(this, ...) call my_fhandle%open(...) class(fhandle) :: this st : ! further details omitted ! object is passed as 1 dummy end subroutine : end module mystuff end program client

Extension module Client usage

©2006-8 LRZ 46 Diagrammatic representation of an interface class and its realization

mod_handle mystuff u

handle fhandle

%open() %open() %foo()

foo_handle() fopen()

Will typically use (at least) two separate modules e.g., binary version of abstract type vendor-provided abstract class and abstract interface indicated by italics non-overridable part → “invariant method”

©2006-8 LRZ 47 Extensions to the interface concept (5): Generalizing generic interface blocks

interface foo_generic module procedure foo_1 Example: module procedure foo_2 interface foo_gen end interface ! provide explicit interface can be replaced by ! for external procedure subroutine foo(x,n) interface foo_generic real, intent(out) :: x procedure foo_1 integer, intent(in) :: n procedure foo_2 end subroutine foo end interface end interface with generalized functionality: interface bar_gen procedure foo referenced procedures can be end interface external procedures is legal in dummy procedures is illegal if procedure pointers module procedure is used

©2006-8 LRZ 48 Extensions to the interface concept (6): Submodules – TR 19767

Problems with modules Solution: tendency towards monster split off implementations modules for large projects (module procedures) into type component privatization also separate files prevents being able to break up these files are called modules submodules recompilation cascade need only to recompile these and their effect descendants for changes to an changes to module procedures would implementation not actually require recompilation need to reference parent workarounds are available, but modules in submodule somewhat clunky access to module specifications is by host association need to spell out explicit interface in module specification section Note: no compiler support today (Feb 2008)

©2006-8 LRZ 49 Extensions to the interface concept (7): Submodules (cont')

Example next, the submodule: first, the module: submodule (mod_date) date_methods module mod_date : ! specification part type :: date contains : ! as previously module procedure inc_day end type ! interface taken from mod_date interface : ! implementation module subroutine & end procedure inc_day inc_day(dt, inc) end submodule date_methods import :: date class(date), & can omit interface or specify intent(inout) :: dt exactly identical to module integer, intent(in) :: inc specifications in submodule end subroutine specification section end interface only accessible within submodule or its end module children note keyword indicating access contents via pointers / TBPs separate module procedure similar for “normal” subroutines default public attribute within submodule

©2006-8 LRZ 50 Diagrammatic representation of submodules

mod_date

date :

inc_day()

I

date_methods

inc_day()

“I” (for “implementation”) within circle indicates that a submodule is referred to

©2006-8 LRZ 51 Final remarks on submodules: handling use dependencies

m_1 m_2 m_1 m_2

u at_1 t_2 t_1 t_2 : : : %foo() foo_t2() foo_t1() foo_t2()

I I I illegal I u u

sub_1 sub_2 sub_1 sub_2 u t_1 class(at_1), & : pointer ... foo_t1() %foo()

direct or indirect use association of independent use access is OK parent module is disallowed (Use e.g., polymorphism to satisfy (pure F95 apart submodule use) type dependencies)

©2006-8 LRZ 52 Part IV

Generic Programming

©2006-8 LRZ 53 Generic container classes

Example: linked list Container in general: abstract type :: list containing collections of type() :: stuff other objects type(list), pointer :: & next => null() methods provided to contains manage the object procedure :: add_item substructure procedure :: delete_list Further classification: end type value containers store copies of objects would like to put anything into a list reference containers cf. C++ class template store references to objects per-list constraints might objects externally managed be needed must be persistent during lifetime of the above code fragment container is not Fortran

©2006-8 LRZ 54 Exploiting the renaming feature (1)

Write container methods once Type definitions here: within a single module type :: list type(dummy) :: stuff module all_types type(list), pointer :: & type :: t1 next => null() : end type end type interface add_item type :: t2 module procedure insert : end interface end type : contains contains : subroutine insert(this, stuff) end module all_types type(list) :: this type(dummy), intent(in) :: & stuff : end subroutine

file list.inc

©2006-8 LRZ 55 Exploiting the renaming feature (2)

Create full set of generics: use all_types use mod_l_t1, l_t1 => list module mod_l_t1 use mod_l_t2, l_t2 => list use all_types, dummy => t1 type(l_t1) :: mylist_t1 include 'list.inc' type(l_t2) :: mylist_t2 end module : module mod_l_t2 call add_item(mylist_t1, o_t1) use all_types, dummy => t2 call add_item(mylist_t2, o_t2) include 'list.inc' : end module Issues: script-generated from full while only one implemen- list of required types tation, somewhat clunky to use Client use: generic only on implementation level, not also requires use of on usage level renaming feature for globals in implementation otherwise type definition of rename also needed is non-unique within list some have problems client with generic resolution (bugs)

©2006-8 LRZ 56 Alternative 1: fpp/cpp Preprocessing: not standard-conforming, but simple

Executing preprocessor module list_GENTYPE use mod_GENTYPE usually automatic for *.F type :: list_GENTYPE files type(GENTYPE) :: stuff specify option otherwise type(list_GENTYPE), & pointer :: next => null() example Intel Fortran: end type ifort ­c mod_type1.f90 interface add_item ifort ­c ­fpp ­DGENTYPE=type1 \ module procedure insert ­o list_type1.o list.f90 end interface contains Apart from not needing subroutine insert(this, stuff) explicit type renaming – type(list) :: this type(GENTYPE), & no substantial intent(in) :: stuff improvement over : previous method end subroutine still cannot perform end module generic naming on client

©2006-8 LRZ 57 Alternative 2: Using fully polymorphic objects module mod_list Features type :: list one implementation class(*), pointer :: stuff type(list), pointer :: & one module next => null() name space pressure reduced on contains client procedure :: add_item enforce type constraint end type contains can also implement value subroutine add_item(this, stuff) container: class(list) :: this allocate(this%stuff, & class(*), intent(in), & source=stuff) target :: stuff : use allocatable component, omit target if (same_type_as(stuff,...)) & attribute then this%stuff => stuff Issues: ! reference container dereferencing contained allocate(this%next) objects else ; ... ; endif requires select type end subroutine end module (partial) offload to client?

©2006-8 LRZ 58 Parametrization of types (1)

Recall character(len=20,kind=c_char) :: line Generalize this concept Intrinsic types: Flavours allowed for with exception of parameters: character only kind type length type parameter parameters are allowed actual value need not be known at allows variable length compile time (“deferred”) strings (finally!) must be determined at run time kind type parameter character(len=:), pointer :: p must be known at compile time character(len=:), allocatable :: v2 however need not necessarily always character(len=122), target :: v1 refer to kind numbers : p => v1 ! p has now len 122 allocate(v2(len=64))

Note: no compiler support today (Feb 2008)

©2006-8 LRZ 59 Parametrization of types (2) Derived types

Exactly analogous to Type parameters are intrinsic types inherited

type, extends(matrix) :: mv(l) type :: matrix(rk, n, m) integer, len :: l integer, kind :: rk real(rk) :: vector(l) integer, len :: n, m end type real(rk) :: entry(n, m) : end type type(mv(dk, :, :, :)), & allocatable :: o_mv declaration of an object : allocate(o_mv(n=15,m=20,l=20)) integer, parameter :: dk = & selected_real_kind(15) can also omit entry in type(matrix(dk, 20, 30)) :: om keyword list if default type(matrix(dk, :, :), & allocatable :: am values for length/kind : type parameters are allocate(am(n=15,m=20)) specified ! by order or keyword

©2006-8 LRZ 60 Parametrization of types (3)

Assumed type parameters Type parameter enquiry can be used for applies to intrinsic and dummy argument object, or derived types select type selector, or inquiry by type parameter allocate statement name only length type type(matrix(...)) o_m parameters : print *, o_m%rk subroutine foo(xm, ...) print *, o_m%n type(matrix(dk, *, *)) :: xm print *, o_m%m : values from actual also works for assumed arguments are taken over type parameters at subroutine call can be used for scalars Methods/Subroutines: and arrays in same must still implement manner separately for each kind

©2006-8 LRZ 61 Conclusion

Support for in Fortran is weak for Fortran 90/95 only slightly improved for Fortran 2003: fully polymorphic objects / interface classes help but do not get you all the way there (dereferencing!) analogue to not available no further improvements planned for Fortran 2008 The hope is that more features will be offered in the post-2008 iteration of the standard

©2006-8 LRZ 62 Part V

Enhancements of I/O functionality

©2006-8 LRZ 63 I/O for derived data types

Non-trivial derived data type : enables binding a subroutine type :: list to an edit descriptor character(len=:), & allocatable :: name type(list) :: o_list integer :: age : ! set up o_list type(list), pointer :: next write(unit, fmt='(dt ...)', ...) & end type o_list can perform I/O using suitable module procedures example shows formatted or TBPs output Disadvantages: bound subroutine called automatically recursive I/O disallowed when dt encountered I/O transfer not easily other variants are enabled by integrable into an I/O stream using generic TBPs or generic interfaces defined by edit descriptor for intrinsic types and arrays can use for hierarchical types or sequence of binary I/O statement

©2006-8 LRZ 64 Binding I/O subroutines to derived types

Interface of subroutines is fixed with exception of the passed object dummy Define as special generic type bound procedure type :: foo generic :: read(formatted) => rf1, rf2 : generic :: read(unformatted) => ru1, ru2contains generic :: write(formatted) => wf1, wf2 : generic :: write(unformatted) => wu1, wu2 generic :: read(formatted) => rf1, rf2 generic :: read(unformatted) => ru1, ru2 generic :: write(formatted) => wf1, wf2 generic :: write(unformatted) => wu1, wu2 end type generic-ness refers to rank, kind parameters of passed object Define via interface block

interface read(formatted) module procedure rf1, rf2 end interface

©2006-8 LRZ 65 DTIO module procedure interface (dummy parameter list determined) subroutine rf1(dtv,unit,iotype,v_list,iostat,iomsg) subroutine wu1(dtv,unit, iostat,iomsg) dtv: v_list (formatted only): scalar of derived type integer, intent(in) - may be polymorphic assumed shape array suitable intent see dt edit descriptor unit: iostat: integer, intent(in) – integer, intent(out) – describes I/O unit or negative scalar, describes error for internal I/O condition iotype (formatted only): iostat_end / iostat_eor character, intent(in) zero if all OK 'LISTDIRECTED', 'NAMELIST' iomsg: or 'DT'//string character(*) - explanation see dt edit descriptor if iostat nonzero

©2006-8 LRZ 66 Limitations for DTIO subroutines

I/O transfers to other units File positioning: than unit are disallowed entry is left tab limit I/O direction also fixed no record termination on internal I/O is OK (and return commonly needed) positioning with Use of the statements rec=... (direct access) or open, close, rewind pos=... (stream access) backspace, endfile is disallowed is disallowed

©2006-8 LRZ 67 Writing formatted output: DT edit descriptor

Example:

type(mydt) :: o_mydt ! formatted writing bound to mydt : write(20, '(dt 'MyDT' (2, 10) )') o_mydt

Available in iotype Available in v_list Empty string if omitted Empty array if omitted both iotype and v_list are available to the programmer of the I/O subroutine determine further parameters of I/O as programmer sees fit

©2006-8 LRZ 68 Example: Formatted DTIO on a linked list

recursive subroutine wl( & this,unit,iotype, & module mod_list vlist,iostat,iomsg) type :: list class(list), intent(in) :: this integer :: age integer, intent(in) :: unit character(20) :: name integer, intent(in) :: vlist(:) type(list), pointer :: next character(len=*), & contains intent(in) :: iotype generic :: & integer, intent(out) :: iostat write(formatted) => wl character(len=*) :: iomsg end type list ! .. locals contains character(len=12) :: pfmt ! continued next slide

©2006-8 LRZ 69 Example (cont'd): DTIO subroutine implementation

! cont'd from previous slide if (iotype != 'DTList') return if (size(vlist) < 2) return ! perform internal IO to generate format descriptor write(pfmt, '(a,i0,a,i0)') & '(i',vlist(1),',a',vlist(2),')' write(unit, fmt=pfmt, iostat=iostat) this%age,this%name if (iostat /= 0 ) return if (associated(this%next)) then ! recursive call call wl(this%next,unit,iotype(3:),vlist,iostat,iomsg) end if end subroutine end module

©2006-8 LRZ 70 Example (cont'd): Client use type(list), pointer :: mylist : ! set up mylist : ! open formatted file to unit write(unit, fmt='(dt 'List' (4,20) )', iostat=is) mylist : ! close unit and destroy list

Final remarks: Unformatted DTIO bound subroutine with shorter argument list is automatically invoked upon execution of write statement

type(mydt) :: o_mydt ! unformatted writing (also) bound to mydt : ! open unformatted file to unit 21 write(21[, rec=...]) o_mydt

additional parameters (e.g. record number) only specifiable in parent data transfer statement

©2006-8 LRZ 71