Документ взят из кэша поисковой машины. Адрес оригинального документа : http://star.arm.ac.uk/f77to90/c10.html
Дата изменения: Sun Feb 11 17:31:30 1996
Дата индексирования: Mon Oct 1 21:24:49 2012
Кодировка:

Поисковые слова: флуоресценция
Generic routines

10. Generic routines

From Fortran 77 (but not from Fortran 66) we are used to have that the elementary functions are generic, which means that a call SIN(1.0) returns a value of type REAL , but SIN (1.0D0) returns a value with a higher precision and of type DOUBLE PRECISION. We now also have the possibility to write our own generic functions or subroutines. Here we first give a complete example of a routine SWAP(A, B), which swaps the values of variables A and B (replaces the value with each other), using different underlying routines depending on the type of the variables REAL, INTEGER or CHARACTER.

       PROGRAM SWAP_MAIN

       IMPLICIT NONE

       INTEGER        :: I, J, K, L

       REAL           :: A, B, X, Y

       CHARACTER      :: C, D, E, F

       INTERFACE SWAP

              SUBROUTINE SWAP_R(A, B)

              REAL, INTENT (INOUT)          :: A, B

              END SUBROUTINE SWAP_R

              SUBROUTINE SWAP_I(A, B)

              INTEGER, INTENT (INOUT)       :: A, B

              END SUBROUTINE SWAP_I

              SUBROUTINE SWAP_C(A, B)

              CHARACTER, INTENT (INOUT)     :: A, B

              END SUBROUTINE SWAP_C

       END INTERFACE



       I = 1   ; J = 2       ;       K = 100 ; L = 200

       A = 7.1 ; B = 10.9    ;       X = 11.1; Y = 17.0

       C = 'a' ; D = 'b'     ;       E = '1' ; F = '"'



       WRITE (*,*) I, J, K, L, A, B, X, Y, C, D, E, F

       CALL SWAP(I, J) ; CALL SWAP(K, L)

       CALL SWAP(A, B) ; CALL SWAP(X, Y)

       CALL SWAP(C, D) ; CALL SWAP(E, F)

       WRITE (*,*) I, J, K, L, A, B, X, Y, C, D, E, F

       END



       SUBROUTINE SWAP_R(A, B)

       IMPLICIT NONE

       REAL, INTENT (INOUT)                 :: A, B

       REAL                                 :: TEMP

               TEMP = A ; A = B ; B = TEMP

       END SUBROUTINE SWAP_R



       SUBROUTINE SWAP_I(A, B)

       IMPLICIT NONE

       INTEGER, INTENT (INOUT)              :: A, B

       INTEGER                              :: TEMP

               TEMP = A ; A = B ; B = TEMP

       END SUBROUTINE SWAP_I



       SUBROUTINE SWAP_C(A, B)

       IMPLICIT NONE

       CHARACTER, INTENT (INOUT)            :: A, B

       CHARACTER                            :: TEMP

               TEMP = A ; A = B ; B = TEMP

       END SUBROUTINE SWAP_C

The above works very well, but the user is not so happy to have to care with all the information about SWAP in these three different variants in the program. The solution to this is to move everything that has to do with the SWAP into a module and then can the module can be used from the main program with the statement USE module name. Please note that in the INTERFACE of the module the specific statement MODULE PROCEDURE has to be used in order to avoid that the routines are specified both in the INTERFACE and in the CONTAINS part. At the use you will have to link both the module and the main program together, e.g. with the statement

	f90 part1.f90 part2.f90

Here the modules follow, it could be in the file part2.f90,

MODULE BO

       INTERFACE SWAP

              MODULE PROCEDURE SWAP_R, SWAP_I, SWAP_C

       END INTERFACE

CONTAINS



       SUBROUTINE SWAP_R(A, B)

       IMPLICIT NONE

       REAL, INTENT (INOUT)                 :: A, B

       REAL                                 :: TEMP

               TEMP = A ; A = B ; B = TEMP

       END SUBROUTINE SWAP_R



       SUBROUTINE SWAP_I(A, B)

       IMPLICIT NONE

       INTEGER, INTENT (INOUT)              :: A, B

       INTEGER                              :: TEMP

               TEMP = A ; A = B ; B = TEMP

       END SUBROUTINE SWAP_I



       SUBROUTINE SWAP_C(A, B)

       IMPLICIT NONE

       CHARACTER, INTENT (INOUT)            :: A, B

       CHARACTER                            :: TEMP

                  TEMP = A ; A = B ; B = TEMP

       END SUBROUTINE SWAP_C

END MODULE BO

Here follows the main program, which is now cleaned of all uninteresting information about SWAP. It could be in the file part1.f90.

PROGRAM SWAP_MAIN

USE BO

       IMPLICIT NONE

       INTEGER                    :: I, J, K, L

       REAL                       :: A, B, X, Y

       CHARACTER                  :: C, D, E, F



       I = 1  ;   J = 2         ;     K = 100 ; L = 200

       A = 7.1 ;  B = 10.9      ;     X = 11.1; Y = 17.0

       C = ' a' ; d = 'b'       ;     E = '1' ; F = '"'



       WRITE  (*,*) I, J, K, L, A, B, C, D, E, F

       CALL  SWAP (I, J)  ;  CALL SWAP (K, L)

       CALL  SWAP (A, B)  ;  CALL SWAP (X, Y)

       CALL  SWAP (C, D)  ;  CALL SWAP (E, F)

       WRITE (*,*) I, J, K, L, A, B, X, Y, C, D, E, F

END


Last modified: 16 November 1995
boein@nsc.liu.se