Functions and Subprograms

Monolithic Structure

      Programs seen so for are just of made of a

   single unit programs: one single block of declarations and statements

      Single block monolithic programs fine for small programs (50 or less LOC)

      Not good for larger programs that you will write; definitely not for your projects

      Very difficult to understand, debug and develop

      Some way of structuring the code required

Programming with Subroutines

      All modern PLs have features to structure the code into multiple units

      This feature enables composing a large program from a number of smaller subprograms

      A typical program consists of

   a number of subprograms

   and a main program

      The main program is invoked by the user

      The main program, in turn, invoke the other subprograms

Design Decomposition

This structuring mechanism has lot of advantages:

 

      Readability and understandability of code improves

   Main program and subprograms can be individually read and understood

 

       Supports structured development process

   Break a complex problem into simple ones,

   arrive at subprograms for smaller ones

     Problem definition, algorithm design, verification, coding and testing all are decomposed

 

Advantages of Subprograms

      Concurrent and independent design of subprograms (Teams of programmers)

      Reuse of existing code

     If someone had already solved one of the subtasks, use them by taking the solution as a subprogram (avoids reinvention)

 

   Library of reusable components or units

Subroutine Definition

A subroutine is an independent program unit:

       SUBROUTINE name ( argument_list)
         ...
         Declaration Section
         ...
         Executable section

         RETURN
       END SUBROUTINE [name]

Programs and Subroutines

      A subroutine almost resembles normal programs

      It has its own name, a declaration part and an executable part

      It is compiled separately

      One difference is:

   It can not be directly executed,

   executed via the (main) program

      Another difference is:

   a list of arguments, variable names

   arguments are dummy, placeholders

