TYPE TypeName
type1 [,attr] :: element1;
type2 [,attr] :: element2;
type3 [,attr] :: element3;
...
END TYPE [TypeName]
|
Example:
TYPE myStruct
INTEGER :: i;
REAL :: f;
END TYPE myStruct
|
TYPE(TypeName) :: variableName |
Example:
TYPE(myStruct) :: x, A[3]; |
Also, variables of a user-defined type are like class variables in C++
TYPE(TypeName) :: x x%i = the component variable "i" in "x" x = The entire object "x" (all components) |
Example:
PROGRAM main
IMPLICIT NONE
TYPE myStruct
INTEGER :: i;
REAL :: f;
END TYPE myStruct
TYPE(myStruct) :: A, B;
A%i = 4 !! Assign 4 to var i in A
A%f =3.14 !! Assign 4 to var f in A
B = A !! Copy both i and f from A to B
END PROGRAM
|
|
|
SUBROUTINE print( x ) TYPE myStruct INTEGER :: i; REAL :: f; END TYPE myStruct TYPE(myStruct) :: x print *, "myStruct x = ", x END SUBROUTINE |
|
Humans will never say that, but a compiler can because it has be programmed to say that :-)...
|
Clearly, f90 uses index (key) equivalence
We must have one single type definition for both compile units
|
Therefore, you must define the user-defined type in a mudule unit:
MODULE moduleName
User Type Definition
END MODULE
|
MODULE myStructModule
TYPE myStruct
INTEGER :: i
REAL :: f
END TYPE myStruct
END MODULE
|
f90 -c myStructModule.f90 |
After the compialtion, you will find a file mystructmodule.mod (all lower case), in your directory
USE moduleName |
reads in the compiled code of a module.
The types defined in the module will now be accessible to a program unit
|
Example:
MODULE myStructModule
TYPE myStruct
INTEGER :: i;
REAL :: f;
END TYPE myStruct
END MODULE
|
f90 -c myStructModule.f90 f90 type02a.f90 |
SUBROUTINE print( x ) USE myStructModule !! Defines TYPE(myStruct) IMPLICIT NONE TYPE(myStruct) :: x print *, "myStruct x = ", x END SUBROUTINE |
SUBROUTINE print( x ) USE myStructModule IMPLICIT NONE TYPE(myStruct) :: x x%i = x%i + 1000 !! <--- proof of pass-by-reference x%f = x%f + 1000 END SUBROUTINE |
FUNCTION MyFuncName(Param1, Param2, ...) USE userTypeModule !! Must preceed IMPLICIT NONE IMPLICIT NONE TYPE(userType) MyFuncName .. function body END FUNCTION |
Or:
FUNCTION MyFuncName(Param1, Param2, ...) RESULT(x) USE userTypeModule !! Must preceed IMPLICIT NONE IMPLICIT NONE TYPE(userType) x .. function body END FUNCTION |
MODULE complexType
TYPE complexNumber
REAL :: re
REAL :: im
END TYPE complexNumber
END MODULE
|
INTERFACE
FUNCTION MyFuncName(Param1, Param2, ...)
USE userTypeModule
... (declare parameters)
TYPE(userType) MyFuncName
END FUNCTION
END INTERFACE
|
Or:
INTERFACE
FUNCTION MyFuncName(Param1, Param2, ...) RESULT(x)
USE userTypeModule
... (declare parameters)
TYPE(userType) x
END FUNCTION
END INTERFACE
|
MODULE complexType
TYPE complexNumber
REAL :: re
REAL :: im
END TYPE complexNumber
END MODULE
|
MODULE complexType
TYPE complexNumber
REAL :: re
REAL :: im
END TYPE complexNumber
END MODULE
|
f90 -c complexType.f90 f90 type04.f90 |
MODULE MyModule TYPE myType INTEGER :: i REAL :: f END TYPE END MODULE |
MODULE MyModule TYPE myType INTEGER :: i REAL :: f END TYPE END MODULE |
|
|
REAL, DIMENSION(:), ALLOCATABLE :: A ALLOCATE(A(4)) A(1) = 1234 |
REAL, DIMENSION(:), POINTER :: B ALLOCATE(B(4)) B(1) = 1234 |
|
(Significant performance differences have been reported with some compilers.)
I got a few seconds in performance difference ...
PROGRAM main USE myStructModule IMPLICIT NONE TYPE(myStruct) :: A CALL Print_myStruct(A) !! Pass by Reference... END PROGRAM |
/* Need to describe data to C ! */
struct myStruct
{
int i;
float f;
};
void print_mystruct_(struct myStruct *x)
{
printf("%d %f\n", x->i, x->f);
}
|