Fortran 90 Tutorial_5_Subroutines.doc (225Kb)

  Subroutines Select the topics you wish to review: Subroutines

  

  

  Designing Subroutines Syntax

A Function receives some input via its formal arguments from outside world and computes and

returns one value, the function value, with the function name. In some cases, you do not want to

return any value or you may want to return more than one values. Then, Fortran's subroutines are

what you need. Functions and subroutines are referred to as subprograms. The syntax of a Fortran subroutine is:

  SUBROUTINE subroutine-name (arg1, arg2, ..., argn)

  IMPLICIT NONE [specification part] [execution part] [subprogram part] END SUBROUTINE subroutine-name

  Here are some elaborations of the above syntax:

   The first line of a subroutine starts with the keyword SUBROUTINE, followed by that subroutine's name.

   Following subroutine-name, there is a pair of parenthesis in which a number of arguments arg1, arg2, ..., argn are separated with commas. These arguments are referred

to as formal arguments. Formal arguments must be variable names and cannot be

expressions and constants. Here are a examples:

  1. The following is a subroutine called Factorial. It has two formal arguments n and Answer.

  2. SUBROUTINE Factorial(n, Answer)

  3. The following is a subroutine called TestSomething. It takes four formal arguments a, b, c, and Error.

  4. SUBROUTINE TestSomething(a, b, c, Error)

   A subroutine must end with END SUBROUTINE, followed by its name.

   Between SUBROUTINE and END SUBROUTINE, there are IMPLICIT NONE,

  specification part, execution part and subprogram part. These are exactly identical to that of a PROGRAM.

   Subroutines can be internal to a program or a module. Subroutine can also be external and in this case INTERFACE blocks are required. If a subroutine does not need any formal argument, it can be written as

  SUBROUTINE subroutine-name ()

  IMPLICIT NONE [specification part] [execution part] [subprogram part] END SUBROUTINE subroutine-name where arg1, arg2, ..., argn are left out.

  Unlike functions, the pair of parenthesis can be removed:

  SUBROUTINE subroutine-name

  IMPLICIT NONE [specification part] [execution part] [subprogram part] END SUBROUTINE subroutine-name

  Semantics The meaning of a subroutine is very simple: A subroutine is a self-contained unit that receives some "input" from the outside world

   via its formal arguments, does some computations, and then returns the results, if any, with its formal arguments. Unlike functions, the name of a subroutine is not a special name to which you can save a

   result. Subroutine's name is simply a name for identification purpose and you cannot use it in any statement except the CALL statement. A subroutine receives its input values from its formal arguments, does computations, and

   saves the results in some of its formal arguments. When the control of execution reaches END SUBROUTINE, the values stored in some formal arguments are passed back to their corresponding actual arguments.

  Any statements that can be used in a PROGRAM can also be used in a SUBROUTINE. 

  Arguments' INTENT Syntax

We have met INTENT(IN) iscussion. It indicates that an argument will receives

some input from outside of the function and its value will not, actually cannot, be changed within

the function. Since a subroutine cannot return a value through its name, it must return the computation results, if any, through its argument. Therefore, we have three cases to consider:

  If an argument only receives value from outside of the subroutine, it still has its intent  like INTENT(IN). This is the simplest case. An argument does not have to receive anything from outside of the subroutine. It can be 

used to pass a computation result back to the outside world. In this case, its intent

becomes INTENT(OUT). In a subroutine, an argument declared with INTENT(OUT) is supposed to hold a computation result so that its value can be passed "out".

  Finally, an argument can receive a value, use it for computation, and hold a result so that

   it can be passed back to the outside world. In this case, its intent is INTENT(INOUT). An argument must be declared with INTENT(IN), INTENT(OUT) or INTENT(INOUT).

  Examples Here are some examples:

The following subroutine Means() has six arguments. Arguments a, b and c are declared

with INTENT(IN) and therefore can only take values from outside world and cannot be

changed. Arguments Am, Gm and Hm are declared with INTENT(OUT), indicating that

their values will be computed and passed to the outside world. More precisely, in subroutine

