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

Similar documents
Computers in Engineering. Subroutines Michael A. Hawker

Computers in Engineering COMP 208. Subprograms. Subroutines. Subroutines Michael A. Hawker

3. Repetitive Structures (Loops)

Introduction to Fortran Programming. -Internal subprograms (1)-

type FUNCTION function-name (arg1, arg2,..., argn)

Review Functions Subroutines Flow Control Summary

Subroutines, Functions and Modules

An interesting related problem is Buffon s Needle which was first proposed in the mid-1700 s.

Subroutines and Functions

Program Structure and Format

FORTRAN 90: Functions, Modules, and Subroutines. Meteorology 227 Fall 2017

Introduction to Fortran Programming. -External subprograms-

Edit Descriptors. Decimal form. Fw.d Exponential form Ew.d Ew.dEe Scientific form ESw.d ESw.dEe Engineering form ENw.d ENw.dEe.

Logical Expressions and Control Statements

NO CALCULATOR ALLOWED!!

Counting Loop: DO-END DO. DO var = initial-value, final-value, step-size

Old Questions Name: a. if b. open c. output d. write e. do f. exit

AN INTRODUCTION TO FORTRAN 90 LECTURE 2. Consider the following system of linear equations: a x + a x + a x = b

SUBPROGRAMS AND MODULES

Review More Arrays Modules Final Review

Introduction to Modern Fortran

(Refer Slide Time 01:41 min)

Computers in Engineering. Moving From Fortran to C Michael A. Hawker

7. Procedures and Structured Programming

Subprograms. FORTRAN 77 Chapter 5. Subprograms. Subprograms. Subprograms. Function Subprograms 1/5/2014. Satish Chandra.

INF 212 ANALYSIS OF PROG. LANGS PROCEDURES & FUNCTIONS. Instructors: Kaj Dreef Copyright Instructors.

Reusing this material

Dept. of CSE, IIT KGP

Goals for This Lecture:

UNIT - I. Introduction to C Programming. BY A. Vijay Bharath

Assignment: 1. (Unit-1 Flowchart and Algorithm)

Object Oriented Programming Using C++ Mathematics & Computing IET, Katunayake

Welcome. Modern Fortran (F77 to F90 and beyond) Virtual tutorial starts at BST

Inductive Data Types

References and pointers

1. User-Defined Functions & Subroutines Part 1 Outline

Fortran 95/2003 Course

CS 345. Functions. Vitaly Shmatikov. slide 1

UNIT V Sub u P b ro r g o r g a r m a s

Subprograms. Bilkent University. CS315 Programming Languages Pinar Duygulu

AMath 483/583 Lecture 8

Flow Chart. The diagrammatic representation shows a solution to a given problem.

APSC 160 Review. CPSC 259: Data Structures and Algorithms for Electrical Engineers. Hassan Khosravi Borrowing many questions from Ed Knorr

COMP 208 Computers in Engineering

Module 25.2: nag correl Correlation Analysis. Contents

PROBLEM SOLVING WITH FORTRAN 90

CS 314 Principles of Programming Languages

Discussion 1H Notes (Week 3, April 14) TA: Brian Choi Section Webpage:

Computer Engineering 1 (1E3)

1 Introduction to MATLAB

I SEMESTER EXAM : : XI :COMPUTER SCIENCE : MAX MARK a) What is the difference between Hardware and Software? Give one example for each.

Review Chapter 6 in Bravaco. Short Answers 1. This type of method does not return a value. a. null b. void c. empty d. anonymous

Assignment 6. Methods Homework Spring 2017 P Question 1 all

SYSC 2006 C Winter 2012

CSE 341 Section Handout #6 Cheat Sheet

Paul F. Dubois. X-Division.

Concepts Review. 2. A program is the implementation of an algorithm in a particular computer language, like C and C++.

Agenda. The main body and cout. Fundamental data types. Declarations and definitions. Control structures

1 Introduction to MATLAB

Extrinsic Procedures. Section 6

1. Character 2. Subrotinas e funções

Flow Control: Branches and loops

Multiple Choice (Questions 1 14) 28 Points Select all correct answers (multiple correct answers are possible)

C for Engineers and Scientists

Programming Tips for Plugins

Procedural programming with C

