TYPE real_matrix(kind,n,m) INTEGER,KIND :: kind INTEGER(int64),LEN :: n,m
All type parameters must be explicitly specified to be of type
INTEGER
, but the kind of integer may vary.
Type parameters are always scalar, never arrays.
Within the type definition, “kind” type parameters may be used in
constant expressions, and any type parameter may be used in a specification
expression (viz array bound, character length, or “length” type
parameter value).
For example, the rest of the above type definition might look like:
REAL(kind) value(n,m) END TYPE real_matrix
When declaring entities of such a derived type, the type parameters must be given after the name. For example,
TYPE(real_matrix(KIND(0d0),100,200)) :: my_real_matrix_variableSimilarly, the type parameters must be given when constructing values of such a type; for example,
my_real_matrix_variable = & real_matrix(kind(0d0),100,200)((/ (i*1.0d0,i=1,20000) /))
To examine the value of a derived type parameter from outside the type definition, the same notation is used as for component accesses, e.g.
print *,'Columns =',my_real_matrix_variable%mThus type parameter names are in the same class as component names and type-bound procedure names. However, a type parameter cannot be changed by using its specifier on the left-hand-side of an assignment. Furthermore, the intrinsic type parameters may also be examined using this technique, for example:
REAL :: array(:,:) CHARACTER(*),INTENT(IN) :: ch PRINT *,array%kind,ch%lenprints the same values as for
KIND(array)
and LEN(ch)
.
Note that a kind parameter enquiry is always scalar, even if the object is
an array.
A derived type parameter does not actually have to be used at all within the type definition, and a kind type parameter might only be used within specification expressions. For example,
TYPE fixed_byte(n) INTEGER,KIND :: n INTEGER(1) :: value(n) END TYPE TYPE numbered_object(object_number) INTEGER,LEN :: object_number END TYPEEven though the
fixed_byte
parameter n
is not used in a constant
expression, a constant value must always be specified for it because it has
been declared to be a “kind” type parameter.
Similarly, even though object_number
has not been used at all, a
value must always be specified for it.
This is not quite as useless as it might seem: each numbered_object
has
a single value for object_number
even if the numbered_object
is
an array.
TYPE char_with_maxlen(maxlen,kind) INTEGER,LEN :: maxlen = 254 INTEGER,KIND :: kind = SELECTED_CHAR_KIND('ascii') INTEGER :: len = 0 CHARACTER(len=maxlen,kind=kind) :: value END TYPE ... TYPE(char_with_maxlen) temp TYPE(char_with_maxlen(80)) card(1000) TYPE(char_with_maxlen(kind=SELECTED_CHAR_KIND('iso 10646'))) ucs4_temp
Note that although kind type parameters can be used in constant expressions
and thus in default initialisation, components that are variable-sized
(because they depend on length type parameters) cannot be default-initialised
at all.
Thus value
in the example above cannot be default-initialised.
Further note that unlike intrinsic types, there are no automatic conversions for derived type assignment with different type parameter values, thus given the above declarations,
card(1) = card(2) ! This is ok, maxlen==80 for both sides. temp = card ! This is not allowed - maxlen 254 vs. maxlen 80.
char_with_maxlen
variable.
SUBROUTINE stars(x) TYPE(char_with_maxlen(*)) x x%value = REPEAT('*',x%maxlen) END SUBROUTINE
CHARACTER
and for parameterised derived types, and
work similarly to deferred array bounds.
A variable with a deferred type parameter must have the ALLOCATABLE
or
POINTER
attribute.
The value of a deferred type parameter for an allocatable variable is that
determined by allocation (either by a typed allocation, or by an intrinsic
assignment with automatic reallocation).
For a pointer, the value of a deferred type parameter is the value of the
type parameter of its target.
For example, using the type real_matrix
defined above,
TYPE(real_matrix(KIND(0.0),100,200)),TARGET :: x TYPE(real_matrix(KIND(0.0),:,:)),POINTER :: y, z ALLOCATE(real_matrix(KIND(0.0),33,44) :: y) ! Typed allocation. z => x ! Assumes from the target. PRINT *,y%n,z%n ! Prints 33 and 100.Note that it is not allowed to reference the value of a deferred type parameter of an unallocated allocatable or of a pointer that is not associated with a target.
If a dummy argument is allocatable or a pointer, the actual argument must have deferred exactly the same type parameters as the dummy. For example,
SUBROUTINE sub(rm_dble_ptr) TYPE(real_matrix(KIND(0d0),*,:)),POINTER :: rm_dble_ptr ... TYPE(real_matrix(KIND(0d0),100,200)),POINTER :: x TYPE(real_matrix(KIND(0d0),100,:)),POINTER :: y TYPE(real_matrix(KIND(0d0),:,:)),POINTER :: z CALL sub(x) ! Invalid - X%M is not deferred (but must be). CALL sub(y) ! This is ok. CALL sub(z) ! Invalid - X%N is deferred (but must not be).
INTENT(OUT)
dummy argument.
A final subroutine of a type must be a subroutine with exactly one argument,
which must be an ordinary dummy variable of that type (and must not be
INTENT(OUT)
).
It may be scalar or an array, and when an object of that type is destroyed the
final subroutine whose argument has the same rank as the object is called.
The final subroutine may be elemental, in which case it will handle any rank
of object that has no other subroutine handling it.
Note that if there is no final subroutine for the rank of an object, no
subroutine will be called.
Final subroutines are declared in the type definition after the CONTAINS
statement, like type-bound procedures.
They are declared by a FINAL
statement, which has the syntax
FINAL
[ ::
] name [ ,
name ]...
A simple type with a final subroutine is as follows.
TYPE flexible_real_vector LOGICAL :: value_was_allocated = .FALSE. REAL,POINTER :: value(:) => NULL() CONTAINS FINAL destroy_frv END TYPE ... ELEMENTAL SUBROUTINE destroy_frv(x) TYPE(flexible_real_vector),INTENT(INOUT) :: x IF (x%value_was_allocated) DEALLOCATE(x%value) END SUBROUTINE
If an object being destroyed has finalisable components, any final subroutine for the object-as-a-whole will be called before finalising any components. If the object is an array, each component will be finalised separately (and any final subroutine called will be the one for the rank of the component, not the rank of the object).
For example, in
TYPE many_vectors TYPE(flexible_real_vector) scalar TYPE(flexible_real_vector) array(2,3) CONTAINS FINAL :: destroy_many_vectors_1 END TYPE ... SUBROUTINE destroy_many_vectors_1(array1) TYPE(many_vectors) array1(:) PRINT *,'Destroying a',SIZE(array1),'element array of many vectors' END SUBROUTINE ... TYPE(many_vector) mv_object(3)when
mv_object
is destroyed, firstly
‘destroy_many_vectors_1
’ will be called with mv_object
as its argument; this will print
Destroying a 3 element array of many vectorsSecondly, for each element of the array, both the
scalar
and
array
components will be finalised by calling destroy_frv
on each
of them.
These may be done in any order (or, since they are elemental, potentially
in parallel).
Note that final subroutines are not inherited through type extension; instead, when an object of extended type is destroyed, first any final subroutine it has will be called, then any final subroutine of the parent type will be called on the parent component, and so on.
PROTECTED
attribute may be specified by the PROTECTED
statement or with the PROTECTED
keyword in a type declaration statement.
It protects a module variable against modification from outside the module.
PROTECTED
statement is:
PROTECTED
[ ::
] name [ ,
name ] ...
The PROTECTED
attribute may only be specified for a variable in a
module.
PROTECTED
attribute may only be modified within the
defining module.
Outside of that module they are not allowed to appear in a variable definition
context (e.g. on the left-hand-side of an assignment statement), similar to
INTENT(IN)
dummy arguments.
This allows the module writer to make the values of some variables generally available without relinquishing control over their modification.
MODULE temperature_module REAL,PROTECTED :: temperature_c = 0, temperature_f = 32 CONTAINS SUBROUTINE set_temperature_c(new_value_c) REAL,INTENT(IN) :: new_value_c temperature_c = new_value_c temperature_f = temperature_c*(9.0/5.0) + 32 END SUBROUTINE SUBROUTINE set_temperature_f(new_value_f) REAL,INTENT(IN) :: new_value_f temperature_f = new_value_f temperature_c = (temperature_f - 32)*(5.0/9.0) END SUBROUTINE ENDThe
PROTECTED
attribute allows users of temperature_module
to
read the temperature in either Farenheit or Celsius, but the variables can only
be changed via the provided subroutines which ensure that both values agree.
POINTER
dummy argument may now have the INTENT
attribute.
This attribute applies to the pointer association status, not to the target of
the pointer.
An INTENT(IN)
pointer can be assigned to, but cannot be
pointer-assigned, nullified, allocated or deallocated.
An INTENT(OUT)
pointer receives an undefined association status on entry
to the procedure.
An INTENT(INOUT)
pointer has no restrictions on its use, but the actual
argument must be a pointer variable, not a pointer function reference.
REAL,TARGET :: x(-100:100,-10:10) REAL,POINTER :: p(:,:) p(1:,1:) => xThe upper bound is formed by adding the extent (minus 1) to the lower bound, so in the above example, the bounds of
P
will be 1:201,1:21
.
Note that when setting the lower bound of any rank in a pointer assignment,
the values must be explicitly specified (there is no default of 1 like there
is in array declarators) and they must be specified for all dimensions of
the pointer.
REAL,POINTER :: diagonal(:),matrix(:,:),base(:) ... ALLOCATE(base(n*n)) matrix(1:n,1:n) => base diagonal => base(::n+1) ! ! DIAGONAL now points to the diagonal elements of MATRIX. !
Note that when rank-remapping, the values for both the lower and upper bounds must be explicitly specified for all dimensions, there are no defaults.
TYPE t LOGICAL, PUBLIC :: flag INTEGER, PRIVATE :: state END TYPEThe structure constructor for the type is not usable from outside the defining module if there is any private component that is not inherited, allocatable or default-initialised (see Structure constructor syntax enhancements).
MODULE m TYPE, PRIVATE :: hidden_type CHARACTER(6) :: code END TYPE TYPE(hidden_type), PUBLIC, PARAMETER :: code_green = hidden_type('green') TYPE(hidden_type), PUBLIC, PARAMETER :: code_yellow = hidden_type('yellow') TYPE(hidden_type), PUBLIC, PARAMETER :: code_red = hidden_type('red') END