Means(), some values must be stored into these three arguments so that they can be passed

out. Note that an argument declared with INTENT(OUT) does not have to receive any value from outside of the subroutine.

  SUBROUTINE Means(a, b, c, Am, Gm, Hm)

  IMPLICIT NONE REAL, INTENT(IN) :: a, b, c REAL, INTENT(OUT) :: Am, Gm, Hm ..........

  END SUBROUTINE Means

  

The following subroutine Swap() has its both arguments declared with INTENT(INOUT).

That means, a and b will receive some values, after some processing a new set of values will

replace the given one so that they can be passed back.

  SUBROUTINE Swap(a, b)

  IMPLICIT NONE

  INTEGER, INTENT(INOUT) :: a, b .......... END SUBROUTINE Swap

  The CALL Statement Syntax Unlike functions, which can be used in expressions, subroutines can only be called with the CALL statement. That means, the call to a subroutine must be on its program line rather than somewhere in an expression. The following is the syntax rules of the CALL statement:

  CALL subroutine-name (arg1, arg2, ..., argn) CALL subroutine-name () CALL subroutine-name

  If the called subroutine has formal arguments, the CALL statement that calls that subroutine must have actual argument. This is the first form. However, if a subroutine does not have any argument, it can be called with the second form or the third form.

  Semantics When a CALL statement is executed, values of actual arguments are passed to those formal arguments declared with INTENT(IN) or INTENT(INOUT). Then, statements of the called subroutine are executed. When the execution reaches END SUBROUTINE, values stored in

those formal arguments declared with INTENT(OUT) and INTENT(INOUT) are passed back

to the corresponding actual arguments in the CALL statement. After this, the next statement following the CALL statement is executed.

  The number and types of actual arguments in the CALL statement must match the number and types of the corresponding formal arguments Examples Here are some simple examples: The following has a subroutine Larger() whose job is returning the larger one of the first

   two arguments with the third argument. Since u and v only receive values from outside of Larger(), they are declared with INTENT(IN). Since the larger value is returned with argument w, it is declared with INTENT(OUT).

  The main program calls subroutine Larger() with a CALL statement. Thus, the values of

a and b are passed to u and v, respectively. In subroutine Larger(), after receiving values, it stores the larger one into w and then reaches END SUBROUTINE. Then, the value stored in w is passed back to its corresponding actual argument c and the control of execution goes back to the caller. In this case, it is the main program. Therefore, variable c receives the larger value of a and b.

  PROGRAM Example1 SUBROUTINE Larger(u, v, w)

  IMPLICIT NONE IMPLICIT NONE

  INTEGER a, b, c INTEGER, INTENT(IN) :: u, v ......... INTEGER, INTENT(OUT) :: w CALL Larger(a, b, c) IF (u > v) THEN ......... w = u END PROGRAM Example1 ELSE w = v END IF END SUBROUTINE Larger

   In the following, subroutine Sort() receives two INTEGER formal arguments and

  

reorders and returns them so that the first is the smaller one and the second is the larger

one.

Since u and v receive values from and return values to the outside of Sort(), they are

declared with INTENT(INOUT). Note that w is not declared with any INTENT since it

is not a formal argument. In this subroutine, if u is greater than v, they are not in order

and the three assignment statements exchange the values of u and v.

In the main program, the values of a and b are passed to u and v, respectively. After

subroutine Sort() finishes its job, since u and v are declared with INTENT(INOUT),

their results are passed back to a and b, respectively. As a result, the original values of a and b are destroyed by the returned values. For example, if a and b have values 5 and 3, respectively, then u and v receive 5 and 3. In subroutine Sort(), the values of u and v are exchanged and returned to a and b. Hence, after returning to the main program, the values of a and b are 3 and 5.

  PROGRAM Example2 SUBROUTINE Sort(u, v)

  IMPLICIT NONE IMPLICIT NONE

  INTEGER a, b INTEGER, INTENT(INOUT) :: u, v ......... INTEGER :: w CALL Sort(a, b) IF (u > v) THEN ......... w = u END PROGRAM Example2 u = v v = w END IF END SUBROUTINE Sort

   In the following program, subroutine DoSomething() takes three formal arguments. If p

  is greater than 3, then adds 1 to q and puts 1 into r. If p is less then -3, then 1 is subtracted from q and 2 is stored to r. Otherwise, r receives 3 and the value of q is unchanged.

