| ||
|
|
Fortran 2000 Programme The Group Comment Overview Exceptions and C Derived types OO features Report About Us FSG Home page Joining the Group Contact details Important Disclaimer |
Malcolm Cohen The Numerical Algorithms Group Ltd. Please note: this HTML file has been constructed directly from the slides used in the presentation. Fortran 2000: DME Overview
ISO/IEC TR 15581 - just briefly
Rationale:
Allocatable components
TYPE t
REAL,ALLOCATABLE :: c(:,:)
END TYPE
SUBROUTINE s
TYPE(t) x
TYPE(t),SAVE :: y
...
END SUBROUTINE
Allocatable components: assignment
(So the assignment statement
x = y
acts like
IF (ALLOCATED(x%c)) DEALLOCATE(x%c)
IF (ALLOCATED(y%c)) THEN
ALLOCATE(x%c(lbound(y%c,1):ubound(y%c,1), &
lbound(y%c,2):ubound(y%c,2)))
x%c = y%c
END IF
And this is recursively applied for nested allocatable components.)
Rationale: Otherwise the bookkeeping would be prohibitive. Allocatable components: example
MODULE matrix_module
TYPE real_matrix
REAL,ALLOCATABLE :: value(:,:)
END TYPE
INTERFACE OPERATOR(*)
MODULE PROCEDURE multiply_mm
END INTERFACE
...
CONTAINS
TYPE(real_matrix) FUNCTION multiply_mm(a,b) RESULT(c)
TYPE(real_matrix),INTENT(IN) :: a,b
ALLOCATE(c%value(size(a%value,1),size(b%value,2)))
c%value = matmul(a%value,b%value)
END FUNCTION
END
PROGRAM example
USE matrix_module
TYPE(real_matrix) :: x,y,z
...
x = y*z
...
END
Better than the pointer component version because it
Allocatable dummy arguments
SUBROUTINE load(arr,unit)
REAL,ALLOCATABLE,INTENT(OUT) :: arr(:,:,:)
INTEGER,INTENT(IN) :: unit
INTEGER n1,n2,n3
READ(unit) n1,n2,n3
ALLOCATE(arr(n1,n2,n3))
READ(unit) arr
END
Notes:
Allocatable function results
FUNCTION read_array(unit) RESULT(array)
REAL,ALLOCATABLE :: array(:,:,:)
INTEGER n1,n2,n3
READ(unit) n1,n2,n3
ALLOCATE(array(n1,n2,n3))
READ(unit) array
END
Notes:
IMPORT statement
Example: IMPORT :: derived_type, working_precision_kind IMPORT statement example
MODULE my_real_module
TYPE my_real
PRIVATE
...
END TYPE
CONTAINS
FUNCTION integrate(fun,from,to)
TYPE(my_real) integrate,from,to
INTENT(IN) from,to
INTERFACE
FUNCTION fun(x)
IMPORT my_real
TYPE(my_real) fun,x
INTENT(IN) x
END
END INTERFACE
...
END FUNCTION
END
Without IMPORT, either
Abstract interfaces
ABSTRACT INTERFACE
REAL FUNCTION fun_R_x_R_to_R(x,y)
REAL,INTENT(IN) :: x,y
END
END INTERFACE
PROCEDURE(fun_R_x_R_to_R) :: f1, f2
A procedure with the POINTER attribute is a "procedure pointer". Note that this is not the same as a function result having the POINTER attribute.
Procedure pointers: "implicit interface" Example 1: An explicitly typed function. PROCEDURE(REAL),POINTER :: real_fun_pointer REAL,EXTERNAL :: f1 ... real_fun_pointer => f1 ... PRINT *,real_fun_pointer(1.5,2.0) PRINT *,f1(1.5,2.0) Example 2: A subroutine or an implicitly typed function.
PROCEDURE(),POINTER :: pp
EXTERNAL :: sub
...
pp => sub
...
CALL pp('hi')
Procedure pointers: "explicit interface" Example 1: PROCEDURE(fun_R_x_R_to_R),POINTER :: fptr fptr => f2 Example 2:
ABSTRACT INTERFACE
SUBROUTINE cbproc
END
END INTERFACE
TYPE callback_list
PROCEDURE(cbproc),NOPASS,POINTER :: callback
TYPE(callback_list),POINTER :: next
END TYPE
PROCEDURE statement: continued This statement can also specify:
E.g. To save and initialise a procedure pointer: PROCEDURE(REAL),POINTER,SAVE :: p => NULL() This statement may also be used to declare ordinary implicit-interface procedures: ! Equivalent to "REAL,EXTERNAL :: f" PROCEDURE(REAL) :: f ! ! Equivalent to "EXTERNAL s" PROCEDURE() :: s Dynamic (deferred) type parameters
NOTE: Extension - ALLOCATABLE scalars.
CHARACTER(:),POINTER :: p READ *,n ALLOCATE(CHARACTER(n)::p) READ *,p ... DEALLOCATE(p) TYPE myvarchar CHARACTER(:),ALLOCATABLE :: value END TYPE New attributes
PROTECTED:
VALUE:
VOLATILE:
Also: ASYNCHRONOUS - for asynchronous i/o. BIND - for C interoperability. PROTECTED example
MODULE m
INTEGER,PROTECTED,PUBLIC :: count_calls
CONTAINS
SUBROUTINE call
count_calls = count_calls + 1
END SUBROUTINE
END
PROGRAM protected_example
USE m
...
PRINT *,count_calls ! ok
count_calls = 10 ! not ok
VALUE example
PROGRAM value_example
REAL :: x = 3
CALL s(x)
PRINT *,x ! x is still 3
CONTAINS
SUBROUTINE s(q)
REAL,VALUE :: q
q = q + 1 ! Alters q without altering x
PRINT *,q ! q is now 4
END SUBROUTINE
END
VOLATILE example
CHARACTER,TARGET,VOLATILE :: keystroke
CALL set_receive_keystrokes(keystroke)
DO i=1,1000
IF (keystroke==ACHAR(3)) EXIT
CALL some_lengthy_calculation(PART=i)
END DO
IF (i==1001) THEN
PRINT *,'Calculation complete'
ELSE
PRINT *,'Exited via Ctrl-C'
END IF
Note: A major motivation for VOLATILE was to be able to use certain
MPI-2 calls.
Pointer extensions
INTENT:
Lower Bounds:
Rank Remapping:
POINTER INTENT
SUBROUTINE pex(p1,p2,p3)
INTENT(IN) :: p1
INTENT(INOUT) :: p2
INTENT(OUT) :: p3
...
p1 = 2 ! ok
p1 => p2 ! not permitted
END
Notes:
POINTER Lower Bounds Lower bounds may be specified on pointer assignment.
REAL,POINTER :: a(:),b(:),c(:) ... ALLOCATE(a(-10:10)) ! Lower bound of A is -10 b => a ! Lower bound of B is -10 c => a(-5:5) ! Lower bound of C is 1 c(-5:) => a(-5:5) ! Lower bound of C is -5 The upper bounds are derived from the specified lower bounds and the extent. POINTER Rank Remapping Motivation: ability to have pointers to diagonals of matrices.
REAL,ALLOCATABLE,TARGET :: base_array(:) REAL,POINTER :: matrix(:,:) REAL,POINTER :: diagonal(:) ... ALLOCATE(base_array(n*n)) matrix(1:n,1:n) => base_array ! rank remapping diagonal => base_array(::n+1) Notes:
Motivation:
Extensions:
Array Constructors continued
Type specification syntax:
Examples:
[ REAL :: ] ! zero-sized array
(/ (3.5,i=1,0) /) ! F95 version
[ CHARACTER(n) :: ] ! zero-sized array
(/ (repeat('x',n),i=1,0) /) ! F95 version dubious
[ CHARACTER(50) :: 'a', 'bcdef' ] ! padded
Initialisation expressions: anything goes Initialisation expressions are used for:
In Fortran 95, these expressions can only use INTEGER, LOGICAL and CHARACTER intrinsic functions, not REAL functions like ATAN. In Fortran 2000, these expressions can use any intrinsic function.
! ! Probably a poor approximation to pi. ! REAL,PARAMETER :: pi = 4*atan(1.0) MAX and MIN for character type The MAX and MIN intrinsic functions have been extended to operate on values of type CHARACTER.
CHARACTER(*) x,y,z ... PRINT *,max(x,y,z) These intrinsics use native character set ordering (as provided by <, <=, >, >=), not the ASCII character set ordering (as provided by LLT, LLE, LGT and LGE). "Enhanced" complex constants In previous Fortrans, complex literal constants have optionally signed integer and real literal constants for the real and imaginary parts. In Fortran 2000, the real and imaginary parts may also be named constants (PARAMETERs). Old style: REAL,PARAMETER :: pi = 22/7 COMPLEX c c = cmplx(pi,-pi) New style: REAL,PARAMETER :: pi = 22/7 REAL,PARAMETER :: minuspi = -pi COMPLEX c c = (pi,minuspi)
ASSOCIATE construct The ASSOCIATE construct allows the association of a complicated variable or expression with a simple name (somewhat like the Pascal "with" construct). The "associate-name" is definable (i.e. like a variable) only if it is associated with a variable.
ASSOCIATE(x=>cos(phi/2)*sin(eta),j=>mod(i,3))
PRINT *,x
ASSOCIATE(y=>a(ifun())%b(j))
y%n = 0
y%value = y%value + x
END ASSOCIATE
x = 0 ! This is not allowed
END ASSOCIATE
Expressions in the ASSOCIATE statement are evaluated once only, at the start of the associate block. Mixed component accessibility With type extension (q.v.), the situation naturally arises where some components are private and others are public. For consistency, it is therefore possible to explicitly specify the accessibility at a per-component level.
TYPE t
REAL,PUBLIC :: accessible_component
REAL,PRIVATE :: inaccessible_component
END TYPE
Public entities of private type In Fortran 95, entities of a PRIVATE type must themselves be private. There is no technical reason for this; other situations can arise when an entity is visible but its type is not (e.g. particularly with host association). In Fortran 2000, this restriction was deemed to be unnecessary and is lifted. Public entities of private type ... An example of the feature is to provide constants which can be used as actual arguments, but since the type is private, cannot be assigned to variables.
MODULE m
TYPE,PRIVATE :: t
INTEGER hiddenvalue
END TYPE
TYPE(t),PUBLIC :: action_1 = t(1)
TYPE(t),PUBLIC :: action_2 = t(2)
CONTAINS
SUBROUTINE act(action)
TYPE(t) action
...
END SUBROUTINE
END
Type Aliases
TYPEALIAS :: byte=>INTEGER(1), single=>REAL(1) TYPE(byte) b TYPE(single) f The type parameters in a TYPEALIAS statement must be initialisation expressions (i.e. constant).
SUBROUTINE s(ch,n)
TYPEALIAS :: assumed_char=>CHARACTER(*) ! Bad
TYPEALIAS :: varchar=>CHARACTER(n) ! Bad
More Type Aliasing A type alias can be used to switch between intrinsic types and derived types with a single edit:
! Uncomment one of the following: ! TYPEALIAS :: wreal => REAL ! TYPEALIAS :: wreal => DOUBLE PRECISION ! TYPEALIAS :: wreal => TYPE(very_big_reals) A typealias is a name for a type-spec, not a type; thus it has no type parameters of its own.
TYPE(single(2)) double_variable ! Not ok For much the same reason, one cannot extend a type alias, even if it is an alias for an extensible type (q.v.).
TYPEALIAS :: alias => extensible_type TYPE,EXTENDS(alias) :: newtype ! Not ok Enumeration Types
ENUM :: colour
ENUMERATOR :: red,orange=1000,yellow=2,green
END ENUM
...
TYPE(colour) paintwork
paintwork = miles/gallon ! ok!
The enumerator values are obtained by a simple algorithm: thus red==0 and green==3. More Enumeration Types One can specify the integer kind instead of letting the compiler pick it:
ENUM(KIND=selected_int_kind(2)) bite ... One can request C interoperability:
ENUM,BIND(C) :: c_enum ... C interoperability really means requesting the compiler to use the same algorithm for picking the integer kind that the C compiler would use for the same enumerator list (viz same values in the same order).
|
| TOP OF PAGE | FORTRAN 2000 FORUM | FSG HOME | © Copyright The British Computer Society |