Calling subroutines

      A subroutine is executed by the main program

      This happens when main program executes a statement

            CALL subroutine_name (argument_list)

      We say that the main program `calls' the subroutine

      When the main program calls the subroutine,

   its execution is suspended

   Control jumps to the beginning of execution part of the subroutine

      When the subroutine completes its execution (by executing the RETURN statement or reaching the end of subroutine)

   Control returns to the main program

   Execution proceeds from the next statement

Call Control Flow

 

 

Call Data Flow

      The arguments given in a call statement are called actual arguments

      The number, order and type of actual arguments must match that of dummy arguments

      Subroutine declaration includes dummy argument declarations

      When the subroutine is invoked (called) by the main program, the values of actual and dummy arguments are exchanged.

      Values of some actual arguments are passed to the corresponding dummy ones at the beginning

      Values of some dummy arguments are passed to the actual ones at the end of the call

INTENT Declaration

      Dummy arguments are of three kinds:

            REAL, INTENT(IN)::            dummy1

            INTEGER, INTENT(OUT):: dummy2

            REAL, INTENT(IN OUT)::   dummy3

 

      dummy1 input argument: receives value at the beginning from corresponding actual argument

 

      dummy2 output argument: It passes a value at the end of the call to the corresponding actual argument

 

      dummy3 input-output argument: It receives a value at the beginning and passes a value at the end from/to the actual argument

Local Variables

      Besides dummy arguments, other variables may be declared in a subroutine

      They are called local since they are accessible only locally

      Main program can not access them

      The names of these variables (or dummy arguments) may be same as some other variables in the main program

      The name spaces are distinct

      Same variables names, labels can appear in a subroutine

Example

     Subroutine swap (var1,var2)
! swaps the contents of var1 and var2
implicit none

integer, intent(inout):: var1,var2

!local variable
integer :: temp

temp = var1
var1 = var2
var2 = temp

return
end Subroutine

 Explanation

      This subprogram takes two input arguments, swaps their contents and returns

      The two parameters are of intent INOUT so that values can be passed to and returned from them

      temp is a local variable

      This subroutine can be separately compiled

      It can be invoked from a main program

Main program

    program sort3

     implicit none

     integer *, x1,x2,x3

     read *, x1,x2,x3

     if (x1 > x2) then
     call swap (x1,x2)   ! call to the subroutine
     if (x2 > x3) then
           call swap (x2,x3)
           if (x1 > x2) then
              call swap(x1,x2)
          endif
     endif
elseif (x2 > x3) then
      call swap(x2,x3)
      if (x1 > x2) then
          call swap(x1,x2)
      endif
endif
write *, x1, x2, x3
end program

 Observation

      Any number of calls to the subroutines

 

      Each call supplies a list of actual arguments

 

      values of actual arguments will be changed after the call  if they are INOUT or OUT arguments

 

      Local variable temp is used in all the invocations

 

      Its value is different in different invocations

 

      It does not retain its value across invocations

 CALL statement

      CALL is an executable statement

      This can appear in the main program and even in the subroutine

      When the call statement in a subroutine is executed, control transfers to subroutine named in the call

      So, starting from a main program, a series of calls can be made to same or different subroutines

      Calls to the same subroutine possible - Recursive Call

Call - Return Sequence






 

Internal Procedures

      Subroutines appearing within the main program definitions are called internal procedures

   Their definition appear before the end statement of the program

   all subroutines given one after another

   no nesting of definition

   before the first subroutine, write  CONTAINS

   exactly one CONTAINS in a program

   variables declared in the main program can be used in the routine

   Global variables

Example

          Program example

          !declaration
          . . .
          !executable statement

               . . .
    
          Contains

                 Subroutine proc1
              ...
             end subroutine
            ...
        end Program

 

External Subroutines

      Subroutines can appear in separate files

   All the files compiled for generating a.out file

   They can be separately compiled to create .o file

   all the .o files and .for files can be finally compiled to create the final a.out file

      Libraries

   Many useful routines developed, compiled and collected together

   These can be used in your programs

   When compiling your programs the object codes of library routines are linked to get an executable

   Process of Linking

   intrinsic functions

General Picture of Compilation






 

Functions

      Functions are like subroutines

      Called from main program to do some independent computations

      The result of computations not passed via parameters

      Instead the function itself returns a value

      Functions are called inside an expression

      No separate call statement

Example

    Real Function x_mul(x)

!to evaluate the value of x(1-x*x)/5

implicit none

integer, intent(IN):: x

x_mul = x*(1 - x**2)/5

end function

 Observation

      The above is a function that computes x(1-x2), when given x

      The function definition looks similar to subroutines

      The value returned by the function is given in the header (Real)

      Note the intent declaration

      There is an assignment that assigns a variable with the same name as the function

Using a function

Program sum

real *, x, Sum
integer *, I

Sum = 0.0
do I = 1, 10
 
   Sum = Sum + x_mul(I)

end

print *, Sum

end program

Side Effects

      Invocation of the function takes place inside expression

      It is like evaluation, returns a value which is used in the expression

      Always use parameters to be of INPUT intent

      Otherwise, function invocation may change the contents of actual parameters

      Then after an expression evaluation, variables would change values

      This is called side effect

Functions and Subroutines

      Only one result would be returned by a function

      Type of the result given in the definition

      For multiple results, use subroutines

      Like subroutines, functions can call other functions

      Functions can be internal or external

      Many useful functions in libraries

PGPLOT Library

      This is a standard library for drawing graphs

      This library consists of various subroutines and functions

      For drawing various kinds of graphs with colours

      on a variety of medium like screen, plotters, etc.

      you can use the functions and routines of this library

      while compiling the name of the library need to be mentioned

      A separate tutorial on use of PGPLOT library

Save Attribute

      Local variables lose their values across different invocations

      Sometimes one would like to retain the values

      Recording of history

      Save attribute is used for this

      Declare in the procedure

   type_name, SAVE :: var_name

      Or initialize the local variable

An Example

Subroutine save_var(mark)

implicit none

integer :: passed = 0 ! This makes it retain the value

!alternately use, integer,save:: passed = 0

 

if (mark > 35) then

    passed = passed + 1

endif

if (mark < 0) then

    print *, passed

endif

end subroutine