From this description, it is clear that p should be declared with INTENT(IN) since its

value is unchanged. Argument q should be declared with INTENT(INOUT), since 1 is added to it or -1 is subtracted from it. To add a value to or subtract a value from it, q must have an existing value and should be passed into subroutine DoSomething(). Finally, r is declared with INTENT(OUT), since its value is not needed for computation. For the main program, if the value read into a is 7, then the CALL will receive 1 for b and 1 for c. If the value read into a is -4, b and c should receive -1 and 2 from subroutine DoSomething(). If a receives a value of 2, since q is not changed in DoSomething(), b and c receive 0 (unchanged) and 3, respectively.

  PROGRAM Example3 SUBROUTINE DoSomething(p, q, r)

  IMPLICIT NONE IMPLICIT NONE

  INTEGER :: a, b, c INTEGER, INTENT(IN) :: p .......... INTEGER, INTEGER(INOUT) :: q READ(*,*) a INTEGER, INTENT(OUT) :: r b = 0 IF (p > 3) THEN CALL DoSOmething(a,b,c) q = q + 1 WRITE(*,*) a, b, c r = 1 .......... ELSE IF (p < -3) THEN END PROGRAM Example3 q = q - 1 r = 2 ELSE r = 3 END IF END SUBROUTINE DoSomething

  Computing Means - Revisited (Again) Problem Statement The arithmetic, geometric and harmonic means of three positive numbers are defined by the following formulas:

Write a program to read three positive numbers and use a single internal subroutine to compute

the arithmetic, geometric and harmonic means.

  ! ---------------------------------------------------------- ! This program contains one subroutine for computing the ! arithmetic, geometric and harmonic means of three REALs.

  ! ---------------------------------------------------------- PROGRAM Mean6

  IMPLICIT NONE REAL :: u, v, w REAL :: ArithMean, GeoMean, HarmMean READ(*,*) u, v, w CALL Means(u, v, w, ArithMean, GeoMean, HarmMean) WRITE(*,*) "Arithmetic Mean = ", ArithMean WRITE(*,*) "Geometric Mean = ", GeoMean WRITE(*,*) "Harmonic Mean = ", HarmMean CONTAINS ! ---------------------------------------------------------- ! SUBROUTINE Means(): ! This subroutine receives three REAL values and computes ! their arithmetic, geometric, and harmonic means. ! ---------------------------------------------------------- SUBROUTINE Means(a, b, c, Am, Gm, Hm)

  IMPLICIT NONE REAL, INTENT(IN) :: a, b, c REAL, INTENT(OUT) :: Am, Gm, Hm Am = (a + b + c)/3.0 Gm = (a * b * c)**(1.0/3.0) Hm = 3.0/(1.0/a + 1.0/b + 1.0/c) END SUBROUTINE Means END PROGRAM Mean6 Clicko download this program.

  Program Input and Output

The following is the output from the above program for the input 3.0, 6.0 and 8.0:

  Arithmetic Mean = 5.66666651 Geometric Mean = 5.24148321 Harmonic Mean = 4.80000019

  Heron's Formula for Computing Triangle Area Using External Functions Problem Statement We have seen Heron's formula for computing triangle area using internal functions. This problem uses the same idea; but the program should use an internal subroutine.

Given a triangle with side lengths a, b and c, its area can be computed using the Heron's formula:

where s is the half of the perimeter length:

In order for a, b and c to form a triangle, two conditions must be satisfied. First, all side lengths

must be positive: Second, the sum of any two side lengths must be greater than the third side length: Write a program to read in three real values and use an internal subroutine to compute the