Array Processing { Part II. Multi-Dimensional Arrays. 1. What is a multi-dimensional array?

Functions. Arash Rafiey. September 26, 2017

Chapter 6. A Brief Introduction to Fortran David A. Padua

Page 1 of 7. Date: 1998/05/31 To: WG5 From: J3/interop Subject: Interoperability syntax (Part 1) References: J3/98-132r1, J3/98-139

Computational Astrophysics AS 3013

Multiple Choice (Questions 1 13) 26 Points Select all correct answers (multiple correct answers are possible)

Here n is a variable name. The value of that variable is 176.

Table 2 1. F90/95 Data Types and Pointer Attributes. Data Option. (Default Precision) Selected-Int-Kind

PACKAGE SPECIFICATION HSL 2013

Numerical Modelling in Fortran: day 2. Paul Tackley, 2017

A. Incorrect! This would be the negative of the range. B. Correct! The range is the maximum data value minus the minimum data value.

Practical Exercise 1 Question 1: The Hello World Program Write a Fortran 95 program to write out Hello World on the screen.

1. In C++, reserved words are the same as predefined identifiers. a. True

Data Abstraction. Andrew DeOrio. andrewdeorio.com (3,4,5) (-3,4,5)

CS558 Programming Languages

Allocating Storage for 1-Dimensional Arrays

Goals for This Lecture:

and n is an even positive integer, then A n is a

ParaFEM Coding Standard for Fortran 90. Contents. 1.0 Introduction. 2.0 Documentation. 2.1 External Documentation

1- Write a single C++ statement that: A. Calculates the sum of the two integrates 11 and 12 and outputs the sum to the consol.

FORM 2 (Please put your name and form # on the scantron!!!!)

Principles of Programming Languages

A Brief Introduction to Fortran of 15

n Group of statements that are executed repeatedly while some condition remains true

CS111: PROGRAMMING LANGUAGE II

There are four numeric types: 1. Integers, represented as a 32 bit (or longer) quantity. Digits sequences (possibly) signed are integer literals:

7 Control Structures, Logical Statements

Run-Time Data Structures

Goals for This Lecture:

Implementing Subprograms

Lectures 4 and 5 (Julian) Computer Programming: Skills & Concepts (INF-1-CP1) double; float; quadratic equations. Practical 1.

Introduction to Fortran Programming. - Module -

Computer Programming, I. Laboratory Manual. Experiment #3. Selections

CA4003 Compiler Construction Assignment Language Definition

Transcription:

FORTRAN Subroutines Syntax Form 1 SUBROUTINE subroutine-name (arg1, arg2,..., argn) [specification part] [execution part] [subprogram part] subroutine-name Form 2 SUBROUTINE subroutine-name () [specification part] [execution part] [subprogram part] subroutine-name Form 3 SUBROUTINE subroutine-name [specification part] [execution part] [subprogram part] subroutine-name

FORTRAN Subroutines 1. Subroutine can be internal or external to a program or a module. 2. 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 some formal arguments. 3. Unlike functions, the name of a subroutine is simply a name for identication purpose and cannot be used in computation. 4. Subroutines can only be CALLed. 5. A subroutine receives its input values from formal arguments, does computations, and saves the results in some of its formal arguments. When the control of execution reaches, the values stored in some formal arguments are passed back to their corresponding actual arguments. 6. Any statements that can be used in a PROGRAM can also be used in a SUBROUTINE.

Arguments' INTENT 1. A formal argument can be declared with INTENT(IN), INTENT(OUT), or INTENT(INOUT). 2. If an argument only receives value from outside of the subroutine, its intent is INTENT(IN). This is the simplest case. 3. 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 is INTENT(OUT). In a subroutine, an argument declared with INTENT(OUT) is supposed to hold a computation result so that the nal value can be passed \out". 4. 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).

5. In subroutine Means(), formal arguments a, b and c receive values from outside and are used to compute results into Am, Gm and Hm. The values stored in Am, Gm and Hm are passed back. SUBROUTINE IMPLICIT Means(a, b, c, Am, Gm, Hm) NONE REAL, INTENT(IN) :: a, b, c REAL, INTENT(OUT) :: Am, Gm, Hm... Means 6. In subroutine Swap(), formal arguments a and b receive values from outside and are used to compute some results which are stored back to a and b. SUBROUTINE Swap(a, b) IMPLICIT NONE INTEGER, INTENT(INOUT) :: a, b... Swap

The CALL Statement Syntax CALL subroutine-name (arg1, arg2,..., argn) CALL subroutine-name () CALL subroutine-name When the CALL statement is executed, values of actual arguments are passed to those formal arguments declared with INTENT(IN) and INTENT(INOUT). Then, the statements of the called subroutine are executed. When the execution reaches, values stored in those formal arguments declared with INTENT(OUT) and INTENT(INOUT) are passed back to their corresponding actual arguments. The caller executes the statement following the CALL statement.

Short Examples The larger value of two. PROGRAM Example1 SUBROUTINE Larger(u, v, w) 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 Larger Sort two numbers into increasing order. PROGRAM Example2 SUBROUTINE Sort(u, v) 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 Sort

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

Computing Means PROGRAM Mean6 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(a, b, c, Am, Gm, Hm) 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) Means END PROGRAM Mean6

PROGRAM HeronFormula REAL REAL Triangle Area :: Side1, Side2, Side3 :: Answer LOGICAL :: ErrorStatus READ(*,*) Side1, Side2, Side3 CALL TriangleArea(Side1, SIde2, Side3, Answer, ErrorStatus) IF (ErrorStatus) THEN WRITE(*,*) "ERROR: not a triangle" ELSE WRITE(*,*) END IF "The triangle area is ", Answer CONTAINS SUBROUTINE IMPLICIT REAL, INTENT(IN) REAL, INTENT(OUT) TriangleArea(a, b, c, Area, Error) NONE :: a, b, c :: Area LOGICAL, INTENT(OUT) :: Error 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 ELSE Error =.FALSE. s = (a + b + c)/2.0 Area = SQRT(s*(s-a)*(s-b)*(s-c)) Error =.TRUE. Area = 0.0 END IF TriangleArea END PROGRAM HeronFormula

YYYYMMDD to Year, Month and Day PROGRAM IMPLICIT INTERFACE YYYYMMDDConversion NONE SUBROUTINE Conversion(Number, Year, Month, Day) INTEGER, INTENT(IN) :: Number INTEGER, INTENT(OUT) :: Year, Month, Day END INTERFACE Conversion INTEGER :: YYYYMMDD, Y, M, D DO WRITE(*,*) "A YYYYMMDD please (0 to stop) -> " READ(*,*) YYYYMMDD IF (YYYYMMDD == 0) EXIT CALL Conversion(YYYYMMDD, Y, M, D) WRITE(*,*) "Year = ", Y WRITE(*,*) "Month = ", M WRITE(*,*) "Day = ", D WRITE(*,*) END DO END PROGRAM YYYYMMDDConversion SUBROUTINE Conversion(Number, Year, Month, Day) INTEGER, INTENT(IN) :: Number INTEGER, INTENT(OUT) :: Year, Month, Day Year = Number / 10000 Month = MOD(Number, 10000) / 100 Day = MOD(Number, 100) Conversion

PROGRAM IMPLICIT QuadraticEquation NONE INTEGER, PARAMETER :: NO_ROOT = 0 INTEGER, PARAMETER :: REPEATED_ROOT = 1 INTEGER, PARAMETER :: DISTINCT_ROOT = 2 INTEGER REAL READ(*,*) CALL a, b, c :: SolutionTypee :: a, b, c, r1, r2 Solver(a, b, c, r1, r2, SolutionType) SELECT CASE (SolutionType) CASE (NO_ROOT) WRITE(*,*) CASE (REPEATED_ROOT) "no real root" WRITE(*,*) "repeated root ", r1 CASE (DISTINCT_ROOT) END SELECT CONTAINS SUBROUTINE WRITE(*,*) IMPLICIT "two roots ", r1, " and ", r2 Solver(a, b, c, Root1, Root2, Type) NONE REAL, INTENT(IN) REAL, INTENT(OUT) INTEGER, INTENT(OUT) :: Type REAL Root1 = 0.0 Root2 = 0.0 d = b*b - 4.0*a*c IF (d < 0.0) THEN Type = NO_ROOT :: a, b, c :: Root1, Root2 :: d ELSE IF (d == 0.0) THEN Type = REPEATED_ROOT Root1 = -b/(2.0*a) ELSE Type d = DISTINCT_ROOT = SQRT(d) Root1 = (-b + d)/(2.0*a) Root2 = (-b - d)/(2.0*a) END IF Solver

Mean, Variance and Standard Deviation Mean = 1 0 1 B@ X n n i=1 x i CA 0 1 X Variance = B@ n i=1 x2 i 1 0 1 B@ X n CA 21 C A n n 1 Standard Deviation = p Variance i=1 x i PROGRAM MeanVariance INTEGER :: Number, IOstatus REAL :: Data, Sum, Sum2 REAL :: Mean, Var, Std Number = 0 Sum = 0.0 Sum2 = 0.0 DO READ(*,*,IOSTAT=IOstatus) Data IF (IOstatus < 0) EXIT Number = Number + 1 WRITE(*,*) "Data item ", Number, ": ", Data CALL Sums(Data, Sum, Sum2) END DO CALL CALL Results(Sum, Sum2, Number, Mean, Var, Std) PrintResult(Number, Mean, Var, Std)

CONTAINS SUBROUTINE Sums(x, Sum, SumSQR) REAL, INTENT(IN) :: x REAL, INTENT(INOUT) :: Sum, SumSQR Sum = Sum + x SumSQR = SumSQR + x*x Sums SUBROUTINE Results(Sum, SumSQR, n, Mean, Variance, StdDev) 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) SUBROUTINE PrintResult(n, Mean, Variance, StdDev) 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 PrintResult END PROGRAM MeanVariance

More About Argument Association The corresponding actual argument of a formal argument declared with INTENT(OUT) or INTENT(INOUT) must be a variable. PROGRAM Errors SUBROUTINE Sub(u,v,w,p,q) 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... Sub ): INTENT(IN) (: INTENT(OUT),: INTENT(INOUT) 1 ( u: Wrong a, v: Wrong b+c ) w: correct (c) ( p: Wrong 1+a ) q: correct.