|
|
module module_name .... end module |
f90 -c ModuleProgFile.f90 |
The f90 compiler will produces a module file:
module_name.mod |
PROGRAM Main USE ModuleName ! must be the first statement .... |
MODULE ModuleName Specification Part 1. can USE other module 2. user-defined types 3. (global) constants 4. (global) variables 5. generic function's interfaces CONTAINS Implementaion Part contain subroutines/functions described in the subprogram interfaces END MODULE [ModuleName] |
|
MODULE ListModule ! ====================== Specification part =============== TYPE ListElem REAL :: value; TYPE(ListElem), POINTER :: next; END TYPE ListElem CONTAINS ! ====================== Implementation part =============== ! ----------------------- ! Insert at head ! ----------------------- FUNCTION InsertList(head, elem) IMPLICIT NONE type( ListElem ), pointer :: head, elem type( ListElem ), pointer :: InsertList elem%next => head InsertList => elem END FUNCTION ! ----------------------- ! Delete at head ! ----------------------- FUNCTION DeleteList(head) IMPLICIT NONE type( ListElem ), pointer :: head type( ListElem ), pointer :: DeleteList type( ListElem ), pointer :: h IF ( ASSOCIATED(head) ) THEN h => head head => head%next deallocate(h) END IF DeleteList => head END FUNCTION ! ----------------------- ! Print ! ----------------------- SUBROUTINE PrintList(head) IMPLICIT NONE type( ListElem ), pointer :: head type( ListElem ), pointer :: ptr ptr => head print *, "The list is: " DO WHILE ( associated(ptr) ) print *, ptr%value ptr => ptr%next END DO print * END SUBROUTINE END MODULE |
PROGRAM ListProcessing Use ListModule type( ListElem ), pointer :: head type( ListElem ), pointer :: newElem integer, parameter :: N = 4 NULLIFY( head ) ! Empty list ! --------------------------------------------- ! Add the N elements ! --------------------------------------------- DO i = 1, N ALLOCATE( newElem ) CALL random_number( newElem%value ) head => InsertList(head, newElem) CALL PrintList(head) END DO head => DeleteList(head) END PROGRAM |
How to compile and run:
f90 -c list-module.f90 // list-module.o + listmodule.mod f90 -c main-list.f90 // main-list.o f90 main-list.o list-module.o |
NOTE: you need to include the "list-module.o" file because the module contains the implementation of the functions/subroutines
MODULE MatrixOps ! ====================== Specification part =============== TYPE MyReal REAL x ! To avoid conflict with REAL END TYPE MyReal INTERFACE operator(*) MODULE PROCEDURE MatVecMult, MatMatMult END INTERFACE ! ====================== Implementation part =============== CONTAINS ! ----------------------- ! Matrix * Vector ! ----------------------- FUNCTION MatVecMult(A, v) result (w) implicit none TYPE(MyReal), dimension(:,:), INTENT(IN) :: A TYPE(MyReal), dimension(:), INTENT(IN) :: v TYPE(MyReal), dimension( SIZE(A,1) ) :: w integer :: j integer :: N N = SIZE(A,2) w(:).x = 0.0 !! clear whole vector DO j = 1, N w(:).x = w(:).x + v(j).x * A( :, j ).x END DO END FUNCTION ! ----------------------- ! Matrix * Matrix ! ----------------------- FUNCTION MatMatMult(A, B) result (C) implicit none TYPE(MyReal), dimension(:,:), INTENT(IN) :: A TYPE(MyReal), dimension(:,:), INTENT(IN) :: B TYPE(MyReal), dimension( size(A,1), size(B, 2) ) :: C integer :: M, N, i, j M = size(A,1) N = size(B,2) C(:,:).x = 0.0 !! clear whole matrix DO i = 1, M DO j = 1, N C(:,i).x = C(:,i).x + B(j,i).x*A(:,j).x END DO END DO END FUNCTION END MODULE |
PROGRAM Main USE MatrixOps implicit none TYPE(MyReal), dimension( 3, 3 ) :: A, B, C TYPE(MyReal), dimension( 3 ) :: v1, v2 v2 = A * v1 !! Matrix * Vector C = A * B !! Matrix * Matrix END PROGRAM |
How to compile and run:
f90 -c matrix-module.f90 // matrix-module.o + matrixmodule.mod f90 -c main-matrix.f90 // main-list.o f90 main-matrix.o matrix-module.o |
NOTE: you need to include the "matrix-module.o" file because the module contains the implementation of the functions/subroutines
|
The access mode can be changed using:
PRIVATE ! Permanent change ! - Items that follows will have PRIVATE access PUBLIC ! Permanent change ! - Items that follows will have PUBLIC access PRIVATE :: x, y ! One time change ! - Items x, y will have PRIVATE access PUBLIC :: x, y ! One time change ! - Items x, y will have PUBLIC access |
MODULE MyModuleName PRIVATE !! Make everything in module private by default PUBLIC :: var1, func1 !! Make these items public PUBLIC :: x, y, z, OPERATOR(.add.) PRIVATE :: u, v, w, ASSIGNMENT(=), OPERATOR(*) integer, PRIVATE :: a, b, c !! Another way to make it private .... END MODULE |
USE module_name, newName1 => Name1, & newName2 => Name2, ... |
|
USE module_name, ONLY : name1, name2, ... |
USE module_name, ONLY : new1 => name1, & new2 => name2, ... |