triangle area. This subroutine should tell the main program if the area computation is successful.

  Solution

  ! -------------------------------------------------------------------- ! PROGRAM HeronFormula: ! This program contains one subroutine that takes three REAL values ! and computes the area of the triangle bounded by the input values.

  ! -------------------------------------------------------------------- PROGRAM HeronFormula

  IMPLICIT NONE

  REAL :: Answer ! will hold the area LOGICAL :: ErrorStatus ! return status READ(*,*) Side1, Side2, Side3 CALL TriangleArea(Side1, Side2, Side3, Answer, ErrorStatus)

  IF (ErrorStatus) THEN ! if error occurs in subroutine WRITE(*,*) "ERROR: not a triangle" ! display a message ELSE ! otherwise, display the area WRITE(*,*) "The triangle area is ", Answer END IF CONTAINS ! -------------------------------------------------------------------- ! SUBROUTINE TriangleArea(): ! This subroutine takes three REAL values as the sides of a ! triangle. Then, it tests to see if these values do form a triangle.

  ! If they do, the area of the triangle is computed and returned with ! formal argument Area and .FALSE. is returned with Error. Otherwise, ! the area is set to 0.0 and .TRUE. is returned with Error.

  ! -------------------------------------------------------------------- SUBROUTINE TriangleArea(a, b, c, Area, Error)

  IMPLICIT NONE REAL, INTENT(IN) :: a, b, c ! input sides REAL, INTENT(OUT) :: Area ! computed area LOGICAL, INTENT(OUT) :: Error ! error indicator REAL :: s LOGICAL :: Test1, Test2 Test1 = (a > 0) .AND. (b > 0) .AND. (c > 0) Test2 = (a+b > c) .AND. (a+c > b) .AND. (b+c > a)

  IF (Test1 .AND. Test2) THEN ! a triangle? Error = .FALSE. ! yes. no error s = (a + b + c)/2.0 ! compute area Area = SQRT(s*(s-a)*(s-b)*(s-c)) ELSE Error = .TRUE. ! not a triangle Area = 0.0 ! set area to zero END IF END SUBROUTINE TriangleArea END PROGRAM HeronFormula Clicko download this program.

  Program Input and Output The following is the output from the above program for input 3.0, 5.0 and 7.0.

  The triangle area is 6.49519062

  Discussion

Subroutine TriangleArea() has five formal arguments. a, b and c are declared with

   INTENT(IN), since they do not return anything. Since Area is used to return the triangle area and Error is used to return the error status, both are declared with INTENT(OUT).

  

If a, b and c can form a triangle, there is no error, Error is set to .FALSE. and the

  

triangle area is computed; otherwise, Error is set to .TRUE. and Area is set to 0.

The error status generated by subroutine TriangleArea() and returned through formal

   argument Error will be passed back to ErrorStatus in the main program. Following the CALL statement, the main program must check to see if the computation was successful by testing the value of ErrorStatus. If it is .TRUE., the input do not form a triangle.

TO EAR ONTH AY ONVERSION

  YYYYMMDD Y , M , D C ROBLEM TATEMENT P S

  In data processing, the year, month and day information are usually written as yyyymmdd,

where the first four digits are Year, the fifth and sixth digits are Month, and the last two digits

