14 - 2/11/2000AME 150 L Subroutine & Functions (& more on HW 7)

25
14 - 2/11/2000 AME 150 L AME 150 L Subroutine & Functions (& more on HW 7)

Transcript of 14 - 2/11/2000AME 150 L Subroutine & Functions (& more on HW 7)

Page 1: 14 - 2/11/2000AME 150 L Subroutine & Functions (& more on HW 7)

14 - 2/11/2000 AME 150 L

AME 150 L

Subroutine & Functions

(& more on HW 7)

Page 2: 14 - 2/11/2000AME 150 L Subroutine & Functions (& more on HW 7)

14 - 2/11/2000 AME 150 L

Homework 7

• Additions to HW61) Conversion of degrees to radians

2) many Logical Statements (IF's) to reduce size of argument to range

3) Change results as a consequence of earlier logical decisions

Page 3: 14 - 2/11/2000AME 150 L Subroutine & Functions (& more on HW 7)

14 - 2/11/2000 AME 150 L

x 2? x = MOD ( x , 2)

Yes

x ?

No !Now x 2

x = 2 - xNegative=.NOT. Negative

Yes

x /2?

x /4?

No

!Now x

No

x = - xYes

!Now x /2

x = /2 - xCosine=.TRUE.

Yes

!Now x /4No

Negative= (x<0)x= ABS(x)

The ABS operator makes x positive

Page 4: 14 - 2/11/2000AME 150 L Subroutine & Functions (& more on HW 7)

14 - 2/11/2000 AME 150 L

IMPLICIT NONEREAL :: x, x1, s1REAL, PARAMETER::pi=3.14159265, Two_pi=2.*piREAL, PARAMETER:: deg_to_rad=pi/180.LOGICAL :: Negative , Cosine! Get a value for x Negative = x < 0 ! Initialize Logical variables! Cosine = .FALSE. x = ABS(x) * deg_to_rad !convert degr to radians x1= MOD( x ,two_pi) !0 <= x1 <= 2 pi IF (x1 > pi) THEN x1 = Two_Pi - x1 Negative = .NOT. Negative END IF ! Now x1 is less than pi IF (x1>pi/2.) x1 = pi - x1 ! Now x1 is less than pi/2 IF (x1>pi/4.) THEN x1=pi/2.-x1 Cosine=.TRUE. END IF ! Now x1 is less than pi/4

Page 5: 14 - 2/11/2000AME 150 L Subroutine & Functions (& more on HW 7)

14 - 2/11/2000 AME 150 L

Truncating the Series

• Since the series will be calculated only for small values of x1 /4, only need 5 terms

x2 = x1*x1

sine = x*(1.-x2/6.*(1.-x2/20.*(1.-x2/42.*(1.-x2/72.))))

