Você está na página 1de 42

SUBPROGRAMS AND MODULES

FORTRAN PROGRAMING
Zerihun Alemayehu

AAiT.CED

Program structure

Advantages of subprograms
Program units can be written and tested independently A program unit that has a well defined task is easier to understand and maintain. Once developed and tested modules and external procedures can be re-used in other programs (allowing to build personal libraries). Some compilers can better optimize code in modular form.

The main program


All programs have one and only one main program. PROGRAM [name] [specification statements] [executable statements] ... [CONTAINS internal procedures] END [PROGRAM [name]]

Procedures
Two types of Procedures: functions and subroutines with the following form procedure name [(argument list)] [specification statements] [executable statements] ... [CONTAINS internal procedures] END procedure [name]

Procedures
Internalinside another program Externalself contained (may not be FORTRAN Modulecontained in a module
To use a procedure requires a referencing statement. Use CALL statement for subroutines while functions are referenced by name:
o CALL subroutine name [( argument list )] o result = function name [( argument list )]

Actual VS Dummy Arguments


Data is made available to a procedure by passing it in an argument list when the procedure is referenced. An argument list is a number of variables or expressions (or even procedure names) ACTUAL arguments the argument(s) in a referencing statement , while DUMMY arguments are those in the corresponding procedure statement

Actual VS Dummy Arguments


Actual and dummy argument are associated by their position in a list, i.e the first actual argument corresponds to the first dummy argument, the second actual argument with the second dummy argument, etc. The data type, rank, etc. of actual and dummy arguments must correspond exactly.

Example: Subroutine
PROGRAM exchange REAL,DIMENSION(10) ::a,b READ*,a,b CALLswap(a,b) PRINT*,a,b SUBROUTINE swap(c,d) REAL,DIMENSION(10) ::c,d,temp temp=c c=d d=temp END SUBROUTINE swap END PROGRAMexchange
Actualarguments

Dummyarguments

Example: Function
A function is used to generate a single result based on its arguments Thenameofthefunction, PROGRAM line_fun line,is treatedlike a REAL :: y,x,c variable, itmustbe READ*, x, c declared withthesame y = line( 3.4,x,c ) datatypeasy
FUNCTION line( m,x,const ) REAL :: line REAL :: m, x, const line = m*x + const END FUNCTION line END PROGRAM line_fun

Weveto assignthenameof thefunction tostore the functionsresult

Internal Procedures
Program units (the main program, external procedures and modules) may contain internal procedures. Placed at the end of a program unit after the CONTAINS statement They may not themselves contain other internal procedures They may only be referenced by their host and other procedures internal to the same host. They may invoke other external procedures.

Internal procedures Example


PROGRAM outer REAL :: a, b, c ... CALL inner( a ) ... CONTAINS SUBROUTINE inner( a ) !only available to outer REAL :: a !passed by argument REAL :: b=1.0 !redefined c = a + b !c host association END SUBROUTINE inner END PROGRAM outer

Experiment Example
Write a program with a single function to convert temperatures from Fahrenheit to Centigrade. In the body of the main program read in the temperature to be converted, and output the result. The actual calculation is to be done in a function. Write an internal function which requires no actual arguments, but which uses host association to access the value to be converted. The result of the function is the converted temperature.

Solution
Program tempfunc Implicit none Real:: c,f Read*, f c = f_to_c (f) Print*, c, f_to_c(f) CONTAINS Function f_to_c (f) Real:: f_to_c, f f_to_c = (f 32)*5.0/9.0 End function End program

Experiment Example
Write a subroutine to calculate new coordinates (x',y') from (x, y) when the axes are rotated counterclockwise through an angle of a radians using:
o x = xcosa + ysina o y' = xsina + ycosa

Hint: The subroutine would look something like SUBROUTINE ChangeCoordinate(X,Y,A,XD,YD) Write a main program to read in values of x,y,a, call the subroutine and print out the new coordinates.

Experiment Example
Program coordinate Implicit none Real:: x, y, newx, newy, a Read*, x, y, a Call ChangeCoordinate (x, y, a, newx, newy) Print*, newx=, newx, newy=, newy Contains Subroutine ChangeCoordinate (x, y, a, xd, yd) Real :: x, y, a, xd, yd xd = x*cos(a) + y*sin(a) yd= x*sin(a) + y*cos(a) End subroutine changecoordinate End program

External procedures
External procedures are self contained program units (subroutines or functions) that may contain (i.e. host) internal procedures.
SUBROUTINE name [( arguments )] [declaration statements ] [executable statements] [CONTAINS internal subprograms ] END [SUBROUTINE [name]] FUNCTION name([ arguments ]) [declaration statements ] [executable statements ] [CONTAINS internal subprograms] END[FUNCTION[name]]

Use the External statement to reference an external procedures

Procedure variables and Save


Whenever a procedure is referenced, variables declared in the procedure are `created' and allocated the required storage from memory. Whenever a procedure exits, by default variables declared in the procedure are `destroyed' and any storage they may have used is recovered. SAVE
o The SAVE attribute forces the program to retain the value of a procedure variable from one call to the next. o REAL, SAVE :: a_old !saved o INTEGER, SAVE :: counter=0 !saved

Interface blocks
Interfaces block are used when one program unit references another.

INTERFACE interface statements END INTERFACE


The interface statements consist of a copy of the SUBROUTINE (or FUNCTION) statement, all declaration statements for dummy arguments and the END SUNROUTINE (or FUNCTION) statement.

Interface block Example


PROGRAM count INTERFACE SUBROUTINE ties(score, n_ties) REAL :: score(50) INTEGER :: n_ties END SUBROUTINE ties END INTERFACE REAL, DIMENSION(50):: data ... CALL ties(data, n) ... END PROGRAM count

Assumed shape objects


Fortran 90 allows dummy arguments to have a variable sizes. Such objects are called assumed shape objects.
SUBROUTINE sub2(data1, data3, str) REAL, DIMENSION(:) :: data1 INTEGER, DIMENSION(:,:,:) :: data3 CHARACTER(len=*) :: str ... The dummy arguments data1 and data3 are both arrays which have been declared with a rank butnosize Similarly str has no explicit length, it adopts the length of theactual argumentstring.

The INTENT attribute


INTENT(IN) - the dummy argument is expected to have a value when the procedure is referenced, but that this value is not updated by the procedure. INTENT(OUT) - the dummy argument has no value when the procedure is referenced, but that it will be given one before the procedure finishes. INTENT(INOUT) - the dummy argument has an initial value that will be updated by the procedure.

The INTENT attribute


SUBROUTINE invert(a, inverse, count) REAL, INTENT(IN) :: a REAL, INTENT(OUT) :: inverse INTEGER, INTENT(INOUT) :: count inverse = 1/a count = count+1 END SUBROUTINE invert

Keyword arguments
Instead of associating actual argument with dummy arguments by position only, we can associate with it by name.
SUBROUTINEsub2(a,b,stat) INTEGER,INTENT(IN)::a,b INTEGER,INTENT(INOUT)::stat ENDSOBROUTINEsub2
INTEGER::x=0 CALLsub2(a=1,b=2,stat=x) CALLsub2(1,stat=x,b=2) CALLsub2(1,2,stat=x) CALLsub2(1,b=2,0)!illegal CALLsub2(1,stat=x,2)!illegalkeyword mustcomelast

Optional Arguments
Occasionally, not all arguments are required every time a procedure is used.
SUBROUTINE sub1(a, b, c, d) INTEGER, INTENT(INOUT):: a, b REAL, INTENT(IN), OPTIONAL :: c, d ... END SUBROUTINE sub1 CALL sub1( a, b ) CALL sub1( a, b, c, d ) CALL sub1( a, b, c ) CALL sub1( a, b, d ) !illegal /use keyword

Optional arguments must come after all arguments associated by position in a referencing statement and require an explicit interface

Procedures as arguments
PROGRAM test INTERFACE REAL FUNCTION func( x ) REAL, INTENT(IN) ::x END FUNCTION func END INTERFACE
...

CALL sub1( a, b, func(2) )


...

It is possible to use a procedure as an actual argument in a call another procedure.

END PROGRAM test REAL FUNCTION func( x ) !external REAL, INTENT(IN) :: x func = 1/x END FUNCTION func

Recursive Function
RECURSIVE FUNCTION factorial( n ) RESULT(res) INTEGER, INTENT(IN) :: n INTEGER :: res IF( n==1 ) THEN res = 1 ELSE res = n*factorial( n-1 ) END IF END FUNCTION factorial

Modules
Modules are a type of program unit designed to hold definitions, data and procedures which are to be made available to other program units. MODULE name [definitions] ... [CONTAINS module procedures] END [MODULE [name]] USE statement must be used to use the Module USE module_name

Global data
We can use modules to place declarations for all global variables and then USE that module. For example: MODULE global REAL, DIMENSION(100) :: a, b, c INTEGER :: list(100) LOGICAL :: test END MODULE global Any number of modules may be used by a program unit, and modules can use other modules. Module cannot USE itself directly or indirectly

Global data
USE global, ONLY: a, c !Use only a and b USE global, state=>test !To avoid name clashing Here the variable state is the local name for the variable test. The => symbol associates a different name with the global variable.

Module Procedures
Procedures contained within a module are called module procedures, and they are global. No INTERFACE block is required in the referencing program unit Variables declared within a module procedure are local to that procedure

Module Procedures
MODULE data REAL, Parameter :: Pi=3.143,g=9.81 CONTAINS Function weight( m ) Real:: weight, m Weight = g * m END Function weight END MODULE data PROGRAM calculate USE data Real:: radius, area, wt Read*, radius Read*, mass Area = pi * radius**2 wt = weight (mass) END PROGRAM calculate

PUBLIC and PRIVATE


The PRIVATE statement/attribute prevents access to module entities from any program unit, PUBLIC is the opposite As a statement PUBLIC or PRIVATE can set the default for the module, or can be applied to a list of variables or module procedure names. As an attribute PUBLIC or PRIVATE can control access to the variables in a declaration list.

PUBLIC and PRIVATE


MODULE one PRIVATE !set the default for module REAL, PUBLIC :: a REAL :: b PUBLIC :: init_a CONTAINS SUBROUTINE init_a() !public
... ...

SUBROUTINE init_b() !private END MODULE one

Generic procedures
task performed by a procedure on one data type can be applied equally to other data types. Fortran 90 allows two or more procedures to be referenced by the same, generic name. Exactly which procedure is invoked will depend on the data type (or rank) of the actual argument(s) in the referencing statement. For example, the argument of ABS may be integer, real or even complex. Overloading

Generic Procedures
INTERFACE swap SUBROUTINE iswap( a, b ) INTEGER, INTENT(INOUT) :: a, b END SUBROUTINE iswap SUBROUTINE rswap( a, b ) REAL, INTENT(INOUT) :: a, b END SUBROUTINE rswap END INTERFACE Real:: x, y Integer :: n, m Call swap (x, y) ! rswap is called Call swap (n, m) ! iswap is called

Derived Data T ypes


Additional Topics

Derived Data Types


We can define our own data type TYPE circle INTEGER :: radius REAL :: area ENDTYPE circle We can declare in the following from TYPE (circle) :: cir_a, cir_b derived data type may be given an initial value TYPE (circle) :: cir=circle(2,12.57)

Derived Data Types


Derived types may be used in the definition of other derived types. TYPE point REAL :: x_coord, y_coord ENDTYPE point Then we can modify the circle type as: TYPE circle TYPE (point) :: centre INTEGER :: radius REAL :: area ENDTYPE circle

Accessing Components
The elements of a derived type may be accessed by using the variable name and the element name separated by the % character, as follows cir_a%radius = 10.0 cir_a%area = pi * cir_a%radius**2 If a derived type has an element which is a derived type then a component may be accessed as follows cir_a%centre%x_coord = 5.0 cir_a%centre%y_coord = 6.0

Experiment
Write a program which will read in two real numbers representing the length and breadth of a rectangle, and will print out the area calculated as length times breadth. (Use a derived type.)

Solution
Program rect Implicit none TYPE rectangle REAL:: width, length, area END TYPE TYPE(rectangle):: rectngle PRINT*,"Give the length and width of a rectangle" READ*, rectngle%width, rectngle%length rectngle%area = rectngle%width * rectngle%length WRITE (*, 100) "The area of the rectangle is", rectngle%area 100 Format '(2x,A,2x, f6.3)' End program

Você também pode gostar