are Day. For example, 19710428 means April 8, 1971, and 20000101 means January 1, 2000. Write a program to read an integer in the form of yyyymmdd and extract the values of Year, Month and Day. Do it with an external subroutine.

  OLUTION S

  ! -------------------------------------------------------------------- ! PROGRAM YYYYMMDDConversion: ! This program uses an external subroutine Conversion() to convert ! an integer value in the form of YYYYMMDD to Year, Month and Day.

  ! -------------------------------------------------------------------- PROGRAM YYYYMMDDConversion

  IMPLICIT NONE

  INTERFACE ! interface block SUBROUTINE Conversion(Number, Year, Month, Day)

  INTEGER, INTENT(IN) :: Number

  INTEGER, INTENT(OUT) :: Year, Month, Day END SUBROUTINE Conversion END INTERFACE

  INTEGER :: YYYYMMDD, Y, M, D DO ! loop until a zero is seen

  READ(*,*) YYYYMMDD ! read in the value

  IF (YYYYMMDD == 0) EXIT ! if 0, then bail out CALL Conversion(YYYYMMDD, Y, M, D) ! do conversation WRITE(*,*) "Year = ", Y ! display results WRITE(*,*) "Month = ", M WRITE(*,*) "Day = ", D WRITE(*,*) END DO END PROGRAM YYYYMMDDConversion ! -------------------------------------------------------------------- ! SUBROUTINE Conversion(): ! This external subroutine takes an integer input Number in the ! form of YYYYMMDD and convert it to Year, Month and Day. ! -------------------------------------------------------------------- SUBROUTINE Conversion(Number, Year, Month, Day)

  IMPLICIT NONE

  INTEGER, INTENT(IN) :: Number

  INTEGER, INTENT(OUT) :: Year, Month, Day Year = Number / 10000 Month = MOD(Number, 10000) / 100 Day = MOD(Number, 100) END SUBROUTINE Conversion Click to download this program.

  I O

  ROGRAM NPUT AND UTPUT P

  The following is the output from the above program for the input 3.0, 6.0 and 8.0: A YYYYMMDD (e.g., 19971027) please (0 to stop) -> 19971026 Year = 1997 Month = 10 Day = 26 A YYYYMMDD (e.g., 19971027) please (0 to stop) -> 20160131 Year = 2016 Month = 1 Day = 31 A YYYYMMDD (e.g., 19971027) please (0 to stop) -> 19010103 Year = 1901 Month = 1 Day = 3 A YYYYMMDD (e.g., 19971027) please (0 to stop) ->

  ISCUSSION D

  Subroutine Conversion() has four INTEGER formal arguments. Number is an  integer in the form of yyyymmdd and Year, Month and Day are the values for year, month and day. Therefore, Number is declared with INTENT(IN) and Year, Month and Day are declared with INTENT(OUT). To compute the value for Year, Number is divided by 10000. In this way, the last

   four digits are removed (i.e., 19971205/10000 is 1997). The value for Day is from the last two digits. It is the remainder of dividing Number  by 100. For example, MOD(19971205,100) yields 5. Two extract the value for Month, frst note that we have to cut the frst four digits of

   so that yyyymmdd becomes mmdd. Then, dividing mmdd by 100 yields mm. This is done with MOD(Number,10000)/100, where MOD(Number,10000) retrieves mmdd and this result is divided by 100 yielding Month. The main program has an INTERFACE block containing the subroutine header and  the declarations of all formal arguments. The main program keeps asking for an integer in the form of yyyymmdd, and CALLs  subroutine Conversion() to perform the conversion until the input is a zero.

UADRATIC QUATION OLVER EVISITED GAIN

  Q E S - R (A ) ROBLEM TATEMENT P S

  Given a quadratic equation as follows: if b*b-4*a*c is non-negative, the roots of the equation can be solved with the following formulae:

Write a program to read in the coefficients a, b and c, and uses an internal subroutine to solve the

