7.4 FORTRAN Functions

A FORTRAN function is a procedure whose result is a single number, logical value, character string or array.

There are two types of functions, intrinsic and user-defined.

User-Defined functions are functions defined by programmers (not really users) to meet a specific need not addressed by the standard intrinsic functions.

General Form of User-Defined Functions

FUNCTION name(argument list)
	!! DECLARACTIONS
	
	!! EXECUTABLES
	
	name = expression
	
RETURN	!!ONLY NEEDED IF WE PLAN TO REACH END FUNCTION ALL OF THE TIME
END FUNCTION name

The name of the function must appear on the left side of at least one assignment statement in the function.

The argument list of the function may be blank if the function can perform all calculations with no input arguments.

Since the function returns a value, it is necessary to assign a type to that function.

Example, Take the Binary Conversion Problem in Project #1 and Implement a Function

In the PROGRAM

!! BINARY VARIABLES AND FUNCTIONS
INTEGER :: numtoconvert !!USER'S NUMBER TO CONVERT TO BINARY
INTEGER :: binaryequiv  !!BINARY EQUIVALENT OF DECIMAL INPUT
INTEGER :: toBinary     !!FUNCTION

!! OTHER CODE REMOVED

        ELSE IF(user_opt == 3) THEN
                WRITE(*,*) "Please enter the number to convert to binary: "
                READ(*,*) numtoconvert
                binaryequiv = toBinary(numtoconvert)
                WRITE(*,*) "The binary equivalent is: ", binaryequiv
In the FUNCTION
!!***************************************************
!!
!!     Function Information
!!
!!     Name of function: toBinary
!!
!!     Type: INTEGER FUNCTION
!!
!!     Dummy Arguments:
!!              decNUM - INTENT(IN)
!!
!!     Function Description:  CALCULATES THE BINARY EQUIVALENT
!!			      OF THE ARGUMENT.  
!!
!!****************************************************

INTEGER FUNCTION toBinary(decNum)
IMPLICIT NONE

INTEGER, INTENT(IN) :: decNum  !!ARGUMENT COMING IN TO FUNCTION
INTEGER :: bineq = 0	!!THE BINARY EQUIVALENT OF decNum
INTEGER :: power = 0	!!THE POWER OF 10 WE ARE CURRENTLY DEALING WITH
INTEGER :: temp		!!temp VALUE TO HOLD A COPY OF THE ARGUMENT

temp = decNum

        DO WHILE(temp > 0)
                bineq = bineq + (MOD(temp, 2) * (MOD(temp, 2) * (10 ** power)))
                power = power + 1
                temp = temp / 2
        END DO

toBinary = bineq

END FUNCTION toBinary

Notes

Example #2, Write a program that uses two functions, one to accept input of a single positive integer value and to determine whether that number is a perfect number.  A perfect number is one such that the sum of all of its even divisors (not including the number itself) it equal to the number.

6 = 1 + 2 + 3, is a perfect number.

The Functions

LOGICAL FUNCTION isPerfect(num)
IMPLICIT NONE

INTEGER, INTENT(IN) :: num
INTEGER :: lcv
INTEGER :: sum

sum = 0

        DO lcv = 1, num-1
                IF(MOD(num, lcv) == 0) THEN
                        sum = sum + lcv
                END IF
        END DO

        IF (sum == num) THEN
                isPerfect = .TRUE.
        ELSE
                isPerfect = .FALSE.
        END IF

END FUNCTION isPerfect

INTEGER FUNCTION getInput()
IMPLICIT NONE

INTEGER :: perfInput
INTEGER :: numInput = 0

        DO
                IF(numInput > 0) THEN
                        WRITE(*,*) "Try again!  Enter a number greater than zero."
                END IF
                numInput = 1
                WRITE(*,*) "Please enter a number to test for perfection: "
                READ(*,*) perfInput
                IF(perfInput > 0) EXIT
        END DO

getInput = perfInput
END FUNCTION getInput
The PROGRAM, two different ways?
PROGRAM perfect
IMPLICIT NONE

INTEGER :: users_num
INTEGER :: getInput
LOGICAL :: isPerfect

!!      users_num = getInput()

        IF (isPerfect(getInput())) THEN
!!      IF (isPerfect(users_num)) THEN
                WRITE(*,*)"Your number, ", users_num, " is perfect!"
        ELSE
                WRITE(*,*)"Your number, ", users_num, " is NOT perfect!"
        END IF

END PROGRAM perfect

Passing Arrays to Functions

The program below will use two functions to accept input, sort an array, and return the number of iterations necessary to sort the array data.

PROGRAM bubblesort

IMPLICIT NONE

        INTEGER :: getData
        INTEGER :: bSort

        INTEGER, PARAMETER :: SIZE = 50
        INTEGER :: data(SIZE)
        INTEGER :: i

        DO i = 1, SIZE, 1
                data(i) = getData()
        END DO

        WRITE(*,*) "Number of iterations: ", bSort(data, SIZE)

        DO i = 2, SIZE, 2
                WRITE(*,*) "a(", i-1, ") = ", data(i-1), "a(", i, ") = ", data(i)
        END DO

END PROGRAM bubblesort

INTEGER FUNCTION bSort(data, size)
IMPLICIT NONE

INTEGER, INTENT(IN) :: size
INTEGER, INTENT(OUT) :: data(size)

        INTEGER :: temp
        INTEGER :: i
        INTEGER :: j
        INTEGER :: num_it = 0
        INTEGER :: ns = 0

        DO i = SIZE, 1, -1
                ns = 0
                DO j = 1, i-1, 1
                        num_it = num_it + 1
                        IF (data(j) > data(j+1)) THEN
                        ns = 1
                        temp = data(j)
                        data(j) = data(j+1)
                        data(j+1) = temp
                        END IF
                END DO
                IF (ns == 0) EXIT
        END DO

bSort = num_it

END FUNCTION bSort

INTEGER FUNCTION getData()
IMPLICIT NONE

INTEGER :: item

        READ(*,*) item
getData = item
END FUNCTION getData

Extra Credit Opportunity: (To be presented in lecture next Tuesday)

1) Write a quick-short-simple program that will take a decimal number as input and return the sum of its digits.

2) Re-write the "means" problem from project 1.  This time, have the 7 numbers stored in an array and then pass that array to a subroutine to calculate the means.