+ All Categories
Home > Documents > Fortran Notes Cambridge University

Fortran Notes Cambridge University

Date post: 10-Sep-2015
Category:
Upload: hugo-contreras
View: 24 times
Download: 5 times
Share this document with a friend
Description:
Fortran Notes
215
CAMBRIDGE FACULTY OF MATHEMATICS FORTRAN PROGRAMMING COURSE *********************************************************** Outline ======= This basic course focuses on the aspects of the language essential to understanding existing code and the writing of new Programs. No previous experience is needed. As an introduction, a short history traces the origins and development of the various versions of Fortran up to the most recent (2003) standard. However, the course deals mainly with the 1977 Standard ("Fortran 77"), but considers those features of the 1990 and later standards ("Fortran 90") most likely to be encountered in and of most value to scientific and mathematical programming. The course comprises 6 one Hour Lectures. The first 2 cover Program structure, data representation and basic flow control constructs, aimed at entry level Fortran programmers. Then Array handling, Files and I/O (Input and Output) and Program Units, are visited, and a full Program is walked through in the last session. A seminar on High Performance (HPC) programming should follow the course. 1
Transcript
  • CAMBRIDGE FACULTY OF MATHEMATICS FORTRAN PROGRAMMING COURSE

    ***********************************************************

    Outline

    =======

    This basic course focuses on the aspects of the language essential to

    understanding existing code and the writing of new Programs. No previous

    experience is needed. As an introduction, a short history traces the

    origins and development of the various versions of Fortran up to the most

    recent (2003) standard. However, the course deals mainly with the 1977

    Standard ("Fortran 77"), but considers those features of the 1990 and

    later standards ("Fortran 90") most likely to be encountered in and of

    most value to scientific and mathematical programming.

    The course comprises 6 one Hour Lectures. The first 2 cover Program

    structure, data representation and basic flow control constructs, aimed

    at entry level Fortran programmers. Then Array handling, Files and I/O

    (Input and Output) and Program Units, are visited, and a full Program is

    walked through in the last session. A seminar on High Performance (HPC)

    programming should follow the course.

    1

  • Contents - Part 1

    ==================

    Introduction : Fortran, a Brief History

    Fortran Program and Code Structure :

    1/ General Fortran Program Structure

    2/ Fortran Statements

    3/ Fortran Fixed Form Code Example (clpent.for)

    4/ Fortran Free Form Code Example (clpent.f90)

    Fortran Data Representation :

    1/ Introduction

    2/ Basic Declaration Form

    3/ Entity (Variable) Names

    4/ Basic (Intrinsic) Types

    5/ Implicit and Explicit Data Types

    6/ Basic (Intrinsic) Type Constants

    7/ Declared (Named) Constants

    8/ Variable Initialisations

    9/ Common Blocks

    10/ Overlays (Equivalences)

    11/ Common Block Data Initialisations

    Fortran Assignments and Operations :

    1/ Introduction

    2/ Basic Assignment Form

    3/ Basic Assignment with COMPLEX Variables

    4/ Basic Assignment of LOGICAL Variables

    5/ Basic Assignment aspects for CHARACTER Variables

    6/ Fortran Expressions

    7/ Fortran Numeric (Arithmetic) Expressions

    8/ Fortran Character (String, or Text) Expressions

    9/ Fortran Logical Expressions

    2

  • Contents - Part 2

    ==================

    Fortran Flow Control and Logic :

    1/ Introduction

    2/ Relational (Conditional) Expressions

    3/ Relational Expressions with Arithmetic Operands

    4/ Relational Expressions with COMPLEX Type Operands

    5/ Relational Expressions with CHARACTER Operands

    6/ Composite Relational Expressions

    7/ Fortran Logical IF Statement

    8/ Fortran Block IF Statements

    9/ Arithmetic IF Statement

    10/ Loops (Iterative constructs) in Fortran

    11/ Branches in Fortran

    12/ Use if INTEGER Variables for Labels in Fortran

    13/ Exiting Fortran Programs

    Fortran Array Processing :

    1/ Introduction

    2/ Array Declarations

    3/ Array Subscript Range Declarations

    4/ Array Declaration Examples

    5/ Arrays in Common Blocks

    6/ Array Storage Rules

    7/ Array Initialisations

    8/ Array Initialisations with Implied DO Loops

    9/ Array Element Access and Assignment

    10/ Array Access and Assignment with DO Loops

    11/ Multidimensional Array Access and Assignment

    12/ Additional Array Processing Features in Fortran 90

    13/ Whole Array or Section Processing in Fortran 90

    14/ Array Section Processing in Fortran 90

    15/ Array Section Processing with Vectors in Fortran 90

    16/ Array Intrinsic Functions in Fortran 90

    17/ WHERE Statements to Process Arrays in Fortran 90

    3

  • Contents - Part 3

    ==================

    Fortran Files And I/O (Input/Output) :

    1/ Introduction

    2/ External File handling and I/O Units

    3/ General Form of Input/Output Statements

    4/ External File Connection, OPEN Statement

    5/ External File Connection, OPEN Statement Examples

    6/ External File Release, CLOSE Statement

    7/ External File Enquiries, INQUIRE Statement

    8/ Input from Files, READ Statement

    9/ Formatted READ Statement Examples

    10/ Unformatted READ Statement Examples

    11/ List Directed READ Statement

    12/ List Directed READ Statement examples

    13/ Input from Internal Files

    14/ Output to Files, WRITE Statement

    15/ External File Repositioning Statements

    16/ Formatted Record Layout, FORMAT Statements

    17/ Formatted Record Layout, FORMAT Statements examples

    Fortran Program Units :

    1/ Introduction

    2/ Invoking Subprograms

    3/ Subprogram Structure and Variables

    4/ Subprogram Execution and Termination

    5/ Function Subprograms

    6/ Subroutine Subprograms

    7/ Assumed Size Arrays and CHARACTER Variables

    8/ Function Subprogram example

    9/ Subroutine Subprogram example

    10/ Intrinsic Functions

    11/ Selected Intrinsic Functions

    12/ Selected Intrinsic Functions New in Fortran 90

    13/ Subprograms as Call Arguments

    4

  • Contents - Part 4

    ==================

    Fortran Program Example :

    1/ Introduction

    2/ Example Program Source Code

    3/ Example Program Control Parameters File

    4/ Example Program Input Data File

    5/ Example Program Output Data File and Run Report

    6/ Observations from Example Program

    7/ General Guidelines

    Appendix 1, Fortran Resources :

    1/ Overview

    2/ General Programming and Specialist Resources

    3/ ANSI (and ISO) Fortran Standards

    4/ Compiler and Implementation Manuals

    5/ Fortran Resources on the World Wide Web

    6/ Selected Fortran 77 Literature

    7/ Selected Fortran 90, 95 and 2003 Literature

    8/ Numerical Applications Literature

    9/ General Programming Literature

    10/ Hardware Design and Performance Literature

    Appendix 2 : Downloading and Running the Examples :

    1/ Downloading the Example Routines and Data Files

    2/ Compiling and Running the Example Routines

    5

  • Fortran, a Brief History - Part 1

    ==================================

    Fortran stands for "Formula Translation". It was the first High Level

    or Third Generation programming language. Before it, all Programs were

    written in Assembler, where one Program Instruction corresponded to a

    single machine operation, and each model of computer featured its own

    Instruction Set.

    Coding in Assembler or Machine Code (where the Mnemonics naming data

    entities or Instructions were replaced by the raw numeric Values and

    Addresses understood by the hardware) was tedious. In 1953, John Backus,

    an IBM researcher proposed the idea of Fortran to ease coding numerical

    and engineering calculations. IBM took up the idea. A first manual was

    ready by October 1956. The Fortran Code, where each Statement could

    replace several Assembler Instructions was transformed to Machine Code

    by a special Program called the Compiler. IBM was worried that Fortran

    would not prove successful if the performance of compiled Binaries did

    not come close to that of hand crafted Assembler Programs, so a lot of

    effort went into optimisation right from the first Fortran Compiler.

    Released in 1957 on the IBM 704 Mainframe, it turned into an instant

    success. The compiled code still delivered good speed compared to the

    Assembler equivalent, but complicated algorithms could be coded in a

    fraction of the time needed before. Fortran II followed in 1958, adding

    Subroutines. Fortran IV, released in 1962 became the de facto standard,

    before it was adopted by the American National Standards Institute in

    1966 as the first (ANSI) standard programming language. By then, several

    other languages had emerged, like ALGOL (Algorithmic Language, 1958),

    COBOL (Common Business Oriented Language, 1960), BASIC (Beginners All

    Purpose Symbolic Instruction Code) and PL/1 (Programming Language 1,

    1964). The latter, from IBM, represented the first universal language

    attempt. It never really left the realm of IBM Mainframes.

    Other computer manufacturers had by the time also produced their own

    Fortran Compilers (as well as offerings for COBOL and Algol). With the

    System 360 Mainframes of 1964, IBM created the first family of genuine

    Plug Compatible computers, which became widespread and emulated by the

    other manufacturers (Britains indigenous manufacturer, I.C.T. offered

    the 1900 series for instance). Much as COBOL became the language of

    choice for commercial applications, Fortran remained predominant in

    scientific programming.

    6

  • Fortran, a Brief History - Part 2

    ==================================

    The 1966 ANSI Standard always represented a minimum specification of

    what the different compilers supported. By the late 1970s, the need

    for a new standard was felt, so the more widespread extensions could be

    included. The 1977 Standard (published in 1978) added CHARACTER Type

    Variables, Block IF constructs, and much enhanced File handling.

    Over the 1980s, the need emerged to incorporate more extensions, but

    also keep the language in tune with programming practice. However, the

    discussions over a new standard, labelled "Fortran8x" proved conflictual

    between those after a minimal expansion and retained compatibility with

    previous versions, and those seeking a more radical redesign. For lack

    of features such as User defined types, or block structured constructs,

    Fortran was being replaced by C, C++ and other languages in a lot

    of applications. It remained very prominent in the sciences though, if

    only because of the vast body of existing Code still in use.

    Also, the tightly defined features and fixed memory model of Fortran

    programs allowed good optimisation of the code. Fortran was the choice

    language on high performance hardware. Its only recently that C++

    Compilers managed producing executables of comparable efficiency to

    their Fortran equivalents.

    Fortan8x finally emerged as Fortran 90 in 1992. Full compatibility

    was preserved, but a lot was added. Free form Source Code, long Names

    and in line Comments eased coding style constraints. New DO WHILE

    and SELECT CASE constructs appeared as did Modules and interfacing

    specifications. A lot of new Intrinsic Functions were included. But,

    the most important development from the scientific viewpoint was that

    Arrays, or parts of them could be manipulated or operated upon (with

    arithmetic or Intrinsic Functions) as single objects.

    Fortran 90 introduced the idea of more regular revisions to the latest

    standard as well as of it charting a way forward for the language. It

    effectively entered constant review. Starting with Fortran 90, items for

    eventual removal are marked as "Obsolete". A few lesser used features

    (PAUSE, ASSIGN and Arithmetic IF Statements for example) were the first.

    These were removed in the next Standard, Fortran 95. Others, including

    Fixed Form Source coding were in then marked for deletion. The important

    scientific aspect of Fortran 95 lies in it now including High Performance

    Fortran elements. The 95 Standard was adopted in 1997.

    7

  • Fortran, a Brief History - Part 3

    ==================================

    Fortran 2003 followed as the next standard, released in 2004. It brought

    interoperability with other languages (mainly C and C++), more object

    oriented programming features, and formalised Exception handling. Items

    obsoleted in 1995 were in fact not removed. With most compilers still

    offering features deleted in the 95 standard, the original 1950 Programs

    should still Compile and run !

    Fortran thus retains a lot of its original concepts and qualities, but

    has again become a modern language, now perfectly suitable for tasks or

    programming methods not yet imagined in the mid 1950s.

    It took a long time for Fortran 90 and later compilers to write Binaries

    getting near the performance of 77 Binaries. So, Fortran 77, if not "the"

    recommended language on supercomputers remains in widespread use on such

    systems. It also forms a much simpler and smaller language than the later

    versions, so forms a good starting point.

    This course focuses on Fortran 77, but will mention Fortran 90 additions

    commonly seen or useful in scientific programming, like Array handling.

    For a more detailed history of the language, see the Fortran Wikipedia

    Page (see http://en.wikipedia.org/wiki/Fortran) or chapter 1, "Whence

    Fortran" from "Fortran 95/2003 Explained" (M. Metcalf, J. Reid, M. Cohen,

    Oxford University Press, 2004, ISBN 0-19-852692-X). The first chapter in

    Volume II of "Handbook of Programming Languages" (P.H. Salus, Macmillan

    Technical Publishing, 1998, ISBN 1-57870-009-4) also begins with a short

    history, emphasising the role of the standards.

    8

  • Fortran Program and Code Structure - Part 1

    ============================================

    - 1/ General Fortran Program Structure :

    Fortran constitutes an Imperative High Level programming language,

    in that the Source Code in Programs is not directly understood, let

    alone executed by the hardware. Instead, the Code is submitted to a

    Compiler which writes out a Binary or Executable Module, containing

    (Machine Code) Instructions appropriate (and often peculiar to) the

    Hardware being used.

    All Fortran Programs begin with a "Non Executable" Part, where

    Variables, Arrays, and Constants may be declared and initialised.

    The "Executable" Part follows, in which all computations, logic,

    and File handling take place.

    Diagrammatic form of a Fortran Program :

    Program : PROGRAM Statement : Optional to Name Program

    Non Executable Part : Non Executable Statements

    Executable Part : Executable Statements

    END : Completes Executable Part

    The two small example Programs at the end of the chapter both

    use Comments to indicate the Non Executable and Executable Parts.

    The PROGRAM Statement at the top Names the Program and marks it

    as a Main Program, as opposed to a Subprogram or Subroutine. The

    PROGRAM Statement is not required, in which case a (unnamed) Main

    Program is assumed. Providing a name can help in tracing Errors,

    or just which Routine is executing at any time.

    Other Statements than PROGRAM would be used (FUNCTION, SUBROUTINE

    or BLOCK DATA) for Subprograms. A (Main) Program makes up a stand

    alone Execution Unit, which can be invoked and run by the (computer)

    system, while Subprograms may not. They need to be invoked (or, in

    programming terminology, "called") from a Main Program. Subprograms

    will be covered in a later chapter of these notes. Subprograms can

    themselves call other Subprograms.

    An END Statement must be present to terminates all Routines.

    9

  • Fortran Program and Code Structure - Part 2

    ============================================

    - 2/ Fortran Statements :

    In Fortran Programs, the Source Code, or simply Code, is written

    as Statements, the equivalent of phrases in English. Except from

    Comments and Blank Lines which may appear anywhere in Programs,

    Statements are either "Non Executable", in which case they may only

    show in the Non Executable Part, or "Executable", only to be used

    in the Executable Part.

    Blank Lines may be placed anywhere in any Source File, and Comment

    Statements ditto, even part way through other Statements. Comments

    are indicated by a C (Upper or Lower Case) or Asterisk (*) in

    the leftmost Position (Column 1) of every Line deemed a Comment :

    * Various ways to indicate Comment Statements (Lines)

    c

    CCCC

    Statements by default take one Line. No terminators are required.

    10

  • Fortran Program and Code Structure - Part 3

    ============================================

    - 2/ Fortran Statements (continued) :

    Columns 1 to 5 are either left blank, or may contain a Numeric Label

    of up to 5 Digits. Labels act as Addresses in Programs. Executable

    Statements can be referred to by their Labels, or (logical) flow

    transferred to them from elsewhere in Routines. Every Label must be

    unique in the Routine it appears in, but no particular ordering of

    Label Values is imposed.

    Labels may sit with any number of blanks before or after, but not

    within, and must not spill over beyond Column 5. Leading Zeros in

    Labels are ignored so 0020 and 20 both refer to Label 20, but

    at least one Digit must be non Zero.

    Column 6 is always reserved for a Continuation Mark, when the Line

    becomes a Continuation of that above. Any non Blank Character apart

    from Zero may be used for that purpose. In Fortran 77, up to 19

    Continuation Lines are allowed. Excluding Comments or blank Lines,

    this means any Statement may occupy up to 20 Lines.

    Columns 7 to 72 inclusive should contain the Code, which need not

    start at Column 7. Columns 73 onwards are ignored. The limitation

    originates from the early years of the language, when many Programs

    were submitted via Punched (Hollerith) Cards, on which Columns 73 to

    80 were left aside for a Card Number in the Deck. Most Terminal or

    Editor Windows will offer 80 Character wide Lines but can be set

    to 72, or Marker Comment Lines of that length slotted in the Code.

    Compilers by default will not flag the presence of Code beyond

    Column 72. However, options exist in most to either generate errors

    in such cases, or allow Lines of a greater length to be used. This

    became part of the Fortran 90 Standard where up to 132 Characters

    are allowed per Line.

    11

  • Fortran Program and Code Structure - Part 4

    ============================================

    - 2/ Fortran Statements (continued) :

    Diagrammatic form of Fortran (77) Statements :

    Cols 1-5 Col 6 Col 7-72 Col 73 onwards

    -------- ----- ---------------------- --------------

    Numeric Cont. Fortran Statement Text Ignored

    Label Mark

    Example Fortran 77 Statements, second one with a Continuation :

    CHARACTER * 32 CLNE1, CLNE2

    1000 WRITE ( *, 10000 ) CLNE1,

    1 CLNE2

    10000 FORMAT ( A, A )

    Fortran 90 extended the permitted Length of Lines to 132 Characters

    with up to 31 Continuation Lines per Statement. Comments could be

    initiated with an Exclamation Mark (!). That can appear at any

    point along the Line, with or without Code preceding it, and will

    turn the rest of the Line into a Comment, for example :

    CHARACTER ( 32 ) CLNE1, CLNE2 ! Two Lines for Results.

    10000 FORMAT ( A, A ) ! Two Character Strings.

    Additionally, multiple Statements could appear on one Line, with

    Semi Colons separating them. In that case, the Column following

    a Semi Colon took the role of Column 1 if that Statement had been

    on the following Line, and so on. This breaks the model of "One

    Statement, one or more Lines and no Terminators" of early versions

    of the language and can be confusing. Semi Colons are used in many

    other languages as Terminators (C, Pascal, or PL/1 for instance),

    and the lack of them makes Fortran Code easy to detect.

    12

  • Fortran Program and Code Structure - Part 5

    ============================================

    - 2/ Fortran Statements (continued) :

    Strictly Standard conforming Fortran 77 Statements should be

    written using only the "Fortran Character Set", as follows :

    A to Z (Upper Case Letters),

    0 to 9 (Digits 0 to 9),

    Blank (not Tab, Null or other non Display Chars),

    = (Equal Sign),

    + and - (Plus and Minus Signs),

    * (Asterisk, used in various roles),

    / (Slash, Divide and Line Feed Operator),

    ( and ) (Left (Open) and Right (Close) Parentheses),

    . (Dot, Condition Delimiter and Decimal Point),

    , (Comma, Separator for any Lists),

    : (Colon, used in various separation roles),

    (Single Quote (Apostrophe), Text Delimiter),

    $ (Dollar, Currency Sign).

    The Currency Sign need not be Dollar but must be present and

    distinct from the other Characters. It plays no special role.

    Fortran 90 extended the Fortran Character Set to include :

    _ (Underscore, may be used in Names),

    % (Per Cent, Derived Types component Delimiter),

    " (Double Quote, alternative Character Delimiter),

    < and > (Less and Greater than, Relational Operators),

    ! (Exclamation Mark, begins a Comment),

    & (Ampersand, Line Continued symbol (at end)),

    ; (Semi Colon, Statement Separator on Line),

    ? (Question Mark, no special role (like $)).

    Note no requirement exists for the presence of Lower Case Letters.

    These notes present all code examples and passages in Upper Case

    to distinguish them from the rest of the text, using Single Quotes

    to delimit Names and Expressions when used inside paragraphs.

    13

  • Fortran Program and Code Structure - Part 6

    ============================================

    - 2/ Fortran Statements (continued) :

    Spaces may be inserted anywhere in Statements, as long as Column

    restrictions are not infringed, and all Keywords, Names and Labels

    remain atomic, so, for example :

    CHARACTER*12 CC

    CHARACTER * 12 CC

    CHARACTER * 12 CC

    will all be equivalent, as will :

    IF(II.EQ.3)YY=XX+5*ZZ**2

    IF ( II.EQ.3 ) YY = XX+5*ZZ**2

    IF ( II .EQ. 3 ) YY = XX + 5 * ZZ ** 2

    but this Code would be invalid :

    CHAR ACTER * 12 CC

    CHARACTER * 12 C C

    CHARACTER * 1 2 CC

    I F(II.EQ.3)YY=XX+5*ZZ**2

    IF ( II.EQ.3 ) Y Y = XX+5*ZZ**2

    IF ( II .E Q. 3 ) YY = XX+5*ZZ**2

    As will be seen when Variables and Constants are described, Spaces

    inside the Single Quote delimited Value of a CHARACTER Variable or

    Constant are significant unless no non Blank Characters follow them.

    Such Spaces in effect become part of that Strings Value.

    On most modern implementations, Fortran Statements may be written

    in any mixture of Upper and Lower case Letters, which are treated

    the same, Lower case being equivalent to Upper. For example :

    CHARACTER * 12 CC

    Character * 12 CC

    character * 12 cc

    would all declare a 12 Byte (Positions) Character Type Variable.

    Originally capitals only were used to simplify parsing by Compilers,

    and some of the Character sets did not include Lower Case letters.

    14

  • Fortran Program and Code Structure - Part 7

    ============================================

    - 2/ Fortran Statements (continued) :

    The Fortran (77 or 90) Character Set should not be confused with

    that available to assign CHARACTER Variables, or Constants, or Text

    Strings in Output Statements, which on most systems includes Lower

    Case Letters, and several additional Punctuation Characters.

    This is called the Collating Sequence. PC and Unix systems use the

    A.S.C.I.I. (American Standard Code for Information Interchange),

    but Mainframes operate under E.B.C.D.I.C. which was arranged for

    easy handling of punched cards.

    Fortran places no constraints on Collating Sequences other than :

    Upper Case Letters must come in alphabetical order,

    though not forcibly in contiguous places in the sequence),

    Digits must come in Numerical order,

    and as a set, before or after the Upper Case Letters,

    the Blank (Space) must precede both the Letters and Digits.

    So overall, either :

    < 0 < 1 < ... < 9 < A < B < ... < Z,

    or

    < A < B < ... < Z < 0 < 1 < ... < 9.

    When included, the Lower Case Letters must also sit in Alphabetical

    order, and as a set, after the Blank (Space), and before or after

    the Digits. The Standards do not specify any relationships between

    Upper and Lower Case Letters.

    Fortran contains special operators for lexicographical comparisons

    of Character Strings, so these remain possible irrespective of the

    relationship of between Letters and other symbols in the Collating

    Sequence of any given system. See the later notes on Operators.

    15

  • Fortran Program and Code Structure - Part 8

    ============================================

    - 2/ Fortran Statements (continued) :

    Fortran 90 also introduced "Free Source Form", which was in effect

    made the standard in Fortran 2003. The format of 77 and earlier

    Source Code was then called "Fixed Source Form".

    Under Free Form coding, the Label, when present, and Statement may

    show anywhere along the Line, as long as at least a Space separates

    the eventual Label and the Statement. Only the Exclamation Mark

    Character remains valid to prefix a Comment, but may be typed any

    Column along the Line. In Free Form, Continuations are marked by

    an Ampersand (&) as the last non Blank or Comment Character in

    the Line. Up to 31 Continuations are permitted, excluding Blank

    and whole Comment Lines. Conversely, several Statements may share

    a Line, separated by Semi Colons.

    Fixed and Free Form coding may not coexist in the same Program.

    Examples of Fixed Form and Free Form Code Programs are given in

    the following pages. Note the minimal changes between the two forms.

    The alterations consist of using Exclamation Marks to initiate the

    Comments, appending Ampersands at the end of continued Lines, and

    removing the Continuation Marks in Column 6 of the Fortran 77 Code.

    The effects of the Various Statements will be explained in later

    pages, but the Comments should give an idea of the processing.

    Notice the use of spacing, between and within Statements, and the

    alignment of the Labels. In the (77) Fixed Form coding Example,

    the Comments all use a CCCC Prefix to better stand out.

    These notes will use "Traditional", Capitalised, Fixed Form coding

    for all examples and passages of Code, unless otherwise indicated.

    If desired, most well laid Fixed Form Source Files should be easy to

    convert to Free Form, while remaining easy to read. Utilities exist

    to automate part of the task.

    16

  • Fortran Program and Code Structure - Part 9

    ============================================

    - 3/ Fortran Fixed Form Code Example (clpent.for) :

    PROGRAM CLPENT

    CCCC PROGRAM COMPUTES PENTAGONAL NUMBER FOR INDEX ENTERED BY USER,CCCC AND NEXT 3 (PENTAGONAL FOR N = ( ( 3 N ** 2 - N ) / 2 ).CCCCCCCC PROGRAM CONFORMS TO A.N.S.I. 1978 FORTRAN 77 STANDARD.

    CCCC NON EXECUTABLE PART (DATA DECLARATIONS).

    CCCC INDEX, INPUT STATUS AND FOUR PENTAGONAL NUMBERS.

    INTEGER NPINDX, NPSTAT,1 NPENT1, NPENT2, NPENT3, NPENT4

    CCCC EXECUTABLE PART, REQUEST STARTING INDEX ENTRY.

    100 WRITE ( *, 1000 )1000 FORMAT ( /, Pentagonal Numbers, Enter Start Index : )

    READ ( *, 1001, ERR = 101, IOSTAT = NPSTAT ) NPINDX1001 FORMAT ( I80 )

    IF ( NPSTAT .NE. 0 ) THEN

    WRITE ( *, 1002 )1002 FORMAT ( /, Not an Integer. Try again )

    GOTO 100ENDIF

    CCCC COMPUTE PENTAGONAL NUMBERS FROM INDEX AND SHOW THEM.

    200 NPENT1 = ( ( 3 * NPINDX ** 2 - NPINDX ) / 2 )

    NPENT2 = ( NPENT1 + ( 3 * ( NPINDX ) ) + 1 )NPENT3 = ( NPENT2 + ( 3 * ( NPINDX + 1 ) ) + 1 )NPENT4 = ( NPENT3 + ( 3 * ( NPINDX + 2 ) ) + 1 )

    WRITE ( *, 2000 ) NPINDX,1 NPENT1, NPENT2, NPENT3, NPENT4

    2000 FORMAT ( /, Pentagonal Numbers from Index , I6, :, /,1 /, 4 ( I8, 1X ) )

    END

    17

  • Fortran Program and Code Structure - Part 10============================================

    - 4/ Fortran Free Form Code Example (clpent.f90) :

    PROGRAM CLPENT

    ! Program computes Pentagonal Number for Index given by User,! and next 3 (Pentagonal for N = ( ( 3 N ** 2 - N ) / 2 ).!! Program conforms to A.N.S.I. (I.S.O.) Fortran 90 Standard.

    ! Non Executable Part (Data declarations).

    ! Index, Input Status and 4 Pentagonal Numbers.

    INTEGER NPINDX, NPSTAT, &NPENT1, NPENT2, NPENT3, NPENT4

    ! Executable Part, request starting Index entry.

    100 WRITE ( *, 1000 )1000 FORMAT ( /, Pentagonal Numbers, Enter Start Index : )

    READ ( *, 1001, IOSTAT = NPSTAT ) NPINDX1001 FORMAT ( I80 )

    IF ( NPSTAT .NE. 0 ) THEN ! Test for Input Error.

    WRITE ( *, 1002 )1002 FORMAT ( /, Not an Integer. Try again )

    GOTO 100 ! Branch back for Index retry.ENDIF

    ! Compute Pentagonal Numbers from Index and show them.

    200 NPENT1 = ( ( 3 * NPINDX ** 2 - NPINDX ) / 2 )

    NPENT2 = ( NPENT1 + ( 3 * ( NPINDX ) ) + 1 )NPENT3 = ( NPENT2 + ( 3 * ( NPINDX + 1 ) ) + 1 )NPENT4 = ( NPENT3 + ( 3 * ( NPINDX + 2 ) ) + 1 )

    WRITE ( *, 2000 ) NPINDX, &NPENT1, NPENT2, NPENT3, NPENT4

    2000 FORMAT ( /, Pentagonal Numbers from Index , I6, :, /, &/, 4 ( I8, 1X ) )

    END

    18

  • Fortran Data Representation - Part 1=====================================

    - 1/ Introduction :

    This Chapter covers how data, numeric or otherwise, are representedin Fortran. The general form of declarations is explained, followedby a description of the Types available. Constants and allocationof Values are described, then Data initialisations. Finally, Themechanism to make data visible to multiple Program Units and sharestorage are explained. Data declaration and associated statementsconstitute the "Non Executable" part of a Fortran Program unit, andmust come before all Executable Statements in the Source Code.

    Whatever their nature, all referenced, aka Named, data in a FortranProgram or Subprogram are explicitly or implicitly declared. Theymust also feature a Type, for which defaults exist for implicitlydeclared Variables. These may be amended if desired. DeclarationStatements are also called "Type" Statements for they always providea Type for all Variables they introduce.

    Fortran 77 includes 6 (Intrinsic) Types : CHARACTER for text data,INTEGER, REAL, DOUBLE PRECISION and COMPLEX for Integer, FloatingPoint (Single and extended Precision) and Complex Numbers, andLOGICAL for On-Off (True or False) Switches.

    Constants may appear in some Fortran Statements, and be named viaa special form of declaration, the PARAMETER Statement. Variablesmay be given initial Values with DATA Statements, which allow thisto be carried out in bulk.

    Groups of Variables, explicitly of implicitly declared, may bemapped in a (single) region of storage (Memory) made available tomultiple Program Units (main Program and any number of Subprograms)in COMMON Blocks, defined in COMMON Statements. For initialisation,Variables in Common Blocks require BLOCK DATA Subprograms.

    Variables can share the same storage (Memory) area. The EQUIVALENCEstatement facilitate this, with some restrictions as the the Typesand other attributes of the Variables so related.

    In Fortran 90 Data Structures and Pointers are also supported.These are not covered in these notes which focus on Fortran 77.Fortran 90 also lifts some restrictions affecting PARAMETER, DATA,COMMON and EQUIVALENCE Statements in Fortran 77.

    19

  • Fortran Data Representation - Part 2=====================================

    - 2/ Basic Declaration Form :

    Type Keyword followed by one or more comma separated entity Names.So, for each intrinsic Type offered in Fortran, with leading Spaces,the Statements below show typical declarations :

    CHARACTER *14 CHS1, CHS2, CHS3CHARACTER CHVAR1, CHVAR2, CHVAR3

    INTEGER INVAR1, INVAR2, INVAR3

    LOGICAL LGVAR1

    REAL REVAR1, REVAR2, REVAR3

    COMPLEX PXVAR1, PXVAR2

    DOUBLE PRECISION DPVAR1, DPVAR2

    Note placing a comma as the last non blank character in a line doesnot alone mean the following Line is considered a continuation. Forthat, a Character will be needed in Column 6 of the next Line :

    CHARACTER CEXMP1,1 CEXMP2

    As an alternative, in Fortran 90 Free Form coding,an Ampersand should follow the comma at the end of the top Line :

    CHARACTER CEXMP1, &CEXMP2

    See more examples below where the Intrinsic Types are described.

    In Fortran 90, a ( KIND = ... ) qualifier, or ( ... ) Kind Valueand comma separated list of Attributes can follow the Type Keyword.KIND allows several Sizes, in terms of Memory Bytes for entities,or some other features, like Character Sets, or numeric ranges.

    Also in Fortran 90 a double colon (::) may split a Type Keywordand Attributes from the following list of Variable Names :

    CHARACTER :: CEXMP1, &CEXMP2

    20

  • Fortran Data Representation - Part 3=====================================

    - 3/ Entity (Variable) Names :

    Fortran 77 - At most 6 alphabetical or numeric Characters,beginning with a letter.

    Upper and Lower Case letters same in Names,so for example, Vrnm01 and VRNM01 bothrefer to the same Variable.

    Many implementations will allow "Long Names",for example up to 31 Characters as in Fortran 90.

    - Note Variables need not be explicitly declared,so Names may first show in Executable Statements.See notes about implicit Variable Types below.

    Implicitly declared Variables allowed fewerStatements in Programs, so less Punched Cards,or smaller Source Code Files for Compilers,but made detection of (typing) errors harder.

    All Variables should now be explicitly declared.

    - Avoid single letter Variable Names,as they can make Variable instances hard to find,for example in Editors, and typing errors couldmore easily slip through undetected.

    - Also avoid Names which clash with Keywords,Intrinsic Functions or other Fortran attributes.

    Fortran 90 - Same as Fortran 77 apart :

    - Entity Names up to 31 Characters allowed,which can also include digits and Underscores.

    Many Fortran 77 compilers allowed "Long Names",though not necessarily limited at 31 Characters.

    - Implicit Types match those found in Fortran 77,but can be invalidated with IMPLICIT NONE,then with no other IMPLICIT Statements allowed.

    21

  • Fortran Data Representation - Part 4=====================================

    - 4/ Basic (Intrinsic) Types :

    CHARACTER - Character String, from 1 to 32,767 Characters,containing any of the Characters present in theCollating Sequence, the full set of possibleCharacters known to the computer system.

    - By default, single Byte length (one character),but eventually given an Integer Length, say NN,with a * NN or * ( NN ) default Prefix, or,for each Variable, Suffix. For example :

    CHARACTER*12 C1, C2, C3

    CHARACTER * 12 C1, C2, C3

    CHARACTER C1*12,1 C2*12,1 C3*12

    CHARACTER C1 * 12,1 C2 * 12,1 C3 * 12

    all Define three 12 Byte Character Strings,named C1, C2, C3. Overrides allowedfor a defaulted Length like :

    CHARACTER * 12 C1, C2, C3 * 10

    CHARACTER C1 * 12,1 C2 * 12,1 C3 * 10

    CHARACTER *(4) CA, CB*1, CC, CD*2

    define 12 Byte Character Strings by default,with an override to Length 10 for the last, C3,then 4 Byte Variables apart from CB and CD.

    - Lengths cannot be Zero or Negative and anysuch Lengths should cause compilation failure.

    22

  • Fortran Data Representation - Part 5=====================================

    - 4/ Basic (Intrinsic) Types (continued) :

    CHARACTER (Cont.) - When Variable a Dummy Variable in a Subprogram,or a Named Constant set in a PARAMETER Statement,Length Value may be "assumed" from actual Data.This is indicated with an Asterisk :

    CHARACTER * (*) CHARG1, CHARG2, CHARG3

    CHARACTER * (*) CHPARM

    For Subprograms, this means length of actualpassed Variable. See later notes on Subprograms.

    For Named Constants, aka Parameters, this meanslength of actual String assigned to Parameter.See later notes on (Named) Constants.

    - In Fortran 90, ( LEN = NN ) or just ( NN )may be used to specify Default Lengths. Then,first example above could be any of :

    CHARACTER ( 12 ) C1, C2, C3

    CHARACTER ( LEN = 12 ) C1, C2, C3

    CHARACTER ( LEN = 12 ) :: C1, C2, C3

    CHARACTER ( LEN = 12 ) :: C1, &C2, &C3

    but next example above requires two Statements :

    CHARACTER ( LEN = 12 ) C1, C2

    CHARACTER ( LEN = 10 ) C3

    23

  • Fortran Data Representation - Part 6=====================================

    - 4/ Basic (Intrinsic) Types (continued) :

    INTEGER - Integer entity.

    - Example : to declare Integers I1, I2, I3,

    INTEGER I1, I2, I3

    - Usually 4 Bytes (32 Binary Bits),so Max. Absolute Value ( 2 to Power 31 ) - 1,thus Range -2,147,483,647 to +2,147,483,647.

    - In some implementations, INTEGER*2 and INTEGER*4allowed to specify 2 or 4 Byte Integers.Two Byte Integers limit absolute Value to 32,767.

    LOGICAL - On or Off Switch,with Value .TRUE. or .FALSE..

    - Example : to declare Variables LG1, LG2,

    LOGICAL XC1, XC2

    - May be used as Conditional on its own,without Conditional Operator (see later).

    - Note despite their On-Off nature,LOGICAL Variables usually occupy full Bytes,Bytes being the lowest level (amount of) Memoryaddressable in machine (Assembler) Instructions.

    So the benefit of LOGICAL Variables lies in thembeing a Condition in their own right, and notin economy of storage compared to other Types.Length 1 CHARACTER Variables also take one Byte.

    24

  • Fortran Data Representation - Part 7=====================================

    - 4/ Basic (Intrinsic) Types (continued) :

    REAL - "Single Precision" Floating Point entity.

    - Usually 4 Bytes (32 Binary Bits) in IEEE format,with Sign, 8 Bit Exponent and 23 Bit Mantissa.

    Thus Binary Exponent Ranges from -127 to +128,corresponding to a Base 10 Range of about 10-38to 10+38. The 23 Bit Mantissa equates to decimalaccuracy of 7 to 8 Digits.

    - Fortran 90 implementations must support at least2 Real Kinds, so extended entities may act as analternative to the DOUBLE PRECISION Type.

    DOUBLE PRECISION - Extended Floating Point entity,allocated twice as much Memory as a REAL entity.

    - Usually 8 Bytes (64 Binary Bits) in IEEE format,with Sign, 11 Bit Exponent and 52 Bit Mantissa.

    Thus Binary Exponent Ranges from -1021 to +1024,corresponding to a Base 10 Range of about 10-308to 10+308. The 52 Bit Mantissa equates to decimalaccuracy of 15 to 16 Digits.

    - Example : to declare Variables D1, D2, D3,

    DOUBLE PRECISION D1, D2, D3

    - In modern applications, all real arithmeticshould be carried out in DOUBLE PRECISION,to reduce numerical drift and other errors.

    - In Fortran 90, an equivalent to DOUBLE PRECISIONVariables may be implemented via the second Kindof REAL Variable a system should offer.

    25

  • Fortran Data Representation - Part 8=====================================

    - 4/ Basic (Intrinsic) Types (continued) :

    COMPLEX - Twin REAL entity, with Real and Imaginary Parts,each a REAL, obeying laws of Complex arithmetic,that is, Real Part behaves like such a number,while squared Imaginary Unit become minus one.

    - Example : to declare Variables XC1, XC2,

    COMPLEX XC1, XC2

    - Fortran 90 implementations must support at least2 Kinds, to allow DOUBLE PRECISION sized entities,for both (Real and Imaginary) Parts.

    26

  • Fortran Data Representation - Part 9=====================================

    - 5/ Implicit and Explicit Data Types :

    By default, declaring Variable in Type Statements not requiredbefore using them in other Statements, including Executable ones.Implicit Types are used for such undeclared Variables.

    By default, Variables not explicitly declared are Integers,for Names beginning with any of the Letters from I to N,and (Single Precision) Real numbers for all others.

    Implicit typing my be overridden with IMPLICIT Statements,to associate one or more starting letter ranges with a Type.

    Each IMPLICIT Statement may cover one or more Types :

    IMPLICIT COMPLEX ( A-B )

    IMPLICIT CHARACTER ( C ),1 LOGICAL ( L )

    IMPLICIT INTEGER ( I-K )

    IMPLICIT DOUBLE PRECISION ( D,E, P-Z )

    Many Fortran 77 implementations and compilers allow NONE,as an Attribute to IMPLICIT, forcing all Variables to be declared.When IMPLICIT NONE used, no other IMPLICIT Statements permitted.This became a Standard feature in Fortran 90.

    For strictly conforming 77 Code, use IMPLICIT CHARACTER ( A-Z ),to force declaring all entities found in assignments or arithmetic,as CHARACTER Values need enclosing Quotes, which will not be validin any form of numerical Expression or Assignment.

    In Fortran 90 Implicit Types match those found in Fortran 77,but can be invalidated with an IMPLICIT NONE, in which case noother IMPLICIT Statements are allowed.

    When available, use of IMPLICIT NONE is recommended.

    27

  • Fortran Data Representation - Part 10=====================================

    - 6/ Basic (Intrinsic) Type Constants :

    Data Values may be used as Constants, to assign Variables,either directly, or in Expressions involving several entities.Constants may also show in Expressions used in Conditionals.

    For each Intrinsic Data Type, constants are written as follows :

    CHARACTER - Enclose actual text String in Single Quotes,and for every Quote to form part of String,code 2 Quotes, distinct from end quotes.Effectively, delimiters not part of Data.

    - CHARACTER Constants cannot be Zero Length,so illegal, and Data over 32,767 Characterstruncated to that length.

    - Examples :

    Data_String for Data_String,01234567 for the Digits 0 to 7,OBrien for OBrien, for one Single Quote.

    - In Fortran 90, Double Quotes delimiters allowed,Single Quotes then being ordinary characters,and vice versa when Single Quotes delimit data.

    Above Examples would alternatively become :

    "Data_String" for Data_String,"01234567" for the Digits 0 to 7,"OBrien" for OBrien,"" for one Single Quote.

    28

  • Fortran Data Representation - Part 11=====================================

    - 6/ Basic (Intrinsic) Type Constants (continued) :

    INTEGER - Digits in Value with optional Arithmetic Sign,always showing at left and without separation.

    - Leading Zeros may show without effect, butDecimal Points, commas and Exponents illegal.

    - Constants are assumed positive when not signed.Signs ignored when Constant Value Zero,

    - Constants over maximum allowed Absolute Valueillegal and should cause compilation to fail.

    - Examples :

    -345+327670034

    - illegal Examples :

    -345.0 (Decimal Point)+32,767 (comma in Field)

    -214748648 (exceeds Max. Absolute Value)

    LOGICAL - May only take Values "True" and "False",written between full stops (as all otherLogical Operators must be in Fortran 77) :

    .TRUE.

    .FALSE.

    29

  • Fortran Data Representation - Part 12=====================================

    - 6/ Basic (Intrinsic) Type Constants (continued) :

    REAL - Digits in Value with optional Arithmetic Sign,Decimal Point, Decimals (following Point),and (Base 10) Exponent, with optional Sign.

    - When present, Arithmetic Sign must show at left,and without separation, while Exponent Codedto right, with E Prefix, and following Sign,then Exponent Absolute Value, without spaces.

    - Leading Zeros may show without effect,including in Exponent, unless that makes Fieldlonger than allowed (2 Digits).

    - Constants and Exponents assumed positivewhen not signed. Signs ignored with Zero Values.

    - When more Digits than can be represented,(in 4 Bytes) right side truncated and rounded.

    - Constants over maximum allowed Absolute Value,that is, with Exponent Absolute Value too large,illegal and should cause compilation to fail.

    For REAL Type Constants, Max. Exponent 38.

    - Examples :

    -345 (effectively 345.0)+32767 ( " 32,767.0)0034.00.0

    12E2 (1200.0, like other writings below)12.E212E+02

    +12.0E+021.20E3

    +0.120E+4

    30

  • Fortran Data Representation - Part 13=====================================

    - 6/ Basic (Intrinsic) Type Constants (continued) :

    DOUBLE PRECISION - Same as for REAL Constants above,except that Exponent must be written as D,rather than E, assumed when no Exponent.

    - For DOUBLE PRECISION Type Constants,Maximum Exponent Absolute Value 308.

    - Examples, matching above REAL cases :

    -345D0 (effectively 345.0)+32767D0 ( " 32,767.0)3.4D10.0D0

    COMPLEX - COMPLEX Constants consist of Real and Imaginary(Single Precision) REAL Values, in parentheses,and with a comma Separator.

    - Examples :

    (3.0,2.1)

    ( 3.0E0, 2.1E0 ) (note same as above)

    ( -0.31E-3, +7.50E+2 )

    31

  • Fortran Data Representation - Part 14=====================================

    - 7/ Declared (Named) Constants :

    Variables of any Type may be used to hold Constant Values,specified via PARAMETER Statements, effectively naming Constants.

    Each PARAMETER Statement presents a bracketed list of Name = Value(Constant) Parameter assignments, separated by commas, for example :

    CHARACTER * 12 CFILE1

    INTEGER IFILE1

    PARAMETER ( CFILE1 = ProgInpt.dat, IFILE1 = 8 )

    Assumed Length CHARACTER Constants allowed, for example :

    CHARACTER CFILE1 * (*)

    would be valid for the above PARAMETER Statement, with the Lengthof the Constant CFILE1 then defined by the count of Characters inthe String assigned to it, here 12 Characters.

    Arithmetic Expressions are allowed as long as all Values known,and exponentiation (** Operator) limited to Integer powers, so :

    INTEGER IEX1

    DOUBLE PRECISION XARG01,1 XARG02,1 XARG03

    PARAMETER ( IEX1 = 3, XARG01 = 3.14159D0,1 XARG02 = 3.14159D0 ** 3,1 XARG03 = ( XARG01 + XARG02 ) )

    Assignments being left to right, in the example above,all Values available at time each Parameter Value assigned.

    Intrinsic Functions CHAR, ICHAR, and LEN are likewise allowed,when associated with already declared CHARACTER Variables.

    32

  • Fortran Data Representation - Part 15=====================================

    - 7/ Declared (Named) Constants (continued) :

    When Values provided in Parameter assignments disagree withcorresponding Variable Types, either forced conversion happens,as would between INTEGER, REAL and DOUBLE PRECISION Types,or the Statement becomes illegal. So, these are allowed :

    INTEGER IPR1

    PARAMETER ( IPR1 = 10.5 )

    REAL RPR2

    DOUBLE PRECISION DPR3

    PARAMETER ( RPR2 = 12, DPR3 = 11.2 )

    In the first case above, IPR1 takes the Integer Value 10,In the second case, RPR2 becomes 12.0, and DPR3 11.2D0.

    When CHARACTER Parameters are assigned Strings of differentLength to that declared, shorter Strings get Blank padded,while longer Strings get truncated, so for example :

    CHARACTER * 12 CHP1, CHP2

    PARAMETER ( CHP1 = Test, CHP2 = Test long String )

    result in CHP1 being assigned Test (8 trailing Blanks),and CHP2 being truncated to Test long St (so ring cut off).

    Note Implicit naming conventions apply to Parameters, and also,later IMPLICIT Statements cannot contradict Types for Parameters.

    PARAMETER ( ICHL = 12 )

    IMPLICIT CHARACTER *7 ( I-J )

    would be invalid because later IMPLICIT would imply Type CHARACTERfor the undeclared ICHL, by default, at that time, an Integer.

    33

  • Fortran Data Representation - Part 16=====================================

    - 8/ Variable Initialisations :

    Variables may be given initial Values via DATA Statements.These take effect once, before Execution begins, so for Subprograms,will not apply beyond the first occasion the Subprogram is called.

    DATA Statements contain a List of comma separated Variable Names,and then, in between slashes, a list of Values for those Variables :

    CHARACTER * 6 CHD1, CHD2

    DATA CHD1, CHD2 / Test01, Test02 /

    INTEGER IDT1, IDT2, IDT3,1 IDT4, IDT5, IDT6

    DATA IDT1, IDT2, IDT3 / 10, 10, 10 /DATA IDT4, IDT5, IDT6 / 10, 11, 12 /

    REAL RDT1DOUBLE PRECISION DDT2

    DATA RDT1, DDT2 / 20.0, 24.0D0 /

    When the Values given disagree with the appropriate Variable Types,conversion happens between INTEGER, REAL and DOUBLE PRECISION Types,or the Statement becomes illegal. For example :

    INTEGER IPR1

    REAL RPR2

    DOUBLE PRECISION DPR3

    DATA IPR1 / 10.5 /

    DATA RPR2, DPR3 / 12, 11.2 /

    In the first case above, IPR1 takes the Integer Value 10,In the second case, RPR2 becomes 12.0, and DPR3 11.2D0.

    34

  • Fortran Data Representation - Part 17=====================================

    - 8/ Variable Initialisations (continued) :

    When CHARACTER Variables are assigned Strings of different Lengthto that declared, as is the case for Parameters (see above),shorter Strings get Blank padded and longer ones truncated, so :

    CHARACTER * 12 CHS1, CHS2

    DATA CHS1, CHS2 / Test, Test long String /

    result in CHS1 being assigned Test (8 trailing Blanks),and CHS2 being truncated to Test long St (so ring cut off).

    Note that unlike CHARACTER Parameters, ordinary CHARACTER Variablescannot be declared with unspecified Length (CHARACTER * ( * ),assigned a Value in a DATA Statement, and take their Length off it.

    CHARACTER entities may be partially initialised by adding a Range,in parentheses after their Names, giving ( FROM : TO ) Substrings,both FROM and TO being Integers.

    For any CHARACTER Substring, the "From" Byte must equal or exceed 1,and "To" may at most equal the base Variable Length. Either or bothmay be defaulted, in which case 1 or the Variable Length are used.Positions following a Substring will be set to Blank, so in effectonly the the "From" value matters. So ( : ) or ( 1 : ) as Rangesequate to the whole Variable.

    Examples of CHARACTER Substring DATA Statements :

    CHARACTER * 12 CHS1, CHS2

    DATA CHS1 ( 5 : 7 ), CHS1 ( 3 : )1 / xx , 123456789 /

    initialise Bytes 5 and 6 of CHS1 to x, with Bytes 7 to 12 Blank,and Bytes 3 to 11 of CHS2 to the String given, and Byte 12 Blank.In both cases leading Bytes before the Substring remain unassigned.

    35

  • Fortran Data Representation - Part 18=====================================

    - 8/ Variable Initialisations (continued) :

    Successive sets of Variable Names and Values may be merged,or DATA Statements with comma separators in one DATA Statement,so the initial DATA example above could be written as :

    DATA IDT1, IDT2, IDT3, IDT41 / 10 , 10 , 10 , 10 /1 IDT5, IDT6, RDT1, DDT21 / 11 , 12 , 20.0, 24.0D0 /

    Repeated Values may be replaced by a Multiplier and a single Value,with the Asterisk (*) symbol between them. The top 2 Lines abovecould for example be written as :

    DATA IDT1, IDT2, IDT3, IDT4 / 4 * 10 /

    or, with CHARACTER Type Variables :

    DATA CHS1, CHS2 / 2 * Test /

    For arrays, a special form of DO Loop called "Implied DO Loop"may also be used in DATA Statements. See later coverage of Arrays.

    In Fortran 90, as an alternative to using DATA Statements,Variables can be initialised in their Type declaration Statement,with Values following the corresponding Names after an Equal Sign :

    CHARACTER ( 6 ) CHD1 = Test01, CHD2 = Test02

    INTEGER IDT1 = 10, IDT2 = 10, IDT3 = 10, IDT4 = 10INTEGER IDT5 = 11, IDT6 = 12

    REAL RDT1 = 20.0DOUBLE PRECISION DDT2 = 24.0D0

    could replace the first set of DATA examples above.

    36

  • Fortran Data Representation - Part 19=====================================

    - 9/ Common Blocks :

    Blocks of storage (Memory) may be accessed by several Program Units,be they a Program and some of its Subprograms, or just the latter.Such structures are called Common Blocks.

    The Variables in a Common Block are listed in one or more COMMONStatements. Common Blocks may be Blank or Named. For the latter, aName, surrounded by Slashes, precedes the comma separated Variables.Several Blocks may be declared per COMMON Statement, optionallyseparated by commas, for example :

    INTEGER IDC1, IDC2, IDC3,1 IDC4, IDC5, IDC6

    DOUBLE PRECISION DDC1, DDC2, DDC3,1 DDC4, DDC5, DDC6

    COMMON IDC1, IDC2, IDC3,1 DDC1, DDC2, DDC3

    COMMON / COM1 / IDC4, IDC5, IDC6,1 / COM2 / DDC4, DDC5, DDC6

    declare a Blank Common, then the Named Common Blocks COM1, COM2in a Single Statement, with the optional comma Separator in between.

    Two consecutive Slashes may also specify Blank Common. Common Namesmust not clash with Program Unit or Intrinsic Function Names, but ifone (Common) Name appears in multiple COMMON Statements, the secondand later Statements merely add to the earlier set of Variables. TheBlank Common above could have been coded :

    COMMON / / IDC1, IDC2, IDC3

    ...

    COMMON / / DDC1, DDC2, DDC3

    Mismatched Numeric data Types as well as Arrays and lone entitiesmay be involved, but CHARACTER or LOGICAL Variables may not be mixedwith other Types. Also, any Variable may appear in only one COMMONStatement, or Block, in any Program Unit.

    37

  • Fortran Data Representation - Part 20=====================================

    - 9/ Common Blocks (continued) :

    When Blank Common is used in multiple Program Units, the list ofVariables need not include the whole set of Variables in the Block,and as long as any Type mismatches remain valid, that list may vary.For example, one CHARACTER Variable could become two :

    Program Unit A :

    CHARACTER * 24 CHCO

    COMMON / / CHCO

    Program Unit B :

    CHARACTER * 12 CHC1, CHC2

    COMMON / / CHC1, CHC2

    For Named Common Blocks, all Variables must be listed in all ProgramUnits where the Block features (in effect implying the same length iskept at all times).

    Variables used as (passed or received) Arguments in Subprograms maynot belong to any Common Blocks. Also, Common Block Variables cannotbe initialised in DATA Statements, but need BLOCK DATA Subprograms.See 11/ below for BLOCK DATA Subprograms.

    38

  • Fortran Data Representation - Part 21=====================================

    - 9/ Common Blocks (continued) :

    Common Blocks allow sets of Variables to remain in proximity to eachother in Memory, and can save overheads when Subprograms are called.This can facilitate efficient Memory access.

    It is advisable to list all the Variables in Common Blocks in oneCOMMON Statement, and the sequence of Names should be the same in allProgram Units where the Block features. For Blank Common, Variablesshould all be listed.

    Fortran 90 relaxes the restriction that Numeric and Non NumericVariables cannot be entered in the same Common Blocks, but stillimposes that 32 Bit Numeric Variables must occupy a full MemoryWord, starting on a multiple of 4 Address, and 64 Bit Variables(DOUBLE PRECISION and COMPLEX) must take a Double Word, with anAddress on a multiple of 8 Bytes.

    39

  • Fortran Data Representation - Part 22=====================================

    - 10/ Overlays (Equivalences) :

    Variables can be forced to share the same storage space (Memory),with EQUIVALENCE Statements, in effect a superimposition of Memorymappings with joint reference points given by the Statements.

    Mismatched Numeric data Types as well as Arrays and lone entitiesmay be involved, but CHARACTER or LOGICAL Variables may not bemixed with other Types. Association of single CHARACTER Variablesand Arrays are allowed. See later coverage regarding Arrays.

    Each Equivalence encompasses 2 or more Variables, with their commaseparated Names listed between parentheses. An EQUIVALENCE Statementcan include several lists each separated by a comma. For example,featuring various Numeric data Types :

    INTEGER IEA1, IEA2, IEA3, IEA4COMPLEX XEQ1REAL REQ1, REQ2DOUBLE PRECISION DPE1, DPE2, DPE3

    EQUIVALENCE ( IEA1, IEA2 )

    EQUIVALENCE ( IEA3, REQ1, DPE1 )

    EQUIVALENCE ( XEQ1, DPE2 ), ( DPE3, REQ2 )

    In terms of Memory Mappings, using = to mark jointly used storageand | at 4 Byte (Memory Word) boundaries, these examples produce :

    |====| 4 Bytes for IEA1|====| 4 " " IEA2 at the same location as IEA2

    |====| 4 Bytes for IEA3|====| 4 " " REQ1, first 4 Shared with IEA3, DPE1|====|----| 8 " " DPE1, " 4 " " IEA3, REQ1

    |====|====| 8 Bytes for XEQ1 (4 for each Part of Complex)|====|====| 8 " " DPE2, shared with XEQ1 Complex Number

    |====|----| 8 Bytes for DPE3|====| 4 " " REQ2, shared with first 4 of DPE3

    40

  • Fortran Data Representation - Part 23=====================================

    - 10/ Overlays (Equivalences) (continued) :

    Note much as Variables are often mapped in Memory in the order theyare declared, this is not required. So, it must not be assumed thatany Variables not explicitly mentioned in EQUIVALENCE lists overlap.In the last example above, the Integer IEA4 will not lay over thetrailing 4 Bytes of DPE1. The one exception to this happens withArrays as these, for Equivalence purposes become single objects. Seethe later notes explaining Arrays.

    Also, as no conversion whatsoever takes place when mismatched Typesappear in EQUIVALENCE Lists, any assignments to one entity in a Listwill not produce the same Value in the others, apart from the onecase of REAL and COMPLEX as each Part of the COMPLEX constitutes aREAL Variable. Using the List ( IEA3, REQ1, DPE1 ) above, with theDecimal Value 49,153 in the Integer IEA3 yields the Bit Map :

    00000000 00000000 11000000 00000001 = 49153

    With either the Sign, 8 Exponent and 23 Mantissa Bits of a REAL, orthe Sign, 11 Exponent and 52 Mantissa Bits of a DOUBLE PRECISION,the Bits making the Integer Value at that Memory location (Address)produce very small, but different, Floating Point Values.

    With CHARACTER Variables, Equivalence (storage overlap) may be setagainst Substrings of the Variables, but the whole storage mappingswill thus become partly of fully overlapped, beyond any Substringsin the actual EQUIVALENCE Statement. For example :

    CHARACTER * 20 CEQ1, CEQ2, CEQ3 * 10, CEQ4

    EQUIVALENCE ( CEQ1 ( 4 : 6 ), CEQ2 )

    EQUIVALENCE ( CEQ3, CEQ4 ( 9 : )

    would give actual storage (Memory) mappings :

    |---=================| CEQ1 Memory|=================---| CEQ2 "

    |==========| CEQ3 Memory|--------==========--| CEQ4 "

    41

  • Fortran Data Representation - Part 24=====================================

    - 10/ Overlays (Equivalences) (continued) :

    One but not both of the pair of Variables in an Equivalence maybelong to a COMMON Block, and at least one must remain outside anyCOMMON Blocks. For example :

    Fortran 90 relaxes the restriction that Numeric and Non NumericVariables cannot be entered in EQUIVALENCE Statements, but stillimposes that 32 Bit Numeric Variables must occupy a full MemoryWord, starting on a multiple of 4 Address, and 64 Bit Variables(DOUBLE PRECISION and COMPLEX) must take a Double Word, with anAddress on a multiple of 8 Bytes.

    Equivalence was useful on hardware with limited Memory, in thatit allowed Programs to invoke more Variables without consumingadditional Memory to hold them, or (see later coverage) overlayArrays of different structure on the same Memory space. Latercomputer systems usually contain enough Memory, so EQUIVALENCElooses its main justification, while Fortran 90 offers obviousways to rearrange Arrays (see later notes).

    42

  • Fortran Data Representation - Part 25=====================================

    - 11/ Common Block Data Initialisations :

    Any Variable listed in a Common Block may only be initialised in aBLOCK DATA Subprogram, and not elsewhere. One Blank BLOCK DATASubprogram is allowed, and any number of Named ones, of which theNames cannot clash with other Subprogram or COMMON Names.

    BLOCK DATA Subprograms begin with a BLOCK DATA Statement, possiblygiving the Subprogram a Name, and finish with an END Statement. Inbetween them, any Common Blocks may appear, at they would in otherProgram Units, with the same constraint that all Variables in NamedCommon Blocks must be listed.

    However, DATA Statements to initialise part or all of the (Common)Variables are allowed, while not permitted in other sorts of ProgramUnit. BLOCK DATA Subprograms may not declare or use Variables not ina Common Block, and cannot contain Executable Statements.

    Example Blank BLOCK DATA Subprogram :

    BLOCK DATA

    INTEGER IDT1, IDT2, IDT3, IDT4COMMON / / IDT1, IDT2, IDT3, IDT4

    DATA IDT1, IDT2, IDT3, IDT4 / 4 * 10 /

    END

    Example Named BLOCK DATA Subprogram :

    BLOCK DATA BKDT01

    DOUBLE PRECISION DDA1, DDA2, DDA3, DDA4DOUBLE PRECISION DDT1, DDB2, DDB3, DDB4

    COMMON / CDT1 / DDA1, DDA2, DDA3, DDA4COMMON / CDT2 / DDB1, DDB2, DDB3, DDB4

    DATA DDA1, DDA2 / 2 * 10.5D0 /DATA DDB1, DDB2 / 2 * 12.5D0 /

    END

    43

  • Fortran Assignments and Operations - Part 1============================================

    - 1/ Introduction :

    Assignments represent the mechanism, via the Equal Sign Operator,to give a (Target) Variable a new Value which may arise from someother Variable, a Constant, or an expression.

    In Expressions, one or more Values, called Operands, are merged viaeventual Operators or Function Calls. The Values may be those of anyVariables (including the Targets initial contents), or Constants,either implemented in PARAMETER Statements, or given in line as partof the Expression itself.

    Functions represent a sort of Subprogram returning a single Valuefrom any number of passed Arguments. Functions may be Intrinsic,built into Fortran and available to any Program, or specific. Thelatter can be provided as additional Source Code at compilation, orin Binary form via Libraries made known to the Compiler. Functionswill be treated in a following part of these notes.

    Items involved in Expressions, must be of consistent Type, thoughsome Type mismatches are tolerated with Numerical data, which willbe converted to the appropriate Type. Operations take place left toright, but in a hierarchical manner. This can be overridden withParentheses. The Operators available differ for Numeric, LOGICALand CHARACTER data. LOGICAL Expressions may serve as Conditionalsin Flow Control Statements. This is covered later in these notes.

    In Fortran 90, whole Arrays or parts of them may be treated as asingle entity in assignments or Expressions. See the later chapteron Arrays. Also, Fortran 90 introduces a new form of Assignment forPointer Variables. This will not be covered in these notes. Last,many new Intrinsic Functions were added in Fortran 90.

    44

  • Fortran Assignments and Operations - Part 2============================================

    - 2/ Basic Assignment Form :

    Fortran Assignments obey the syntax "Target = Value". The Targetmust be a Variable, explicitly declared in the Non Executable Part,or implicitly declared by appearing in Executable Part Statements.

    The initial content of the Target may form part of the Value. Theyare lost with no possibility of retrieval after the assignment. Ineffect the area in Memory where the Target resides is overwritten.

    The Equal (Sign) Operator (=) is required to effect assignments,with the Target always the Left Hand Side. The assigned Value may bethat of a Constant, another Variable, or an expression. In Fortran,no data on the Right hand side of an assignment can change.

    The Value may be absolute, or an Expression, involving one or moreOperands and Operators such that a single Value is produced by theevaluation of the Expression. See the rules affecting Expressionsin the following pages.

    Also, the Value in an assignment must be of the same Type as theTarget. In line Constants must obey the rules for their Type. Whennot, conversions are eventually forced for Numeric Types, whichcan entail loss of accuracy, or compilation errors arise. Data inCHARACTER Variables can be assigned to Numeric Fields but only viaREAD Input Statements. Likewise, WRITE Output Statements are neededto send Numeric Values to CHARACTER strings. These are not taken asConversions, and are treated in a later chapter of these notes.

    So, in effect only mismatches between Numeric Types are toleratedin assignments and can be resolved at compilation time. For goodpractice, all conversions should be made explicit in the Code.

    45

  • Fortran Assignments and Operations - Part 3============================================

    - 2/ Basic Assignment Form (continued) :

    Basic assignment examples (not involving composite Expressions) :

    CHARACTER * 12 CVR1, CVR2, CVR3, CVR4

    INTEGER INV1, INV2

    REAL RLV1, RLV2, RLV3

    DOUBLE PRECISION DPV1, DPV2, DPV3

    CVR1 = Data_StringCVR2 = 01234567CVR3 =

    INV1 = 10INV1 = -8

    RLV1 = 10.0RLV2 = 0.8E-02RLV3 = RLV2

    DPV1 = 120.0D0DPV2 = 1200.0D0DPV3 = DPV2

    all these assignments feature matched data Types (in most casesinvolving an in line Constant as the Value) across the Equal Sign.

    46

  • Fortran Assignments and Operations - Part 4============================================

    - 2/ Basic Assignment Form (continued) :

    Using the same Variables as in the previous examples, all these :

    DPV1 = 120DPV2 = 1200.0DPV3 = RLV3

    RLV1 = 10RLV2 = 8E-03RLV3 = DPV1

    INV1 = 10.5INV2 = RLV2

    exhibit Constants improperly written for the Target Type, or forceType Conversions. In the Floating Point to Integer cases, Decimalsare dropped, so INV1 would become 10, and INV2 Zero. The toptwo REAL and DOUBLE PRECISION assignments will be rearranged as ifwritten with one digit left of the Decimal Point and an exponent.

    Note the first pair of DOUBLE PRECISION assignments risks loss ofaccuracy. The Constants might be saved as REAL, and then converted.Good compilers should avoid this, but the last DOUBLE PRECISION andREAL assignments imply Type Conversions. The Code could explicitlyshow such Conversions, at no computational cost, for clarity :

    DPV3 = DBLE ( RLV3 )RLV3 = REAL ( DPV3 )

    and for the INV2 = RLV2 Integer case :

    INV2 = INT ( RLV2 )

    As shown above, the INT, REAL and DBLE Functions carry outconversion of their (Numeric) Argument to Integer, REAL and DOUBLEPRECISION. They should be used whenever that actually happens.

    When a Numeric Variable receives a Value in excess of the Maximumallowed, either a compilation error should arise or, if this cannotbe seen then, an "Execution Time" (or "Run Time") error should haltexecution. This may happen with Floating Point to Integer, or DOUBLEPRECISION to REAL or COMPLEX, for the latter, because of the fewerExponent Bytes provided in REAL or COMPLEX Fields.

    47

  • Fortran Assignments and Operations - Part 5============================================

    - 3/ Basic Assignment with COMPLEX Variables :

    Unless assigned from another COMPLEX Variable, Values for COMPLEXVariables should be a comma separated pair of REAL Variables or inLine Constants. Each item in the pair should meet the criteria forREAL assignments above. For example :

    COMPLEX CXV1, CXV2,1 CXV3, CXV4

    REAL RLV1, RLV2, RLV3

    RLV1 = -2.2E-2RLV1 = +0.05

    CXV1 = ( 12.4, 28.6 )CXV2 = ( RLV1, RLV2 )

    CXV3 = CXV1CXV4 = ( RLV1, -3.0 )

    make up valid COMPLEX Variable assignments, where either anotherCOMPLEX or two REAL Variables are involved. With one or both Partsof a Value INTEGER or DOUBLE PRECISION, the above rules for INTEGERor DOUBLE PRECISION to REAL assignments apply. The examples belowboth imply conversion to REAL or the DOUBLE PRECISION Real Partand INTEGER Imaginary Part :

    COMPLEX CXV1, CXV2

    DOUBLE PRECISION DPV1INTEGER INV1, INV2

    DPV1 = 120.0D0INV1 = -300

    CXV1 = ( DPV1 , INV1 )CXV2 = ( 120.0D0, -300 )

    The examples would be more clearly coded as :

    CXV1 = ( REAL ( DPV1 ), REAL ( INV1 ) )CXV2 = ( 120.0, -300.0 )

    48

  • Fortran Assignments and Operations - Part 6============================================

    - 3/ Basic Assignment with COMPLEX Variables (continued) :

    Non COMPLEX Numerical Variables can be assigned COMPLEX Values. Ifno conversion is explicitly specified, the Imaginary Part is lostand the Real Part possibly converted to INTEGER or DOUBLE PRECISION.

    Conversely, COMPLEX Variables may actually be assigned atomicValues of other Numeric Types, in which case the Imaginary Part isset to Zero (0.0). In both instances of COMPLEX and other NumericType mismatches across the Equal Sign, coding conversion Functionscan make the Code easier to follow :

    CXV1 = DPV1CXV2 = INV1

    RLV2 = CXV3INV2 = CXV4

    would be more clearly coded as :

    CXV1 = ( DPV1, 0.0 )CXV2 = ( INV1, 0.0 )

    RLV2 = REAL ( CXV3 )INV2 = INT ( REAL ( CXV4 ) )

    For completeness, and clarity, the CMPLX conversion Function couldbe coded. It accepts one or two Arguments, standing for the Real andImaginary Parts of the resulting COMPLEX Value respectively. forexample, the first pair of assignments above could be written :

    CXV1 = CMPLX ( DPV1 )CXV2 = CMPLX ( INV1 )

    or more clearly :

    CXV1 = CMPLX ( REAL ( DPV1 ), 0.0 )CXV2 = CMPLX ( REAL ( INV1 ), 0.0 )

    Non Numeric Types cannot be mixed with COMPLEX Variables.

    49

  • Fortran Assignments and Operations - Part 7============================================

    - 3/ Basic Assignment with COMPLEX Variables (continued) :

    Were the Imaginary Part of a COMPLEX Variable to be assigned to anatomic Numerical Variable, the AIMAG Function would be required.The above RLV2 and INV2 assignments would become :

    RLV2 = AIMAG ( CXV3 )INV2 = INT ( AIMAG ( CXV4 ) )

    Likewise, to place a unitary Numerical Values into the ImaginaryPart of a COMPLEX Variable, the Real Part should be entered as Zerowith or without explicit inclusion of the CMPLX Function :

    CXV1 = ( 0.0, REAL ( DPV1 ) )CXV2 = ( 0.0, REAL ( INV1 ) )

    CXV1 = CMPLX ( 0.0, REAL ( DPV1 ) )CXV2 = CMPLX ( 0.0, REAL ( INV1 ) )

    In Fortran 90, COMPLEX Type entities may use either REAL or DOUBLEPRECISION for their component Parts. So, assignments involving onlyCOMPLEX Values can still require conversions, when the Types forthe COMPLEX Parts are mismatched.

    50

  • Fortran Assignments and Operations - Part 8============================================

    - 4/ Basic Assignment of LOGICAL Variables :

    Only LOGICAL Type Values or Variables may be involved in assigningLOGICAL Variables, which can only take Values .TRUE. or .FALSE..When presented as in Line Constants, these must be written with thesurrounding Dots (.), but without any other form of quoting :

    LOGICAL LGV1, LGV2, LGV3

    LGV1 = .FALSE.LGV2 = .TRUE.

    LGV3 = LGV1

    In Fortran 77, Variables or Constants of other Types cannot directlybe converted to LOGICAL, and vice versa. Assignments mismatchingLOGICAL entities with other Types should cause compilation failures.

    51

  • Fortran Assignments and Operations - Part 9============================================

    - 5/ Basic Assignment aspects for CHARACTER Variables :

    Like LOGICAL data, CHARACTER assignments need a Right Hand side ofthat Type. Using the earlier 12 Byte CHARACTER Variables, these willall generate errors. The first two lack delimiting Single Quotes,while the third assigns an empty String which is not permitted :

    CVR1 = Data_StringCVR2 = 01234567CVR3 =

    For CHARACTER Type Variables, when the Value proves longer than theVariable, the Bytes beyond the Length of the Variable are truncated.Again with the earlier 12 Byte CHARACTER Variables :

    CVR1 = Data String too longCVR2 = Long Tail CVR3 =

    result in :

    CVR1 = Data_String CVR2 = Long TailCVR3 =

    Conversely, with CHARACTER Targets longer than the assigned Values,the tail of the Target is filled with Spaces. So, over the completeVariables, these earlier CHARACTER assignments

    CVR1 = Data_StringCVR2 = Some TextCVR3 =

    equate to :

    CVR1 = Data_String CVR2 = Some Text CVR3 =

    Thus trailing Blanks are ignored when dealing with CHARACTER data.For instance, may be used to blank a whole Variable, or to testwhether it contains any non Blank data anywhere along its Length.

    52

  • Fortran Assignments and Operations - Part 10============================================

    - 6/ Fortran Expressions :

    Expressions combine any number of Variables Values and Constantswith Operators to form a single Value. That may be assigned to aVariable, or used in a Relational Expression (used as Conditionalin an IF Statement). Thus, the right hand sides of the assignmentexamples above form simple Expressions. Operators available inExpressions depend on the Data Types involved. Rules govern the wayExpressions are evaluated to yield a single result.

    All the data entities in an expression should be of the same Type.However, when mismatched Numeric Types are present, conversions dotake place, by implicit or explicit use of the appropriate Functionas detailed above for basic assignments.

    This means Expressions split into three major sorts :

    Numeric Expressions, also called Arithmetic,

    CHARACTER Expressions, also described as Text Expressions,

    LOGICAL Expressions.

    Numeric Expressions themselves subdivide into :

    INTEGER (Type) Expressions,

    REAL (Type) Expressions,

    DOUBLE (Type) PRECISION Expressions,

    COMPLEX (Type) Expressions.

    So, three categories of Operators exist, applicable to Numeric,CHARACTER and LOGICAL Expressions respectively. As they rely ondiffering Symbols, risks of confusion or misuse are minimal.

    53

  • Fortran Assignments and Operations - Part 11============================================

    - 7/ Fortran Numeric (Arithmetic) Expressions :

    When evaluating Numeric Expressions with entities of dissimilarTypes, these are levelled by internal Conversions, to the higherType in the following atomic entity Type classification :

    Lowest : INTEGERREAL

    Top : DOUBLE PRECISION

    This means Expressions mixing REAL and INTEGER entities will beresolved after conversion to the REAL Type. Similarly, Expressionswith any DOUBLE PRECISION entities will call for their conversionto that Type. An exception exists for Exponentiation. See the notesabout Operators below.

    Example of Expressions and Assignments with mixed Type entities :

    INTEGER INV1

    REAL RLV1, RLV2

    DOUBLE PRECISION DPV1, DPV2

    INV1 = RLV1 + 52 * DPV1DPV2 = RLV2 * 12.6D2

    The first case leads to 52 being converted to DOUBLE PRECISIONand multiplied by DPV1, then a similar conversion of RLV1 beingadded to it, before the result gets turned to INTEGER (loosing thedecimals). In the second example, a prior conversion of RLV2 toDOUBLE PRECISION is multiplied before assignment to DPV2.

    Expressions featuring COMPLEX entities will call for conversionto that Type. That can entail "down" typing of DOUBLE PRECISIONentities when they become Parts of a COMPLEX one.

    54

  • Fortran Assignments and Operations - Part 12============================================

    - 7/ Fortran Numeric (Arithmetic) Expressions (continued) :

    Fortran Numeric Expressions may use 5 Arithmetic Operators :

    ** (Exponentiation),* (Multiplication),/ (Division),+ (Addition),- (Subtraction).

    Also, an Arithmetic or "Unary" Sign can be placed without spacingimmediately to the left of a Value or Variable Name. A Unary Minuseffectively flips the Sign of the entity, a Plus being redundant.For example -INV1 means ( -1 * INV1 ) for an INTEGER entity.

    Operations fall into 4 levels, regarding order of evaluation :

    Unary Sign applied when present,** evaluated first,* and / " after all **+ and - " last, after all ** and * or /.

    Sets of adjacent operations of the same category are processed leftto right, except Exponentiation (**), carried out right to left.

    This order may be altered by placing portions to be evaluated firstinside parentheses. Also, any Function calls in an Expression willbe resolved before other evaluations. For example :

    IVAR = 3 * INT ( DVR1 ) + 3DVR2 = 80.0D0 * ( DVR1 + 12.4D0 )

    means the INT conversion in the top Statement happens first, thenthe multiplication and last the addition. In the second case, thattakes place first, due to the Parentheses.

    55

  • Fortran Assignments and Operations - Part 13============================================

    - 7/ Fortran Numeric (Arithmetic) Expressions (continued) :

    Exponentiation Operator (**) :

    Unless Parentheses are used to alter this natural order, and takingentity Types as already equalised, Exponentiation takes priority overother Operations in the evaluation of Numeric Expressions.

    Unlike other Operations, Exponentiation proceeds right to left :

    DPVR ** 3.2D0 ** 4.4D0

    first raises 3.2 to the power 4.4, to then exponentiate DPVR.

    Integer Exponents may be processed more efficiently by the system,so they should be coded as such to facilitate that gain. Theseoperations to exponentiate a DOUBLE PRECISION Variable :

    DPV1 ** 3.0D0DPV2 ** 2.8D-1 ** 3.0D0 ** -4.8D0

    would be better (and more clearly) coded as :

    DPV1 ** 3DPV2 ** 2.8D-1 ** 3 ** -4.8D0

    or, to avoid any ambiguities in the second case :

    DPV2 ** ( 2.8D-1 ** ( 3 ** -4.8D0 ) )

    or, to also isolate the Unary Minus :

    DPV2 ** ( 2.8D-1 ** ( 3 ** ( -4.8D0 ) ) )

    In a lot of Code, squaring (Exponentiation by 2) is replaced by selfmultiplication (so DPV1 * DPV1 substitutes for DPV1 ** 2). Nocomputational cost is incurred, while poor compilers would not alwaysimplement this special case in an optimal manner.

    56

  • Fortran Assignments and Operations - Part 14============================================

    - 7/ Fortran Numeric (Arithmetic) Expressions (continued) :

    Multiplication and Division Operators (* and /) :

    Again assuming entities of have been brought to a single Type,Multiplications and Divisions follow any Exponentiations, butprecede all Additions and Subtractions in computing Expressions.Use of Parentheses may of course alter this natural order.

    In the standard fashion, Multiplications and Divisions proceedleft to right, taking operations of either sort indiscriminately :

    DPV1 * 3.2D0 / DPV2 * 4.8D0 / DPV3

    multiplies DPV1 by 3.2, divides the result by DPV2, that resulttimes 4.8 and, last, divided by DPV3 giving the Expression Value.

    As with the last Exponentiation example on the previous page,including Parentheses or positioning all operations of a same sortin succession can make the Code clearer :

    ( DPV1 * 3.2D0 * 4.5D0 ) / ( DPV3 * DPV2 )

    also, a good Compiler should reduce 3.2D0 * 4.8D0 to 15.36D0so as to save one Multiplication when running the compiled Binary.

    Integer Division removes any Decimals which would have been in thequotient of an equivalent Floating Point Division. For example :

    INV1 = 244INV2 = INV1 / 5

    assigns the result 48 to INV2.

    The remainder from an Integer Division, aka the Numerator Modulothe Divisor may be obtained via the MOD Intrinsic Function, like :

    INV3 = MOD ( INV1, INV2 )

    which, with INV1 and INV2 as above, produces the Value 4.

    57

  • Fortran Assignments and Operations - Part 15============================================

    - 7/ Fortran Numeric (Arithmetic) Expressions (continued) :

    Addition and Subtraction Operators (+ and -) :

    Again assuming entities of of a consistent Type in the Expression,Additions and Subtractions are performed last (that is followingall Exponentiations, and Multiplications or Divisions). As usual,Parentheses can force changes to this natural order.

    In the standard fashion, Additions and Subtractions are workedleft to right, taking operations of either sort indiscriminately :

    DPV1 + 8.6D0 + DPV2 - 4.8D0 + DPV3

    adds 8.6 to DPV1, then DPV2 to the result, before subtracting4.8 and finally adding DPV3 to yield the final Expression Value.

    No special criteria apply to INTEGER entities, and apart from makingthe Code clearer, no computational benefits, or gains in accuracyaccrue from grouping additions and subtractions in an Expressions.However, in the example above, the + 8.6D0 and - 4.8D0 couldbe turned into + 3.8D0 to economise one Subtraction. The Codewould then become the neater :

    DPV1 + DPV2 + DPV3 + 3.8D0

    58

  • Fortran Assignments and Operations - Part 16============================================

    - 8/ Fortran Character (String, or Text) Expressions :

    In terms of Data, CHARACTER Type Expressions can only includeVariables and Named or in Line Constants of that Type. HoweverVariables or Named Constants (set in PARAMETER Statements)may be presented in the form of Substrings.

    Concatenation forms the only Operator for CHARACTER Expressions.

    When CHARACTER entities are concatenated, their non Blank portions,if any, are merged in left to right order. As usual with CHARACTERassignments, any remaining Bytes are filled with Spaces.

    Example of CHARACTER Expressions and Concatenation :

    CHARACTER * 16 CHV1, CHV2, CHV3

    CHV1 = 01 // 234567CHV2 = CHV1 // 89CHV3 = CHV1 // 89 // ABCDEF

    The first Concatenation merges 01 and 234567 into CHV1, andfills the rest of CHV1 with Spaces. In the second case, 89 istacked straight after the 7 in CHV1, leaving 6 trailing Spaces.The third example in effect takes these tail Blanks with ABCDEF.So, CHV1 contains 01234567 , CHV2 0123456789 ,and CHV3 01234567890ABCDEF.

    Exactly the same could be achieved with Substrings :

    CHV1 ( 1 : 8 ) = 01 // 234567CHV2 ( 1 : 10 ) = CHV1 ( 1 : 8 ) // 89CHV3 = CHV2 ( 1 : 10 ) // ABCDEF

    However, Substrings would have made these examples different :

    CHV1 ( 1 : 12 ) = 01234567xx // abCHV2 ( 1 : 10 ) = CHV1 ( 1 : 8 ) // 89CHV3 = CHV2 ( 1 : 10 ) // ABCDEF

    with CHV2 and CHV3 ending as before, despite a changed CHV1.

    59

  • Fortran Assignments and Operations - Part 17============================================

    - 8/ Fortran Character (String, or Text) Expressions (continued) :

    As with Numeric Data Additions or Subtractions, no computationalgain accrues from reordering Concatenations. However, benefit isobtained by eliminating redundant operations. So :

    CHV3 = CHV1 // 89ABCDEFCHV3 = CHV2 // ABCDEF

    would have proved more efficient for the last two examples above.

    Parentheses may, just as in Arithmetic Expressions, force a givenorder of evaluation, much as this will not change the final Value.

    As usual with CHARACTER assignments, placing a String in a Variablewhose Length is less than that of the data causes truncation of theexcess text. For example :

    CHARACTER CHV1 * 4, CHV2 * 4,1 CHV3 * 6, CHV4 * 10

    CHV1 = 01 // 234567CHV2 = CHV1 // 89CHV3 = CHV1 // 89CHV4 = CHV1 // 89 // ABCDEF

    result in 01234567 being assigned to CHV1, which becomes 0123.The 89 Concatenation to CHV2 makes no difference. CHV1 fillsthat Variable already. But 89 gets placed after CHV1 into CHV3as the Expression 012389 is formed by the Concatenation, despitethe full state of CHV1.

    In the last case, 89 first gets appended to 0123, then ABCDEF,but EF is lost when the Expression is assigned to a Variable tooshort to hold it.

    60

  • Fortran Assignments and Operations - Part 18============================================

    - 9/ Fortran Logical Expressions :

    Regarding Data, LOGICAL Type Expressions can only contain entitiesof that Type. Type specific Operators must be used in Expressions,as listed below.

    Fortran Logical Operators (Delimiting Dots always required) :

    .NOT. (Negation, True when following entity Falseand False when following entity True),

    .AND. (Conjunction, True when both Sides True),

    .OR. (Inclusive Disjunction, True when either Side True),

    .EQV. (Equivalence, True when both Sides same),

    .NEQV. (Non Equivalence, True when both Sides dissimilar).

    Apart from .NOT. which relates to the entity to its Right handSide only, the Logical Operators require entities on both Sides whenshowing in Expressions, or when assigning Expressions to Variables.

    Operations fall into 4 levels, regarding order of evaluation :

    .NOT. evaluated first,

    .AND. " after all .NOT.,

    .OR. " " " .NOT. and .AND.,

    .EQV. and .NEQV. " last, after other Operators.

    Example of LOGICAL Expressions and Operators :

    LOGICAL LGV1, LGV2, LGV3,1 LGV4, LGV5, LGV6

    LGV1 = .TRUE.LGV2 = .NOT. LGV1LGV3 = LGV1 .AND. .TRUE.

    LGV4 = LGV2 .OR. LGV1 .AND. .FALSE.LGV5 = LGV1 .EQV. LGV3LGV6 = LGV2 .NEQV. LGV3

    Except in the second and fourth cases the Target will be .TRUE..

    61

  • Fortran Assignments and Operations - Part 19============================================

    - 9/ Fortran Logical Expressions (continued) :

    Evaluation of same level Operators proceeds left to right in anExpression, unless Parentheses force their contents to be computedfirst. The LGV4 example above, when written :

    LGV4 = ( LGV2 .OR. LGV1 ) .AND. LGV3

    would have yielded .TRUE. as both Sides of the .AND. are so.It may help readability anyway to include (redundant) Parentheses,and will entail no computational cost. Reordering operations in anExpression, unless some can thus be eliminated will not bring anyefficiency gains either.

    However, in this example Expression :

    LGV4 = .NOT. ( LGV1 .OR. LGV2 ) .AND. LGV3

    the Parentheses insure the .NOT. affects the result of the .OR.between LGV1 and LGV2, and not merely LGV1 alone, but theyalso force evaluation of that negated .OR. before the .AND..

    Without the Parentheses, the .NOT. would be effected first, thenthe .AND. between LGV2 and LGV3 and last a .OR. betweenthe outcome of the .AND. and the negated LGV1 from earlier.

    62

  • Fortran Flow Control and Logic - Part 1========================================

    - 1/ Introduction :

    Flow control Statements, or merely Control Statements direct thesequencing of Statements in the Executable Part of Fortran Programs.This may depend on some Data Values, or allow repeated execution ofsome portions of the Program.

    Conditional Statements, under the various forms of the IF Statementevaluate Relational, Logical, or Arithmetic Expressions, and thisresults in one or more Statements being executed or not, dependingon the True or False nature of the Expression or its Value. Logicaland Block IF Statements use Relational and Logical Expressions. Theobsolete Arithmetic IF uses Arithmetic Expressions.

    Multiple execution of a passage of Code is facilitated by Loops.The one available sort of Fortran Loop construct is called DO. ACounter limits the number of runs, or Iterations, through Loops.

    Branch Statements may also evaluate a Variable, but will alwaysresult in transferring execution to a labelled Statement, whereverthat sits in the Executable Part of the Program. Branch Statementsin Fortran are all called GOTO.

    Additional Control Statement permit temporary or permanent haltsto the execution of Programs, and mark the completion of Routines.The STOP Statement terminates execution anywhere it appears. An ENDis required as the last (Executable) Statement in all Routines.

    Fortran 90 introduced additional Loop constructs, where iterationsmay be handled on a conditional rather than just on a Count basis.New Statements were also designed to deal with Loop exits.

    63

  • Fortran Flow Control and Logic - Part 2========================================

    - 2/ Relational (Conditional) Expressions :

    Relational (sometimes called Conditional) Expressions are commonlyused with the two main forms of IF Statement in Fortran (the LogicalIF and the Block IF and associated Statements).

    Relational Expressions compare Arithmetic or CHARACTE


Recommended