equation. Note that a quadratic equation has repeated root if b*b-4.0*a*c is equal to zero.

  OLUTION S

  ! PROGRAM QuadraticEquation: ! This program calls subroutine Solver() to solve quadratic ! equations.

  ! -------------------------------------------------------------------- PROGRAM QuadraticEquation

  IMPLICIT NONE

  INTEGER, PARAMETER :: NO_ROOT = 0 ! possible return types

  INTEGER, PARAMETER :: REPEATED_ROOT = 1

  INTEGER, PARAMETER :: DISTINCT_ROOT = 2

  INTEGER :: SolutionType ! return type variable REAL :: a, b, c ! coefficients REAL :: r1, r2 ! roots READ(*,*) a, b, c ! read in coefficients CALL Solver(a, b, c, r1, r2, SolutionType) ! solve it SELECT CASE (SolutionType) ! select a type CASE (NO_ROOT) ! no root WRITE(*,*) "The equation has no real root" CASE (REPEATED_ROOT) ! repeated root WRITE(*,*) "The equation has a repeated root ", r1 CASE (DISTINCT_ROOT) ! distinct roots WRITE(*,*) "The equation has two roots ", r1, " and ", r2 END SELECT CONTAINS ! -------------------------------------------------------------------- ! SUBROUTINE Solver(): ! This subroutine takes the coefficients of a quadratic equation ! and solve it. It returns three values as follows: ! (1) Type - if the equation has no root, a repeated root, or ! distinct roots, this formal arguments returns NO_ROOT, ! REPEATED_ROOT and DISTINCT_ROOT, respectively.

  ! Note that these are PARAMETERS declared in the main ! program. ! (2) Root1 and Root2 - if there is no real root, these two formal ! arguments return 0.0. If there is a repeated ! root, Root1 returns the root and Root2 is zero. ! Otherwise, both Root1 and Root2 return the roots. ! -------------------------------------------------------------------- SUBROUTINE Solver(a, b, c, Root1, Root2, Type)

  IMPLICIT NONE REAL, INTENT(IN) :: a, b, c REAL, INTENT(OUT) :: Root1, Root2

  INTEGER, INTENT(OUT) :: Type REAL :: d ! the discriminant Root1 = 0.0 ! set the roots to zero Root2 = 0.0 d = b*b - 4.0*a*c ! compute the discriminant

  Type = NO_ROOT ! no root ELSE IF (d == 0.0) THEN ! if the discriminant is 0 Type = REPEATED_ROOT ! a repeated root Root1 = -b/(2.0*a) ELSE ! otherwise, Type = DISTINCT_ROOT ! two distinct roots d = SQRT(d) Root1 = (-b + d)/(2.0*a) Root2 = (-b - d)/(2.0*a) END IF END SUBROUTINE Solver END PROGRAM QuadraticEquation Clito download this program.

  P ROGRAM

  I NPUT AND O UTPUT If the input to the program consists of 3.0, 6.0 and 2.0, we have the following output.

  3.0 6.0 2.0 The equation has two roots -0.422649741 and -1.57735026 If the input to the program consists of 1.0, -2.0 and 1.0, we have the following output.

  1.0 -2.0 1.0 The equation has a repeated root 1. If the input to the program consists of 1.0, 1.0 and 1.0, we have the following output. 1.0 1.0 1.0 The equation has no real root

  D

  ISCUSSION

   The main program reads in the coefcients of a quadratic equation and calls subroutine Solver() to fnd the roots. Because there are three possible cases (i.e., no root, a repeated root and two distinct roots), the main program defnes three

  PARAMETERs for these cases: NO_ROOT for no real root, REPEATED_ROOT for

  repeated root, and DISTINCT_ROOT for distinct roots. Since they are declared in the main program, they are global and can be "seen" by all internal functions and subroutines.  The main program passes the coefcients to Solver() and expects the subroutine to return the roots through r1 and r2 and the type of the roots with SolutionType. After receiving the type, the main program uses SELECT CASE to display the results.

   Subroutine Solver() receives the coefcients from a, b and c. If the equation has no root (resp., repeated root or distinct roots), NO_ROOT (resp., REPEATED_ROOT or DISTINCT_ROOT) is stored into formal argument Type.

  Note that formal arguments Root1 and Root2 are initialized with zero. Therefore, in  case they do not receive values in subsequent computations, they still return values. In the subroutine, if the equation has no root, both Root1 and Root2 return zero; if the equation has a repeat root, Root1 contains the root and Root2 is zero; and if the equation has distinct roots, the roots are stored in Root1 and Root2.

OMPUTING EAN ARIANCE AND TANDARD EVIATION

  C M , V S D ROBLEM TATEMENT P S

  

Given n data items x1, x2, ..., xn, the mean, variance and standard deviation of these data items