• Note the order of evaluation of the series (it's almost backwards) Horner's Rule

note also that

cosine = 1.-x2/2*(1.-x2/12.*(1.-x2/30.*(1.-x2/56.)))

Page 6: 14 - 2/11/2000AME 150 L Subroutine & Functions (& more on HW 7)

14 - 2/11/2000 AME 150 L

The "MOD" function

• A mod P is the fractional part of A/PMOD(A,P) A - P * INT( A / P )

• where INT is the integer part of a (real) division

• For ordinary integers, MOD(N,10) is the ones digit of N (the remainder of 10)

• and MOD(N,100)/10 is the tens digit

Page 7: 14 - 2/11/2000AME 150 L Subroutine & Functions (& more on HW 7)

14 - 2/11/2000 AME 150 L

Fortran Syntax

We now return to Subroutines, Functions, and other similar real and mythical beasts

Page 8: 14 - 2/11/2000AME 150 L Subroutine & Functions (& more on HW 7)

14 - 2/11/2000 AME 150 L

Programming Style

• It is often useful to set a very limited goal for a program module– Specify what program module is to do– Decide how program module will be invoked– Develop a testing strategy for the module– Code the program module

• Read B:284-348, D:81-119

Page 9: 14 - 2/11/2000AME 150 L Subroutine & Functions (& more on HW 7)

14 - 2/11/2000 AME 150 L

Invoke• in·voke (n-vk)

v. tr. in·voked, in·vok·ing, in·vokes.

– To call on (a higher power) for assistance, support, or inspiration: “Stretching out her hands she had the air of a Greek woman who invoked a deity” (Ford Madox Ford).

– To appeal to or cite in support or justification. – To call for earnestly; solicit: invoked the help of a passing motorist.

– To summon with incantations; conjure. – To resort to; use or apply: “Shamelessly, he invokes coincidence to achieve ironic effect” (Newsweek).

See Synonyms at enforce.

• [Middle English envoken, from Old French invoquer, from Latin invocre: in-, in; see in-2 + vocre, to call; see wekw- in Indo-European Roots.]

The American Heritage® Dictionary of the English Language, Third EditionCopyright © 1996, 1992 by Houghton Mifflin Company.

Page 10: 14 - 2/11/2000AME 150 L Subroutine & Functions (& more on HW 7)

14 - 2/11/2000 AME 150 L

Why Modular Programming?

• Small modules are easy to understand, develop, and code (lots of small modules)

• Easy to test & verify

• Can be used in many separate situations

• Can control and isolate effect of module

Page 11: 14 - 2/11/2000AME 150 L Subroutine & Functions (& more on HW 7)

14 - 2/11/2000 AME 150 L

What is a Module?

• A separately compiled program unit

• Common usage is– Main Program (just called PROGRAM)– External Procedures

Subroutine (argument list)

Function (argument list)

Page 12: 14 - 2/11/2000AME 150 L Subroutine & Functions (& more on HW 7)

14 - 2/11/2000 AME 150 L

Main Programs

• A Main Program is invoked by the operating system, and returns control to the operating system

• Any Program can invoke another program – IF the interface is clearly specified

• Rules for transferring control

• Rules for transferring data (in and out)

Page 13: 14 - 2/11/2000AME 150 L Subroutine & Functions (& more on HW 7)

14 - 2/11/2000 AME 150 L

Subroutines & Functions

• Declarations (same as PROGRAM)SUBROUTINE sub_name (argument_list)

…Fortran statements

END SUBROUTINE sub_name

and

FUNCTION funct_name (argument_list)

…Fortran statements

END FUNCTION funct_name

Page 14: 14 - 2/11/2000AME 150 L Subroutine & Functions (& more on HW 7)

14 - 2/11/2000 AME 150 L

InvocationCALL sub_name (argument_list)

– executable Fortran Statement

– Transfers control and passes data

• The function is slightly more complex in that it may appear in an expression and returns a value

var = funct_name (argument_list)• A function can be used anywhere a variable or

constant can appear (on the right hand side), or as an argument of an expression

Page 15: 14 - 2/11/2000AME 150 L Subroutine & Functions (& more on HW 7)

14 - 2/11/2000 AME 150 L

Argument List• Arguments are separated by commas, and

can be– Any Expression

• Constants

• Expressions

• Other Functions

– Pointers to arrays of data– Keyword controlled (Fortran 90 & later)

Page 16: 14 - 2/11/2000AME 150 L Subroutine & Functions (& more on HW 7)

14 - 2/11/2000 AME 150 L

ar·gu·ment (ärgy-mnt) noun (1)

• A discussion in which disagreement is expressed; a debate.

• A quarrel; a dispute.

• Archaic. A reason or matter for dispute or contention: “sheath'd their swords for lack of argument” (Shakespeare).

• A course of reasoning aimed at demonstrating truth or falsehood: presented a careful argument for extraterrestrial life.

• A fact or statement put forth as proof or evidence; a reason: The current low mortgage rates are an argument for buying a house now.

• A summary or short statement of the plot or subject of a literary work.

• A topic; a subject: “You and love are still my argument” (Shakespeare).

Page 17: 14 - 2/11/2000AME 150 L Subroutine & Functions (& more on HW 7)

14 - 2/11/2000 AME 150 L

ar·gu·ment (ärgy-mnt) noun (2)

• Logic. The minor premise in a syllogism.

• Mathematics.

• The independent variable of a function. • The amplitude of a complex number.

• Computer Science. A value used to evaluate a procedure or subroutine.[bad definition]

Page 18: 14 - 2/11/2000AME 150 L Subroutine & Functions (& more on HW 7)

14 - 2/11/2000 AME 150 L

ar·gu·ment (ärgy-mnt) noun (3)

[Middle English from Old French from Latin argmentum, from arguere, to make clear; see argue.]

Synonyms: argument, dispute, controversy. These nouns denote discussion involving conflicting points of view. Argument stresses the advancement by each side of facts and reasons buttressing its contention and intended to persuade the other side: Emotions are seldom swayed by argument. Dispute stresses division of opinion by its implication of contradictory points of view and often implies animosity: A dispute arose among union members about the terms of the new contract. Controversy is especially applicable to major differences of opinion involving large groups of people rather than individuals: The use of nuclear power is the subject of widespread controversy.

Page 19: 14 - 2/11/2000AME 150 L Subroutine & Functions (& more on HW 7)

14 - 2/11/2000 AME 150 L

Examples: Subroutine/Function Calls

CALL SUB1(X,Y,Z,a,b,c)

CALL SUB2(input_data, result)

CALL SUB3(SUB1 , SUB2(a,b) )

result=FUN1(a,b,result_2)

result=FUN2(x)*FUN3(y)

IF(FUN3(x)<=FUN4(Y))THEN …

WRITE(*,*)a,b,FUN7(a,b,SUB4(x))

Page 20: 14 - 2/11/2000AME 150 L Subroutine & Functions (& more on HW 7)

14 - 2/11/2000 AME 150 L

Declaration of Arguments

• Argument can carry data, defined in calling program, in to the subprogram INTENT(IN)

• Argument can point to a location defined in the calling program, that the subprogram will use to store resultsINTENT(OUT)

Page 21: 14 - 2/11/2000AME 150 L Subroutine & Functions (& more on HW 7)

14 - 2/11/2000 AME 150 L

Declaration of Arguments (2)

• Argument can point to a location defined in the calling program, that the subprogram will use as input, and then modifyINTENT(INOUT) or (IN OUT)

• Argument can point to the name of another external subroutine or functionEXTERNAL

Page 22: 14 - 2/11/2000AME 150 L Subroutine & Functions (& more on HW 7)

14 - 2/11/2000 AME 150 L

Declaration of Arguments (3)SUBROUTINE sub1 (a, b, i, My_Func)

IMPLICIT NONE

REAL, INTENT(IN):: a

REAL, INTENT(OUT)::b

INTEGER, INTENT(INOUT)::i

REAL, EXTERNAL:: My_Func…

RETURN

END SUBROUTINE sub1

Page 23: 14 - 2/11/2000AME 150 L Subroutine & Functions (& more on HW 7)

14 - 2/11/2000 AME 150 L

Declaration of Arguments (4)

REAL FUNCTION Funct (a, i, My_Func)

IMPLICIT NONE

REAL, INTENT(IN):: a

INTEGER, INTENT(INOUT)::i

REAL, EXTERNAL:: My_func…

Funct = {some expression}

RETURN

END FUNCTION Funct

Page 24: 14 - 2/11/2000AME 150 L Subroutine & Functions (& more on HW 7)

14 - 2/11/2000 AME 150 L

Scope of Variables• Arguments are variables that exist in the

calling program, that the subprogram can use in calculations if INTENT(IN)

• Other variables are local– Local variables exist only in the subprogram– Local variables have SAVE attribute by default,

unless SAVE is explicitly used in TYPE statements (unless some are named, then others are not)

Page 25: 14 - 2/11/2000AME 150 L Subroutine & Functions (& more on HW 7)

14 - 2/11/2000 AME 150 L

Checking arguments by Compiler

• Mismatch of arguments is a very common source of Fortran error

• If the Compiler could check, it can become an early error (not a run-time error)

• The CONTAINS statement/construct is used to pass information about subprograms to the compiler and the calling program