FORTRAN Part 3:Structured Programming, Procedures

FORTRAN Part 3:Structured Programming, Procedures

Introduction to Fortran95 Programming Part III By Deniz Savas, CiCS, Shef. Univ., 2018 Course Summary • Program Units: Subroutines Functions Modules Common Blocks Include Statements • More on Pointers Program Units • Main Program • External Procedures – Subroutines – Functions • Internal Procedures – Subroutines – Functions • Modules • Common Blocks Program Structure [PROGRAM [program_name] ] [ Data specification & declaration_statements] [executable_statements] [contains] [internal_procedures] END [ PROGRAM [program_name] Main program containing internal procedure(s) [PROGRAM [program_name] ] [ declaration_statements] executable_statements CONTAINS [ internal procedure(s)] : END [ PROGRAM [program_name] ] Note: Everything is contained in one file. Main program containing external procedure(s) [PROGRAM [program_name] ] [ declaration_statements] executable_statements END [ PROGRAM [program_name] ] [procedure] : [procedure] Note: Procedures can be contained in separate files. Procedures • There are two types of procedures, namely SUBROUTINE and FUNCTION • The only difference between a subroutine and a function is that a function returns results as its value. • There is no specification difference between internal and external procedures. • Functions are utilised by referencing their name in an expression where as subroutines are CALL’ed. A typical program structure with internal procedures. PROGRAM declarations executable statements CONTAINS SUBROUTINE abc (… ) declarations executable statements END SUBROUTINE def(…) declarations executable statements END FUNCTION ghi( … ) declarations executable statements END END A typical program structure. PROGRAM declarations executable statements END SUBROUTINE abc (… ) declarations executable statements END SUBROUTINE def(…) declarations executable statements END FUNCTION ghi( … ) declarations executable statements END Subroutines SUBROUTINE name [ ( argument_list ) ] declaration executable statements END EXAMPLE: SUBROUTINE FILTER ( VOLTAGE, CURRENT) REAL , INTENT(IN) :: VOLTAGE REAL,INTENT(INOUT) :: CURRENT executable_statements END Functions [type] FUNCTION name [ ( argument_list ) ] declaration executable statements END EXAMPLE: REAL FUNCTION ENERGY ( MASS, VELOCITY) REAL , INTENT(IN) :: MASS , VELOCITY ENERGY = MASS*VELOCITY*VELOCITY END Subroutines & Functions SUBROUTINE SUB1 ( A , B , C ) REAL , INTENT(IN) :: A,B PROGRAM xxxx REAL INTENT(OUT) :: C : : CALL SUB1( A,B,C) C= ….. RETURN : : : : : C= …. RETURN Y= FUNC1( D,E) END REAL FUNCTION FUNC1 ( D , E ) REAL , INTENT(IN) :: D , E : : : END FUNC1 = ……. RETURN END Using Subroutines and Functions • Assuming the declarations in the previous two slides, the following are valid statement which use these procedures. REAL :: VOLT(10) , CUR(10) , REAL :: MASS,V , A , ENERGY : DO I = 1, 10 CALL FILTER(V(I) , CUR(I) ) END DO A = SQRT(MASS)*ENERGY(MASS,V ) Scope of Variables The rules governing this ‘Referability’ is called the scoping rules. For any variable or label scoping rules define the parts of the program where this item is visible. Variables declared within a program or subroutine or function (referred to as ‘program units’) are accessible from anywhere within that program unit and also other program units CONTAIN’ed within it. Scope of Variables PROGRAM TEST REAL :: BASE ,X(10) ,Y(20) BASE = 123.4 CALL NORMALISE(X) CALL NORMALISE(Y) CONTAINS ! Thus the subroutine is internal to program test …. SUBROUTINE NORMALISE(ARRAY) REAL :: ARRAY(:) ARRAY = ARRAY/BASE END SUBROUTINE NORMALISE END PROGRAM TEST Variables BASE, X and Y are available for use in subroutine NORMALISE. Scope of Variables continued … PROGRAM test REAL :: BASE ,X(10) ,Y(20) BASE = 123.4 CALL NORMALISE(X) CALL NORMALISE(Y) END program test SUBROUTINE NORMALISE(ARRAY) REAL :: ARRAY(:) ARRAY = ARRAY/BASE END subroutine normalise None of the variables BASE,X or Y are available in the subroutine NORMALISE. Because BASE is not available, this program will not work! When should I use Internal Procedures • PREFER AN INTERNAL PROCEDURE; – If it is needed to be called from only one program unit. – If you are accessing a lot of variables which will make the argument list rather large. – If you do not want that routine to be available from any other routine. • Otherwise use the EXTERNAL form Subroutine & Function Arguments Arguments enable data exchange between the calling/ invoking and the called/invoked subroutine/function. The way the data is exchanged can be specified more precisely by the following keywords. • Intent : Defines the ability to modify the arguments. • Keyword : Enables us to pass arguments in an order independent way. • Optional : Allows us to make some arguments optional. • Recursive, Result : Needed for recursive invocation. Array valued functions allow array values to be returned. The Use of Intent Attribute SUBROUTINE DISTANCE( P1 , P2 , DIST,N) INTEGER , INTENT(IN) :: N REAL ,INTENT(IN) :: P1(N) , P2(N) REAL , INTENT(OUT) : DIST DIST = 0.0 DO I = 1 , N DIST = DIST + ( P1(I) -P2(I) ) **2 END DO DIST = SQRT ( DIST ) RETURN END Intent Examples cont. REAL FUNCTION SWAPNSUM ( A , B ) REAL , INTENT(INOUT) : A , B REAL :: TEMP TEMP = A A = B B = TEMP SWAPNSUM = A + B END Exercises • Perform exercises (9a) and (9b) that re-writes the answer to exercise (7) by using functions and/or subroutines. • Perform Exercises (10) Using Keyword Arguments INTERFACE SUBROUTINE GETDET ( AREA , DENSIT ,C , D , ELEV ) REAL, OPTIONAL,INTENT(INOUT) :: AREA,DENSIT,C,D,ELEV END SUBROUTINE GETDET END INTERFACE : CALL GETDET ( X,Y,Z,W,Q ) CALL GETDET ( X,Y, ELEV=Q,D=W, C=Z) CALL GETDET ( AREA=X,DENSIT=Y ,ELEV=Q ,C=Z,D=W) ! All above three calls are identical in effect. Optional Arguments OPTIONAL & KEYWORD ARGUMENTS CALL GETDET(V,W, X,Y,Z ) CALL GETDET(V,W,X) CALL GETDET( C=X, ELEV=Z ) CALL GETDET(V,W,D=Y) : : SUBROUTINE GETDET ( AREA , DENSIT ,C , D , ELEV ) REAL, OPTIONAL,INTENT(INOUT) :: AREA,DENSIT,C,D,ELEV : END Always Use INTERFACE to declare External Routines with Optional Arguments PROGRAM MAIN INTERFACE SUBROUTINE SOLVE ( A , B ,C , D , E ) REAL , OPTIONAL, INTENT(INOUT) :: A,B,C,D,E END SUBROUTINE SOLVE FUNCTION ZZZ : END FUNCTION ZZZ END INTERFACE : CALL SOLVE ( NEWX , E=DELTA_SOFAR ) USE function PRESENT to check the presence of an optional argument SUBROUTINE SOLVE ( A , B ,C , D , E ) REAL , OPTIONAL, INTENT(INOUT) :: A,B,C,D,E : IF ( PRESENT( D) ) THEN DD = D ELSE DD = 0.001 ENDIF : END Result Clause & Recursive Functions RECURSIVE FUNCTION FACTORIAL ( N ) RESULT (MULT) INTEGER :: MULT INTEGER, INTENT(IN) :: N IF( N = = 1 ) THEN MULT = 1 ELSE MULT = N*FACTORIAL( N-1) ENDIF RETURN END ! Note: INTEGER RECURSIVE FUNCTION( ...) is also valid syntax. Array Valued Functions FUNCTION NORM( A ) REAL, INTENT=IN :: A REAL , DIMENSION(SIZE(A) ) :: NORM REAL : MINI , MAXI MINI = MINVAL(A) MAXI = MAXVAL(A) IF ( MINI - MAXI .LE. 0.0 ) THEN NORM = 0.0 ELSE NORM = ( A - MINI) / (MAXI-MINI) RETURN END FUNCTION NORM Exercises on PC platforms Perform exercise (8c) from the exercises sheet •We shall use the Salford FTN95 compiler. •Integrated development environment is PLATO. •It is just as easy to work using COMMAND SHELL and a few commands: Example: 1. In the Fortran Command shell move into directory named optpath. cd optpath 2. Compile opath3.f90 with debugging flags ftn95 opath3 /undef /debug /link 3. Run it under debugger sdbg opath3.exe Common Blocks • Common blocks can be used to make a set of variables available to a selected set of program units without having to use INTERNAL program units. • Syntax: COMMON /name/ variables_list EXAMPLE: REAL :: ARATIO , RATE(10,10) INTEGER :: TEMP COMMON /RATIOS/ ARATIO, RATE, TEMP Common Blocks • Variables which are declared to be in a COMMON BLOCK can be made available to any program unit by declaring the same set of variables and the common block. • A common block is a continuous area of memory where the variables are stored in the order of declaration in the COMMON statement, rather than the names. Therefore it is vitally important to keep to the same order in all declarations of the same COMMON BLOCK. Common Blocks & INCLUDE Files • To avoid mistakes use INCLUDE files. • INCLUDE statement is not part of the FORTRAN specifications but all known compilers accept it. • The statement: INCLUDE ‘filename’ makes the compiler read the contents of the specified file at that point, pretending that it is all part of the source inserted at that point. Common Blocks & INCLUDE Files • By putting the declarations for all the variables within a common block and the COMMON statement which follows it into a file and using the INCLUDE ‘filename’ statement in every subroutine or function which uses that common block, we can ensure that there are no problems arising from misspelling or mis-declaration of common block variables. INCLUDE: examples • Create a file called RATIOS.INC which contains the following set of lines. REAL :: ARATIO , RATE(10,10) INTEGER :: TEMP COMMON /RATIOS/ ARATIO, RATE, TEMP Now in every program unit where you intend to use this common block simply add the line: INCLUDE ‘RATIOS.INC’ within the declarations section. MODULES • Think of Modules as the next generation of the COMMON BLOCKS concept. The idea of common blocks was to make the same set of variables available to as many different routines as required. Modules take this concept further to make a set of variables ( and optionally subroutines&functions which act on that data) available in a unified manner. • Modules can also deliver the functionality that INCLUDE statements have

View Full Text

Details

  • File Type
    pdf
  • Upload Time
    -
  • Content Languages
    English
  • Upload User
    Anonymous/Not logged-in
  • File Pages
    51 Page
  • File Size
    -

Download

Channel Download Status
Express Download Enable

Copyright

We respect the copyrights and intellectual property rights of all users. All uploaded documents are either original works of the uploader or authorized works of the rightful owners.

  • Not to be reproduced or distributed without explicit permission.
  • Not used for commercial purposes outside of approved use cases.
  • Not used to infringe on the rights of the original creators.
  • If you believe any content infringes your copyright, please contact us immediately.

Support

For help with questions, suggestions, or problems, please contact us