are defined as follows: Write a program that reads in an unknown number of data items, one on each line, counts the number of input data items and computes their mean, variance and standard deviation.

  OLUTION S

  ! -------------------------------------------------------------------- ! PROGRAM MeanVariance: ! This program reads in an unknown number of real values and ! computes its mean, variance and standard deviation. It contains ! three subroutines: ! (1) Sums() - computes the sum and sum of squares of the input ! (2) Result() - computes the mean, variance and standard ! deviation from the sum and sum of squares ! (3) PrintResult() - print results ! -------------------------------------------------------------------- PROGRAM MeanVariance

  IMPLICIT NONE

  INTEGER :: Number, IOstatus REAL :: Data, Sum, Sum2 REAL :: Mean, Var, Std Number = 0 ! initialize the counter Sum = 0.0 ! initialize accumulators Sum2 = 0.0 DO ! loop until done

  IF (IOstatus < 0) EXIT ! if end-of-file reached, exit Number = Number + 1 ! no, have one more value WRITE(*,*) "Data item ", Number, ": ", Data CALL Sums(Data, Sum, Sum2) ! accumulate the values END DO CALL Results(Sum, Sum2, Number, Mean, Var, Std) ! compute results CALL PrintResult(Number, Mean, Var, Std) ! display them CONTAINS ! -------------------------------------------------------------------- ! SUBROUTINE Sums(): ! This subroutine receives three REAL values: ! (1) x - the input value ! (2) Sum - x will be added to this sum-of-input ! (3) SumSQR - x*x is added to this sum-of-squares ! -------------------------------------------------------------------- SUBROUTINE Sums(x, Sum, SumSQR)

  IMPLICIT NONE REAL, INTENT(IN) :: x REAL, INTENT(INOUT) :: Sum, SumSQR Sum = Sum + x SumSQR = SumSQR + x*x END SUBROUTINE Sums ! -------------------------------------------------------------------- ! SUBROUTINE Results(): ! This subroutine computes the mean, variance and standard deviation ! from the sum and sum-of-squares: ! (1) Sum - sum of input values ! (2) SumSQR - sun-of-squares ! (3) n - number of input data items ! (4) Mean - computed mean value ! (5) Variance - computed variance ! (6) StdDev - computed standard deviation ! -------------------------------------------------------------------- SUBROUTINE Results(Sum, SumSQR, n, Mean, Variance, StdDev)

  IMPLICIT NONE

  INTEGER, INTENT(IN) :: n REAL, INTENT(IN) :: Sum, SumSQR REAL, INTENT(OUT) :: Mean, Variance, StdDev Mean = Sum / n Variance = (SumSQR - Sum*Sum/n)/(n-1) StdDev = SQRT(Variance) END SUBROUTINE ! -------------------------------------------------------------------- ! SUBROUTINE PrintResults(): ! This subroutine displays the computed results.

  ! --------------------------------------------------------------------

  SUBROUTINE PrintResult(n, Mean, Variance, StdDev)

  IMPLICIT NONE

  INTEGER, INTENT(IN) :: n REAL, INTENT(IN) :: Mean, Variance, StdDev WRITE(*,*) WRITE(*,*) "No. of data items = ", n WRITE(*,*) "Mean = ", Mean WRITE(*,*) "Variance = ", Variance WRITE(*,*) "Standard Deviation = ", StdDev END SUBROUTINE PrintResult END PROGRAM MeanVariance Click to download this program.

  I O

  ROGRAM NPUT AND UTPUT P

  The follow shows six input data values and their mean, variance and standard deviation: Data item 1: 5. Data item 2: 2. Data item 3: 6. Data item 4: 8. Data item 5: 4.5 Data item 6: 7. No. of data items = 6 Mean = 5.41666651 Variance = 4.44166565 Standard Deviation = 2.10752606

  D

  ISCUSSION

  The mean program has a DO-EXIT-END DO. For each iteration, an input value is

   read into Data. Note that IOSTAT= is used in the READ statement. Thus, if the value of IOstatus is negative, end-of-fle is reached and the execution exits the DO- loop. Otherwise, the main program calls subroutine Sums() to add the input value Data to Sum and the square of Data to Sum2.

  After reaching the end of file, the EXIT brings the execution to the second CALL. It calls subroutine Results() to compute the mean, variance and standard deviation from Sum and Sum2.

  Finally, subroutine PrintResult() is called to display the result.

  Subroutine Sums() receives an input value from x and adds its value to Sum and its  square to SumSQR. Why are Sum and SumSQR declared with INTENT(INOUT)? Subroutine Results() computes the mean, variance and standard deviation using

   Sum, SumSQR and n.

  Subroutine PrintResult() displays the results.  ORE ABOUT RGUMENT SSOCIATION M A A

