Subroutine Comp 208 Yi Lin
Comp208 Computers in Engineering SUBROUTINE SUBROUTINE is a program unit like FUNCTION, except that It does not have return value, so no TYPE in declaration To be called: CALL <name of SUBROUTINE> Syntax SUBROUTINE name(arg1, arg2, ..., argn) IMPLICIT NONE [declarations] [statements] [other subprograms] END SUBROUTINE name 2018/11/12 Comp208 Computers in Engineering
Comp208 Computers in Engineering SUBROUTINE (cont.) Since there is no return value for a SUBROUTINE, what is the reason to use a SUBROUTINE? A subroutine is used to change the value of one or more of its arguments. 2018/11/12 Comp208 Computers in Engineering
A Factorial Subroutine INTEGER FUNCTION Factorial(n) IMPLICIT NONE INTEGER :: n, Fact, i Fact = 1 DO i = 1, n Fact = Fact * i END DO Factorial=Fact END FUNCTION Factorial SUBROUTINE Factorial(n, Fact) IMPLICIT NONE INTEGER :: n, Fact, i Fact = 1 DO i = 1, n Fact = Fact * i END DO END SUBROUTINE Factorial …… READ(*,*) a CALL Factorial(a, value) WRITE(*,*) value CALL 2018/11/12 Comp208 Computers in Engineering
Comp208 Computers in Engineering SUBROUTINE example PROGRAM testSwap IMPLICIT none REAL::x=1, y=2 WRITE(*,*) "x=", x, "y=", y CALL swap(x,y) END PROGRAM SUBROUTINE swap( a, b ) REAL:: a, b, temp temp = a a = b b = temp END SUBROUTINE swap 2018/11/12 Comp208 Computers in Engineering
SUBROUTINE example (cont.) REAL::x=1, y=2 WRITE(*,*) "x=", x, “y=", y ! X=1.0 y=2.0 CALL swap(x,y) 1.0 a x 2.0 b y SUBROUTINE swap( a, b ) REAL:: a, b, temp temp = a a = b b = temp END SUBROUTINE swap 1.0 temp 2.0 a x 1.0 b y WRITE(*,*) "x=", x, “y=", y ! x=2.0 y=1.0 2018/11/12 Comp208 Computers in Engineering
Function and Subroutine argument passing Actual argument: the argument(s) in a referencing statement, e.g., CALL swap(x, y) x and y are actual arguments Dummy argument: those in the corresponding function or subroutine definition statement e.g., SUBROUTINE swap( a, b ) a and b are dummy arguments 2018/11/12 Comp208 Computers in Engineering
Function and Subroutine argument passing If actual arguments are variables, the corresponding dummy arguments refer to the same variables (i.e., using the same memory slot with actual argument) So if dummy arguments are to be changed in the functions or subroutines, the actual arguments will be changed also. Programmers must be very careful about argument passing. 2018/11/12 Comp208 Computers in Engineering
Comp208 Computers in Engineering Example PROGRAM Mid8 IMPLICIT NONE INTEGER :: Calc, a a = 10 WRITE(*,*) Calc(a) - Calc(a) END PROGRAM Mid8 INTEGER FUNCTION Calc(N) INTEGER :: N, var var = 0 DO IF (N<=0) EXIT var = var + N N = N - 1 END DO Calc = var END FUNCTION Calc A. 0 B. 10 C. 45 D. 55 E. None of the above 2018/11/12 Comp208 Computers in Engineering
Array argument and examples Yi Lin Oct 4, 2005
Comp208 Computers in Engineering Array as arguments Sometimes we need to pass a list of variables with the same type to a function or subroutine. In this case, we can use an array as an argument. INTEGER::a, b, c, d …… CALL sub1(a, b, c, d) Or sometimes we need to process different arrays in the same way by using a function or subroutine. We can use an array as an argument. INTEGER::array1(10), array2(20) CALL sub3(array1, array2, …) INTEGER::array1(4) …… CALL sub2(array1, …) 2018/11/12 Comp208 Computers in Engineering
Comp208 Computers in Engineering Array as argument Passing an array as an argument is like passing a variable. The function needs to know the following information about the array: Name of the array Type of the array Besides those, one more information is needed, compared to passing a variable: Bounds of the array To avoid referring to elements out of the bounds. 2018/11/12 Comp208 Computers in Engineering
Example passing array as argument ! Input a list of real number and calculate their sum. PROGRAM Test IMPLICIT NONE INTEGER :: Data(1000) INTEGER :: ActualSize, i INTEGER :: SumFunc READ(*,*) ActualSize READ(*,*) (Data(i), i=1, ActualSize) WRITE(*,*) "Sum = ", SumFunc(Data, ActualSize) END PROGRAM Test INTEGER FUNCTION SumFunc(x, n) INTEGER :: n INTEGER :: x(n) INTEGER :: Total INTEGER :: i Total = 0.0 DO i = 1, n Total = Total + x(i) END DO SumFunc = Total END FUNCTION SumFunc 2018/11/12 Comp208 Computers in Engineering
Comp208 Computers in Engineering How do we input the data? The straightforward way to read data into an array uses a counted DO loop: INTEGER :: data(100) INTEGER :: n, i READ(*,*) n DO i = 1, n READ(*,*) data(i) END DO In this example, if the input to n is 15, the READ(*,*) statement executes 15 times. Each time it is executed, it reads one line and takes the first integer value on that line. Therefore, excluding the input for n, 15 input lines are required. 2018/11/12 Comp208 Computers in Engineering
Comp208 Computers in Engineering Implied DO Loops The implied DO loop can simplify this greatly. INTEGER :: data(100) INTEGER :: n, i READ(*,*) n READ(*,*) (data(i), i=1, n) If the value of n is 15, this READ(*,*) statement is equivalent to READ(*,*) data(1), data(2),. . ., data(15) What is the difference? The values read can appear on one or more lines since FORTRAN will automatically search for the next input on the current input line or go on to the next line if needed. 2018/11/12 Comp208 Computers in Engineering
Output with Implied DO Loops Implied DO Loops can also be used to output expressions. Note that any expressions can appear, not just array elements. INTEGER :: data(10) INTEGER :: n = 5, i DO i = 1, 5 WRITE(*,*) i, data(i) END DO WRITE(*,*) (i, data(i), i=1, n) The first WRITE(*,*) is executed five times. Thus, the output is on five different lines. The second WRITE(*,*) is equivalent to WRITE(*,*) 1, data(1), 2, data(2), 3, data(3), 4, & data(4), 5, data(5) Therefore, the ten output values are on the same line. 2018/11/12 Comp208 Computers in Engineering
Example passing array as argument ! Input a list of real number and calculate their sum. PROGRAM Test IMPLICIT NONE INTEGER :: Data(1000) INTEGER :: ActualSize, i INTEGER :: Sum READ(*,*) ActualSize READ(*,*) (Data(i), i=1, ActualSize) WRITE(*,*) "Sum = ", Sum(Data, ActualSize) END PROGRAM Test INTEGER FUNCTION Sum(x, n) INTEGER :: n, I, total INTEGER :: x(n) Total = 0.0 DO i = 1, n Total = Total + x(i) END DO Sum = Total END FUNCTION Sum 1 2 3 4 5 15 6 9 10 Data x Sum=43 2018/11/12 Comp208 Computers in Engineering
Example passing array as argument Sometimes if the function only processes part of the array, we need to pass the bounds (lower and/or upper) PROGRAM Test …… WRITE(*,*) “Sum from 2 to n-1:”, sumFunc(data, n, 2, n-1) END PROGRAM Test INTEGER FUNCTION SumFunc(x, n, startIndex, endIndex) IMPLICIT NONE INTEGER :: x(n) INTEGER :: Total INTEGER :: i Total = 0 DO i = startIndex, endIndex Total = Total + x(i) END DO SumFunc = Total END FUNCTION SumFunc 1 2 3 4 5 15 6 9 10 Data x Sum=18 2018/11/12 Comp208 Computers in Engineering
Example with array arguments Problem: Given an array, reverse its elements. For example, given: 15 6 3 9 10 10 9 3 6 15 2018/11/12 Comp208 Computers in Engineering
Example: reversing an array Recall that we have SUBROUTINE swap(x,y) before. We can reuse this SUBROUTINE. Which two elements need to swap? In general, to which position will a(i) be swapped? i = (n+1)-j then a(i) a(j) What happens if there are odd elements in the array? The middle element swaps with itself. a(1) a(5) a(2) a(4) a(3) a(3) 15 6 3 9 10 2018/11/12 Comp208 Computers in Engineering
Example: reverse an array SUBROUTINE reverseArray(a, n) IMPLICIT NONE INTEGER :: n, I INTEGER :: a(n) DO i=1, n CALL swap(a(i), a(n+1-i)) END DO END SUBROUTINE n/2 2018/11/12 Comp208 Computers in Engineering
Example: reverse an array SUBROUTINE swap( a, b ) real :: a, b real::temp temp = a a = b b = temp END SUBROUTINE swap YES! Changed to INTEGER Note that SUBROUTINE reverseArray will use this SUBROUTINE to swap two integers. But this SWAP requires two real number as arguments. Will this be a problem? 2018/11/12 Comp208 Computers in Engineering
Example: reverse an array PROGRAM test IMPLICIT NONE INTEGER::data(5) INTEGER::i Do i=1,5 data(i)=I End Do WRITE(*,*) (data(i), i=1,5) CALL reverseArray(data, 5) END PROGRAM test 15 6 3 9 10 10 9 3 6 15 2018/11/12 Comp208 Computers in Engineering
Examples in Midterm 05 winter PROGRAM QUESTION9 IMPLICIT NONE INTEGER ARR(5), I, FUNC DO I = 1 , 5 READ(*,*) ARR(I) END DO PRINT*, FUNC(ARR) STOP END PROGRAM QUESTION9 INTEGER FUNCTION FUNC(ARR) INTEGER ARR(5), I, J FUNC = 0 FUNC = FUNC + ARR(I)*10**(I-6) END FUNCTION FUNC Input : 1 2 3 4 5 Answer: A. 0 B. 0.54321 C. 0.12345 D. 54321 E. None of the above 2018/11/12 Comp208 Computers in Engineering
Comp208 Computers in Engineering Programming example Given an array with n elements and an amount delta, please write a subroutine to increase all elements of an array by the amount. Consider these hints: What is the interface of your subroutine? How many arguments does it takes? What types? How to implement the increasing of all elements? 2018/11/12 Comp208 Computers in Engineering
Multidimensional Arrays The same rules apply to multidimensional arrays used as arguments The extent of each dimension can be specified If assumed shape arrays are used, only the lower bound is required If the lower bound is 1, even that can be omitted 2018/11/12 Comp208 Computers in Engineering
Example with 2 dimensional array PROGRAM Test IMPLICIT NONE INTEGER :: data(2,3), I, j Do i=1, 2 Do j=1, 3 data(I,j)=i*j end do End do WRITE(*,*) “Sum=“, SumFunc(data, 2, 3) End program test INTEGER FUNCTION SumFunc(a, n, m) integer:: n, m, a(n,m) INTEGER::I, j, Total DO i=1, n DO j=1, m Total=total+a(I,j) END DO SumFunc = Total END FUNCTION SumFunc Bug: Total is not initiated as 0 2018/11/12 Comp208 Computers in Engineering
A complete example: Is an M Prime? Look for factors less than M If M>2 it must be odd We need a loop that checks goes through the potential factors Potential factors must be odd numbers, 3, 5, 9, 11, … For each one we check to see whether it divides M evenly A clever observation: We only have to check for factors up to Sqrt(M) 2018/11/12 Comp208 Computers in Engineering
Comp208 Computers in Engineering Testing for Primality ! This function receives an INTEGER formal argument Number. If it is a prime ! number, .TRUE. is returned; otherwise, this function returns .FALSE. ! -------------------------------------------------------------------- LOGICAL FUNCTION Prime(Number) IMPLICIT NONE INTEGER :: Number INTEGER :: Divisor IF (Number < 2) THEN Prime = .FALSE. ELSE IF (Number == 2) THEN Prime = .TRUE. ELSE IF (MOD(Number,2) == 0) THEN ELSE Divisor = 3 DO IF (Divisor*Divisor>Number .OR. MOD(Number,Divisor)==0) EXIT Divisor = Divisor + 2 END DO Prime = Divisor*Divisor > Number END IF END FUNCTION Prime 2018/11/12 Comp208 Computers in Engineering
Comp208 Computers in Engineering Complete Program (1) ! --------------------------------------------------------------- ! Find all prime numbers in the range of 2 and an input value ! -------------------------------------------------------------- PROGRAM Primes IMPLICIT NONE INTEGER :: Range, Number, Count INTEGER::GetNumber LOGICAL::prime Range = GetNumber() Count = 1 WRITE(*,*) 'Prime number #', Count, ': ', 2 DO Number = 3, Range, 2 IF (Prime(Number)) THEN Count = Count + 1 WRITE(*,*) 'Prime number #', Count, ': ', Number END IF END DO WRITE(*,*) 'There are ', Count, ' primes between 2 and ', Range END PROGRAM Primes 2018/11/12 Comp208 Computers in Engineering
Comp208 Computers in Engineering Complete Program (2) !------------------------------------------------------ ! This function does not require any formal argument. ! It prompts the user to enter an integer >= 2 INTEGER FUNCTION GetNumber() IMPLICIT NONE INTEGER :: N WRITE(*,*) 'What is the range ? ' DO READ(*,*) N IF (N >= 2) EXIT WRITE(*,*) 'The range value must be >= 2. Your input is ', N WRITE(*,*) 'Please try again:' END DO GetNumber = N END FUNCTION GetNumber 2018/11/12 Comp208 Computers in Engineering
Comp208 Computers in Engineering Complete Program (3) LOGICAL FUNCTION Prime(Number) IMPLICIT NONE INTEGER :: Number INTEGER :: Divisor IF (Number < 2) THEN Prime = .FALSE. ELSE IF (Number == 2) THEN Prime = .TRUE. ELSE IF (MOD(Number,2) == 0) THEN ELSE Divisor = 3 DO IF (Divisor*Divisor>Number .OR. MOD(Number,Divisor)==0) EXIT Divisor = Divisor + 2 END DO Prime = Divisor*Divisor > Number END IF END FUNCTION Prime 2018/11/12 Comp208 Computers in Engineering