INTENT(IN)

  We have discussed the meaning of INTENT(IN) earlier in Simply speaking, a formal argument declared with INTENT(IN) means it only receives a value from its corresponding actual argument and its value will not be changed in this function or subroutine.

INTENT(OUT)

  A formal argument declared with INTENT(OUT) serves the opposite purpose. It means that formal argument does not have to receive any value from its corresponding actual argument. Instead, at the end of the subroutine's execution, the most recent value of that formal argument will be passed back to its corresponding actual argument.

  From the caller's point of view, an actual argument whose corresponding formal argument is

declared with INTENT(OUT) does not have to have any valid value because it will not be used

in the subroutine. Instead, this actual argument expects a value passed back from the called subroutine.

INTENT(INOUT)

  A formal argument declared with INTENT(INOUT) expects a valid value from the caller and sends a value back to the caller. Therefore, the caller must supply a valid value and the subroutine must generate a valid value so that it can be passed back.

  Suppose we have the following main program and subroutine:

  PROGRAM TestExample SUBROUTINE Sub(u, v, w)

  IMPLICIT NONE IMPLICIT NONE

  INTEGER :: a, b, c = 5 INTEGER, INTENT(IN) :: u a = 1 INTEGER, INTENT(INOUT) :: v b = 2 INTEGER, INTENT(OUT) :: w CALL Sub(a, b, c) w = u + v ..... v = v*v - u*u END PROGRAM TestExample END SUBROUTINE Sub Subroutine Sub() has three formal arguments. u is declared with INTENT(IN) and receives 1. v is declared with INTENT(INOUT) and receives 2. w is declared with INTENT(OUT) and its fnal value will be passed back to the main program replacing the value of c. The following diagram illustrate this relationship:

  HE

  ITUATION S OT O

  I N S S , T

  IMPLE HOUGH T S

  An actual argument could be a variable, a constant, or an expression. We have seen in function's discussion that one can pass a variable, a constant or an expression to a formal argument declared with INTENT(IN). The expression is frst evaluated, its result is stored in a temporary location, and the value of that location is passed. Note that a constant is considered as an expression.

  How about arguments declared with INTENT(OUT) and INTENT(INOUT)? That is simple. Please keep in mind that the corresponding actual argument of any formal argument declared with INTENT(OUT) or INTENT(INOUT) must be a variable!

  PROGRAM Errors SUBROUTINE Sub(u,v,w,p,q)

  IMPLICIT NONE IMPLICIT NONE

  INTEGER :: a, b, c INTEGER, INTENT(OUT) :: u .......... INTEGER, INTENT(INOUT) :: v CALL Sub(1,a,b+c,(c),1+a) INTEGER, INTENT(IN) :: w .......... INTEGER, INTENT(OUT) :: p END PROGRAM Errors INTEGER, INTENT(IN) :: q ..........

  END SUBROUTINE Sub There are some problems in the above argument associations. Let us examine all fve actual/formal arguments:

  Actual argument 1 is a constant and is considered as an expression. Its  corresponding formal argument u is declared with INTENT(OUT). This is an error. Actual argument a is a variable. Its corresponding formal argument v is declared with  INTENT(INOUT). This is fne.

  Actual argument b+c is an expression. Its corresponding formal argument w is

   declared with INTENT(IN). This is ok. Actual argument (c) is an expression. Its corresponding formal argument p is

   declared with INTENT(OUT). This is an error. Actual argument 1+a is a expression. Its corresponding formal argument q is

   declared with INTENT(IN). This is ok.

  Are these rules rational? Yes, they are. If an actual argument is an expression, as mentioned

earlier, it will be evaluated, its value is stored in a temporary location, and the value stored there

is passed. Therefore, if its corresponding formal argument is declared with INTENT(OUT) or

  

INTENT(INOUT), the result will be passed back to that temporary location which cannot be

used by the caller. As a result, the actual argument must be a variable to receive the result.