fortran_fortran examples - wiki books, open books for an open world

Upload: haniballkinga2778

Post on 06-Apr-2018

236 views

Category:

Documents


0 download

TRANSCRIPT

  • 8/3/2019 Fortran_Fortran Examples - Wiki Books, Open Books for an Open World

    1/20

    Fortran/Fortran examples

    Part of the Fortran WikiBook

    The following Fortran code examples or sample programs show different situations depending on the

    compiler. The first set of examples are for the Fortran II, IV, and 77 compilers. The remaining examples can be

    compiled and run with any newer standard Fortran compiler (see the end of the main Fortran article for lists of

    compilers). Most modern Fortran compilers expect a file with a .f or .for extension (for FORTRAN 66 or

    FORTRAN 77 source, although the FORTRAN 66 dialect may have to be selected specifically with a

    command-line option) or .f90/.f95 extension (for Fortran 90/95 source, respectively).

    FORTRAN II, IV, and 77 compilers

    NOTE: Before FORTRAN 90, most FORTRAN compilers enforced fixed-format source code, a carryover

    from IBM punch cards (http://en.wikipedia.org/wiki/Punch_card)

    comments must begin with a * or C or ! in column 1

    statement labels must occur in columns 1-5

    continuation lines must have a non-blank character in column 6

    statements must start in column 7

    the line-length may be limited to 72 characters (derived from the 80-byte width of a punch-card, with last

    8 characters reserved for (optional) sequence numbers)

    If errors are produced when you compile your FORTRAN code, first check the column alignment. Some

    compilers also offer free form source (http://en.wikipedia.org/wiki/Free-form_language) by using a compiler

    flag

    Area Of a Triangle program

    Simple Fortran II program

    One data card input

    If one of the input values is zero, then the program will end with an error code of "1" in the job control card

    listing following the execution of the program. Normal output will be one line printed with A, B, C, and AREA.

    No specific units are stated.

    C AREA OF A TRIANGLE - HERON'S FORMULA

    C INPUT - CARD READER UNIT 5, INTEGER INPUT

    C OUTPUT - LINE PRINTER UNIT 6, REAL OUTPUT

    C INPUT ERROR DISPAY ERROR OUTPUT CODE 1 IN JOB CONTROL LISTING

    INTEGER A,B,C

    READ(5,501) A,B,C

    501 FORMAT(3I5)

    IF(A.EQ.0 .OR. B.EQ.0 .OR. C.EQ.0)STOP1

    S =(A + B + C)/2.0

    an/Fortran examples - Wikibooks, open books for an open world http://en.wikibooks.org/wiki/Fortran/Fortran_

    0 10/28/2011

  • 8/3/2019 Fortran_Fortran Examples - Wiki Books, Open Books for an Open World

    2/20

    AREA =SQRT( S *(S - A)*(S - B)*(S - C))

    WRITE(6,601) A,B,C,AREA

    601 FORMAT(4H A= ,I5,5H B= ,I5,5H C= ,I5,8H AREA= ,F10.2,12HSQUARE

    STOP

    END

    Simple Fortran IV program

    Multiple data card input

    This program has two input checks: one for a blank card to indicate end-of-data, and the other for a zero value

    within the input data. Either condition causes a message to be printed.

    C AREA OF A TRIANGLE - HERON'S FORMULA

    C INPUT - CARD READER UNIT 5, INTEGER INPUT, ONE BLANK CARD FOR END-OF-

    C OUTPUT - LINE PRINTER UNIT 6, REAL OUTPUT

    C INPUT ERROR DISPAY ERROR MESSAGE ON OUTPUT

    501 FORMAT(3I5)

    601 FORMAT(4H A= ,I5,5H B= ,I5,5H C= ,I5,8H AREA= ,F10.2,12HSQUARE

    602 FORMAT(10HNORMAL END)

    603 FORMAT(23HINPUT ERROR, ZERO VALUE)

    INTEGER A,B,C

    10 READ(5,501) A,B,C

    IF(A.EQ.0 .AND. B.EQ.0 .AND. C.EQ.0)GOTO50

    IF(A.EQ.0 .OR. B.EQ.0 .OR. C.EQ.0)GOTO90

    S =(A + B + C)/2.0

    AREA =SQRT( S *(S - A)*(S - B)*(S - C))

    WRITE(6,601) A,B,C,AREA GOTO10

    50 WRITE(6,602)

    STOP

    90 WRITE(6,603)

    STOP

    END

    Simple Fortran 77 program

    Multiple data card input

    This program has two input checks in the READ statement with the END and ERR parameters, one for a blank

    card to indicate end-of-data; and the other for zero value along with valid data. In either condition, a message

    will be printed.

    C AREA OF A TRIANGLE - HERON'S FORMULA

    C INPUT - CARD READER UNIT 5, INTEGER INPUT, NO BLANK CARD FOR END OF D

    C OUTPUT - LINE PRINTER UNIT 6, REAL OUTPUT

    an/Fortran examples - Wikibooks, open books for an open world http://en.wikibooks.org/wiki/Fortran/Fortran_

    0 10/28/2011

  • 8/3/2019 Fortran_Fortran Examples - Wiki Books, Open Books for an Open World

    3/20

    C INPUT ERROR DISPAYS ERROR MESSAGE ON OUTPUT

    501 FORMAT(3I5)

    601 FORMAT(" A= ",I5," B= ",I5," C= ",I5," AREA= ",F10.2,"SQUARE U

    602 FORMAT("NORMAL END")

    603 FORMAT("INPUT ERROR OR ZERO VALUE ERROR")

    INTEGER A,B,C

    10 READ(5,501,END=50,ERR=90) A,B,C

    IF(A=0.OR. B=0.OR. C=0)GOTO90

    S =(A + B + C)/2.0

    AREA =SQRT( S *(S - A)*(S - B)*(S - C))

    WRITE(6,601) A,B,C,AREA

    GOTO10

    50 WRITE(6,602)

    STOP

    90 WRITE(6,603)

    STOP

    END

    "Retro" FORTRAN IV

    A retro example of a FORTRAN IV (later evolved into FORTRAN 66) program deck is available on the IBM

    1130 page, including the IBM 1130 DM2 JCL required for compilation and execution. An IBM 1130 emulator

    is available at IBM 1130.org (http://ibm1130.org/) that will allow the FORTRAN IV program to be compiled

    and run on a PC.

    Hello, World program

    In keeping with computing tradition, the first example presented is a simple program to display the words"Hello, world" on the screen (or printer).

    FORTRAN 66 (also FORTRAN IV)

    C FORTRAN IV WAS ONE OF THE FIRST PROGRAMMING

    C LANGUAGES TO SUPPORT SOURCE COMMENTS

    WRITE (6,7)

    7 FORMAT(13H HELLO, WORLD)

    STOP

    END

    This program prints "HELLO, WORLD" to Fortran unit number 6, which on most machines was the line printer

    or terminal. (The card reader or keyboard was usually connected as unit 5). The number 7 in the WRITE

    statement refers to the statement number of the corresponding FORMAT statement. FORMAT statements may be

    placed anywhere in the same program or function/subroutine block as the WRITE statements which reference

    them. Typically a FORMAT statement is placed immediately following the WRITE statement which invokes it;

    alternatively, FORMAT statements are grouped together at the end of the program or subprogram block. If

    execution flows into a FORMAT statement, it is a no-op; thus, the example above has only two executable

    an/Fortran examples - Wikibooks, open books for an open world http://en.wikibooks.org/wiki/Fortran/Fortran_

    0 10/28/2011

  • 8/3/2019 Fortran_Fortran Examples - Wiki Books, Open Books for an Open World

    4/20

  • 8/3/2019 Fortran_Fortran Examples - Wiki Books, Open Books for an Open World

    5/20

    PROGRAM EUCLID

    PRINT *, 'A?'

    READ *, NA

    IF(NA.LE.0)THEN

    PRINT *, 'A must be a positive integer.'

    STOP

    ENDIF

    PRINT *, 'B?'

    READ *, NB

    IF(NB.LE.0)THEN

    PRINT *, 'B must be a positive integer.'

    STOP

    ENDIF

    PRINT *, 'The GCD of', NA, ' and', NB, ' is', NGCD(NA, NB), '.'

    STOP

    END

    FUNCTION NGCD(NA, NB)

    IA = NAIB = NB

    1 IF(IB.NE.0)THEN

    ITEMP = IA

    IA = IB

    IB =MOD(ITEMP, IB)

    GOTO1

    ENDIF

    NGCD = IA

    RETURN

    END

    The above example is intended to illustrate the following:

    The PRINT and READ statements in the above use '*' as a format, specifying list-directed formatting.

    List-directed formatting instructs the compiler to make an educated guess about the required input or

    output format based on the following arguments.

    As the earliest machines running Fortran had restricted character sets, FORTRAN 77 uses abbreviations

    such as .EQ., .NE., .LT., .GT., .LE., and .GE. to represent the relational operators =, , , , and ,

    respectively.

    This example relies on the implicit typing mechanism to specify the INTEGER types ofNA, NB, IA, IB,

    and ITEMP.

    In the function NGCD(NA, NB), the values of the function arguments NA and NB are copied into the local

    variables IA and IB respectively. This is necessary as the values ofIA and IB are altered within the

    function. Because argument passing in Fortran functions and subroutines utilize call by reference by

    default (rather than call by value, as is the default in languages such as C), modifying NA and NB from

    within the function would effectively have modified the corresponding actual arguments in the main

    PROGRAM unit which called the function.

    The following shows the results of compiling and running the program.

    an/Fortran examples - Wikibooks, open books for an open world http://en.wikibooks.org/wiki/Fortran/Fortran_

    0 10/28/2011

  • 8/3/2019 Fortran_Fortran Examples - Wiki Books, Open Books for an Open World

    6/20

  • 8/3/2019 Fortran_Fortran Examples - Wiki Books, Open Books for an Open World

    7/20

    EXP() corresponds to the exponential function ex. In FORTRAN 77, this is a generic function, meaning

    that it accepts arguments of multiple types (such as REAL and, in this example, COMPLEX). In FORTRAN

    66, a specific function would have to be called by name depending on the type of the function arguments

    (for this example, CEXP() for a COMPLEX-valued argument).

    When applied to a COMPLEX-valued argument, REAL() and AIMAG() return the values of the argument's

    real and imaginary components, respectively.

    Incidentally, the output of the above program is as follows (see the article on Euler's formula for the geometricinterpretation of these values as eight points spaced evenly about a unit circle in the complex plane).

    $ cmplxd

    e**(j*0*pi/4) = 1.0000000 + j0.0000000

    e**(j*1*pi/4) = 0.7071068 + j0.7071068

    e**(j*2*pi/4) = 0.0000000 + j1.0000000

    e**(j*3*pi/4) = -0.7071068 + j0.7071068

    e**(j*4*pi/4) = -1.0000000 - j0.0000001

    e**(j*5*pi/4) = -0.7071066 - j0.7071069

    e**(j*6*pi/4) = 0.0000000 - j1.0000000e**(j*7*pi/4) = 0.7071070 - j0.7071065

    Error can be seen occurring in the last decimal place in some of the numbers above, a result of the COMPLEX data

    type representing its real and imaginary components in single precision. Incidentally, Fortran 90 also made

    standard a double-precision complex-number data type (although several compilers provided such a type even

    earlier).

    Fortran 90/95 examples

    Summations with a DO loop

    In this example of Fortran 90 code, the programmer has written the bulk of the code inside of a DO loop. Upon

    execution, instructions are printed to the screen and a SUM variable is initialized to zero outside the loop. Once

    the loop begins, it asks the user to input any number. This number is added to the variable SUM every time the

    loop repeats. If the user inputs 0, the EXIT statement terminates the loop, and the value of SUM is displayed on

    screen.

    Also apparent in this program is a data file. Before the loop begins, the program creates (or opens, if it has

    already been run before) a text file called "SumData.DAT". During the loop, the WRITE statement stores any

    user-inputted number in this file, and upon termination of the loop, also saves the answer.

    ! sum.f90

    ! Performs summations using in a loop using EXIT statement

    ! Saves input information and the summation in a data file

    program summation

    implicitnone

    integer:: sum, a

    an/Fortran examples - Wikibooks, open books for an open world http://en.wikibooks.org/wiki/Fortran/Fortran_

    0 10/28/2011

  • 8/3/2019 Fortran_Fortran Examples - Wiki Books, Open Books for an Open World

    8/20

    print*, "This program performs summations. Enter 0 to stop."

    open(unit=10, file="SumData.DAT")

    sum =0

    do

    print*, "Add:"

    read*, a

    if(a ==0)then

    exit

    else

    sum = sum + a

    endif

    write(10,*) a

    enddo

    print*, "Summation =", sum

    write(10,*)"Summation =", sumclose(10)

    end

    When executed, the console would display the following:

    This program performs summations. Enter 0 to stop.

    Add:

    1

    Add:

    2

    Add:

    3

    Add:

    0

    Summation = 6

    And the file SumData.DAT would contain:

    1

    2

    3

    Summation = 6

    Calculating cylinder area

    The following program, which calculates the surface area of a cylinder, illustrates free-form source input and

    an/Fortran examples - Wikibooks, open books for an open world http://en.wikibooks.org/wiki/Fortran/Fortran_

    0 10/28/2011

  • 8/3/2019 Fortran_Fortran Examples - Wiki Books, Open Books for an Open World

    9/20

    other features introduced by Fortran 90.

    program cylinder

    ! Calculate the surface area of a cylinder.

    !

    ! Declare variables and constants.

    ! constants=pi! variables=radius squared and height

    implicitnone ! Require all variables to be explicitly declared

    integer:: ierr

    character(1):: yn

    real:: radius, height, area

    real, parameter:: pi =3.141592653589793

    interactive_loop:do

    ! Prompt the user for radius and height

    ! and read them.

    write (*,*)'Enter radius and height.'

    read (*,*,iostat=ierr) radius,height

    ! If radius and height could not be read from input,

    ! then cycle through the loop.

    if(ierr /=0)thenwrite(*,*)'Error, invalid input.'

    cycle interactive_loop

    endif

    ! Compute area. The ** means "raise to a power."

    area =2* pi *(radius**2+ radius*height)

    ! Write the input variables (radius, height)

    ! and output (area) to the screen.

    write (*,'(1x,a7,f6.2,5x,a7,f6.2,5x,a5,f6.2)')&

    'radius=',radius,'height=',height,'area=',area

    yn =' '

    yn_loop:do

    write(*,*)'Perform another calculation? y[n]'

    read(*,'(a1)') yn

    if(yn=='y'.or. yn=='Y')exit yn_loop

    if(yn=='n'.or. yn=='N'.or. yn==' ')exit interactive_loop

    an/Fortran examples - Wikibooks, open books for an open world http://en.wikibooks.org/wiki/Fortran/Fortran_

    0 10/28/2011

  • 8/3/2019 Fortran_Fortran Examples - Wiki Books, Open Books for an Open World

    10/20

    enddo yn_loop

    enddo interactive_loop

    endprogram cylinder

    Dynamic memory allocation and arrays

    The following program illustrates dynamic memory allocation and array-based operations, two features

    introduced with Fortran 90. Particularly noteworthy is the absence ofDO loops and IF/THEN statements in

    manipulating the array; mathematical operations are applied to the array as a whole. Also apparent is the use of

    descriptive variable names and general code formatting that comport with contemporary programming style.

    This example computes an average over data entered interactively.

    program average

    ! Read in some numbers and take the average

    ! As written, if there are no data points, an average of zero is return

    ! While this may not be desired behavior, it keeps this example simple

    implicitnone

    integer:: number_of_points

    real, dimension(:), allocatable:: points

    real:: average_points=0., positive_average=0., negative_average=0.

    write (*,*)"Input number of points to average:"

    read (*,*) number_of_points

    allocate(points(number_of_points))

    write (*,*)"Enter the points to average:"

    read (*,*) points

    ! Take the average by summing points and dividing by number_of_points

    if(number_of_points > 0) average_points = sum(points)/number_of_point

    ! Now form average over positive and negative points only

    if(count(points > 0.) > 0) positive_average = sum(points, points > 0.

    /count(points > 0.)

    if(count(points < 0.) > 0) negative_average = sum(points, points < 0.

    /count(points < 0.)

    deallocate(points)

    ! Print result to terminal

    write (*,'(''Average = '', 1g12.4)') average_points

    write (*,'(''Average of positive points = '', 1g12.4)') positive_aver

    write (*,'(''Average of negative points = '', 1g12.4)') negative_aver

    an/Fortran examples - Wikibooks, open books for an open world http://en.wikibooks.org/wiki/Fortran/Fortran_

    20 10/28/2011

  • 8/3/2019 Fortran_Fortran Examples - Wiki Books, Open Books for an Open World

    11/20

  • 8/3/2019 Fortran_Fortran Examples - Wiki Books, Open Books for an Open World

    12/20

    ! dot_product(a,v)=a'b

    tol_max =max((abs(x(i)- xk)/(1. +abs(xk)))**2, abs(A(i, i)

    x(i)= xk

    enddo iteration_loop

    enddo convergence_loop

    if(present(actual_iter)) actual_iter = iter

    endfunction gauss_sparse

    Note that an explicit interface to this routine must be available to its caller so that the type signature is known.

    This is preferably done by placing the function in a MODULE and then USEing the module in the calling routine.

    An alternative is to use an INTERFACE block, as shown by the following example:

    program test_gauss_sparse

    implicitnone

    ! explicit interface to the gauss_sparse function

    interface

    function gauss_sparse(num_iter, tol, b, A, x, actual_iter)resu

    real:: tol_max

    integer, intent(in):: num_iter

    real, intent(in):: tol

    real, intent(in), dimension(:):: b, A(:,:)

    real, intent(inout):: x(:)

    integer, optional, intent(out):: actual_iter

    endfunction

    endinterface

    ! declare variables

    integer:: i, N =3, actual_iter

    real:: residue

    real, allocatable:: A(:,:), x(:), b(:)

    ! allocate arrays

    allocate(A(N, N), b(N), x(N))

    ! Initialize matrix

    A =reshape([(real(i), i =1, size(A))], shape(A))

    ! Make matrix diagonally dominant

    do i =1, size(A, 1)

    A(i,i)= sum(A(i,:))+1

    enddo

    ! Initialize b

    b =[(i, i =1, size(b))]

    an/Fortran examples - Wikibooks, open books for an open world http://en.wikibooks.org/wiki/Fortran/Fortran_

    20 10/28/2011

  • 8/3/2019 Fortran_Fortran Examples - Wiki Books, Open Books for an Open World

    13/20

    ! Initial (guess) solution

    x = b

    ! invoke the gauss_sparse function

    residue = gauss_sparse(num_iter =100, &

    tol = 1E-5, &

    b = b, &

    A = a, &

    x = x, &

    actual_iter = actual_iter)

    ! Output

    print '(/ "A = ")'

    do i =1, size(A, 1)

    print '(100f6.1)', A(i,:)

    enddo

    print '(/ "b = " / (f6.1))', b

    print '(/ "residue = ", g10.3 / "iterations = ", i0 / "solution = "

    residue, actual_iter, x

    endprogram test_gauss_sparse

    Writing subroutines

    In those cases where it is desired to return values via a procedure's arguments, a subroutine is preferred over a

    function; this is illustrated by the following subroutine to swap the contents of two arrays:

    an/Fortran examples - Wikibooks, open books for an open world http://en.wikibooks.org/wiki/Fortran/Fortran_

    20 10/28/2011

  • 8/3/2019 Fortran_Fortran Examples - Wiki Books, Open Books for an Open World

    14/20

    subroutine swap_real(a1, a2)

    implicitnone

    ! Input/Output

    real, intent(inout):: a1(:), a2(:)

    ! Locals

    integer:: i

    real:: a

    ! Swap

    do i =1, min(size(a1), size(a2))

    a = a1(i)

    a1(i)= a2(i)

    a2(i)= a

    enddo

    endsubroutine swap_real

    As in the previous example, an explicit interface to this routine must be available to its caller so that the type

    signature is known. As before, this is preferably done by placing the function in a MODULE and then USEing the

    module in the calling routine. An alternative is to use a INTERFACE block.

    Internal and Elemental Procedures

    An alternative way to write the swap_real subroutine from the previous example, is:

    subroutine swap_real(a1, a2)

    implicitnone

    ! Input/Output

    real, intent(inout):: a1(:), a2(:)

    ! Locals

    integer:: N

    ! Swap, using the internal subroutine

    N =min(size(a1), size(a2))

    call swap_e(a1(:N), a2(:N))

    contains

    elemental subroutine swap_e(a1, a2)

    real, intent(inout):: a1, a2

    real:: a

    a = a1

    an/Fortran examples - Wikibooks, open books for an open world http://en.wikibooks.org/wiki/Fortran/Fortran_

    20 10/28/2011

  • 8/3/2019 Fortran_Fortran Examples - Wiki Books, Open Books for an Open World

    15/20

    a1 = a2

    a2 = a

    endsubroutine swap_e

    endsubroutine swap_real

    In the example, the swap_e subroutine is elemental, i.e., it acts upon its array arguments, on an element-

    by-element basis. Elemental procedures must be pure (i.e., they must have no side effects and can invoke only

    pure procedures), and all the arguments must be scalar. Since swap_e is internal to the swap_real subroutine, no

    other program unit can invoke it.

    The following program serves as a test for any of the two swap_real subroutines presented:

    program test_swap_real

    implicitnone

    ! explicit interface to the swap_real subroutine

    interface

    subroutine swap_real(a1, a2)

    real, intent(inout):: a1(:), a2(:)

    endsubroutine swap_real

    endinterface

    ! Declare variables

    integer:: i

    real:: a(10), b(10)

    ! Initialize a, b

    a =[(real(i), i =1, 20, 2)]b = a +1

    ! Output before swap

    print '(/"before swap:")'

    print '("a = [", 10f6.1, "]")', a

    print '("b = [", 10f6.1, "]")', b

    ! Call the swap_real subroutine

    call swap_real(a, b)

    ! Output after swapprint '(// "after swap:")'

    print '("a = [", 10f6.1, "]")', a

    print '("b = [", 10f6.1, "]")', b

    endprogram test_swap_real

    Pointers and targets methods

    an/Fortran examples - Wikibooks, open books for an open world http://en.wikibooks.org/wiki/Fortran/Fortran_

    20 10/28/2011

  • 8/3/2019 Fortran_Fortran Examples - Wiki Books, Open Books for an Open World

    16/20

    In Fortran, the concept of pointers differs from that in C-like languages. A Fortran 90 pointer does not merely

    store the memory address of a target variable; it also contains additional descriptive information such as the

    target's rank, the upper and lower bounds of each dimension, and even strides through memory. This allows a

    Fortran 90 pointer to point at submatrices.

    Fortran 90 pointers are "associated" with well-defined "target" variables, via either the pointer assignment

    operator (=>) or an ALLOCATE statement. When appearing in expressions, pointers are always dereferenced; no

    "pointer arithmetic" is possible.

    The following example illustrates the concept:

    module SomeModule

    implicitnone

    contains

    elemental function A(x)result(res)

    integer:: res

    integer, intent(IN):: x

    res = x +1

    endfunctionendmodule SomeModule

    program Test

    use SomeModule, DoSomething => A

    implicitnone

    !Declare variables

    integer, parameter:: m =3, n =3

    integer, pointer:: p(:)=>null(), q(:,:)=>null()

    integer, allocatable, target:: A(:,:)

    integer:: istat =0, i, j

    character(80)::fmt

    ! Write format string for matrices

    ! (/ A / A, " = [", 3( "[",3(i2, 1x), "]" / 5x), "]" )

    write (fmt, '("(/ A / A, "" = ["", ", i0, "( ""["",", i0, "(i2, 1x),

    allocate(A(m, n), q(m, n), stat = istat)

    if(istat /=0)stop'Error during allocation of A and q'

    ! Matrix A is:! A = [[ 1 4 7 ]

    ! [ 2 5 8 ]

    ! [ 3 6 9 ]

    ! ]

    A =reshape([(i, i =1, size(A))], shape(A))

    q = A

    write(*, fmt)"Matrix A is:", "A", ((A(i, j), j =1, size(A, 2)), i

    an/Fortran examples - Wikibooks, open books for an open world http://en.wikibooks.org/wiki/Fortran/Fortran_

    20 10/28/2011

  • 8/3/2019 Fortran_Fortran Examples - Wiki Books, Open Books for an Open World

    17/20

    ! p will be associated with the first column of A

    p => A(:, 1)

    ! This operation on p has a direct effect on matrix A

    p = p **2

    ! This will end the association between p and the first column of A

    nullify(p)

    ! Matrix A becomes:

    ! A = [[ 1 4 7 ]

    ! [ 4 5 8 ]

    ! [ 9 6 9 ]

    ! ]

    write(*, fmt)"Matrix A becomes:", "A", ((A(i, j), j =1, size(A, 2))

    ! Perform some array operation

    q = q + A

    ! Matrix q becomes:

    ! q = [[ 2 8 14 ]

    ! [ 6 10 16 ]

    ! [12 12 18 ]

    ! ]

    write(*, fmt)"Matrix q becomes:", "q", ((q(i, j), j =1, size(A, 2))

    ! Use p as an ordinary array

    allocate(p(1:m*n), stat = istat)

    if(istat /=0)stop'Error during allocation of p'

    ! Perform some array operation

    p =reshape(DoSomething(A + A **2), shape(p))

    ! Array operation:

    ! p(1) = 3

    ! p(2) = 21

    ! p(3) = 91

    ! p(4) = 21

    ! p(5) = 31

    ! p(6) = 43

    ! p(7) = 57

    ! p(8) = 73

    ! p(9) = 91

    write(*, '("Array operation:" / (4x,"p(",i0,") = ",i0))')(i, p(i),

    deallocate(A, p, q, stat = istat)

    if(istat /=0)stop'Error during deallocation'

    endprogram Test

    an/Fortran examples - Wikibooks, open books for an open world http://en.wikibooks.org/wiki/Fortran/Fortran_

    20 10/28/2011

  • 8/3/2019 Fortran_Fortran Examples - Wiki Books, Open Books for an Open World

    18/20

    Module programming

    A module is a program unit which contains data definitions, global data, and CONTAINed procedures. Unlike a

    simple INCLUDE file, a module is an independent program unit that can be compiled separately and linked in its

    binary form. Once compiled, a module'spublic contents can be made visible to a calling routine via the USE

    statement.

    The module mechanism makes the explicit interface of procedures easily available to calling routines. In fact,modern Fortran encourages every SUBROUTINE and FUNCTION to be CONTAINed in a MODULE. This allows the

    programmer to use the newer argument passing options and allows the compiler to perform full type checking

    on the interface.

    The following example also illustrates derived types, overloading of operators and generic procedures.

    module GlobalModule

    ! Reference to a pair of procedures included in a previously compiled

    ! module named PortabilityLibrary use PortabilityLibrary, only: GetLastError, & ! Generic procedure

    Date ! Specific procedure

    ! Constants

    integer, parameter:: dp_k =kind(1.0d0) ! Double precision ki

    real, parameter:: zero =(0.)

    real(dp_k), parameter:: pi =3.141592653589793_dp_k

    ! Variables

    integer:: n, m, retint

    logical::status, retlog

    character(50):: AppName

    ! Arrays

    real, allocatable, dimension(:,:,:):: a, b, c, d

    complex(dp_k), allocatable, dimension(:):: z

    ! Derived type definitions

    type ijk

    integer:: i

    integer:: j

    integer:: k

    endtype ijk

    type matrix

    integer m, n

    real, allocatable:: a(:,:) ! Fortran 2003 feature. For Fortran 9

    endtype matrix

    ! All the variables and procedures from this module can be accessed

    ! by other program units, except for AppName

    public

    an/Fortran examples - Wikibooks, open books for an open world http://en.wikibooks.org/wiki/Fortran/Fortran_

    20 10/28/2011

  • 8/3/2019 Fortran_Fortran Examples - Wiki Books, Open Books for an Open World

    19/20

    private:: AppName

    ! Generic procedure swap

    interface swap

    moduleprocedure swap_integer, swap_real

    endinterface swap

    interface GetLastError ! This adds a new, additional procedure to t

    ! generic procedure GetLastError

    moduleprocedure GetLastError_GlobalModule

    endinterface GetLastError

    ! Operator overloading

    interfaceoperator(+)

    moduleprocedure add_ijk

    endinterface

    ! Prototype for external procedure

    interface function gauss_sparse(num_iter, tol, b, A, x, actual_iter)result(

    real:: tol_max

    integer, intent(in):: num_iter

    real, intent(in):: tol

    real, intent(in), dimension(:):: b, A(:,:)

    real, intent(inout):: x(:)

    integer, optional, intent(out):: actual_iter

    endfunction gauss_sparse

    endinterface

    ! Procedures included in the module contains

    ! Internal function

    function add_ijk(ijk_1, ijk_2)

    type(ijk) add_ijk, ijk_1, ijk_2

    intent(in):: ijk_1, ijk_2

    add_ijk = ijk(ijk_1%i + ijk_2%i, ijk_1%j + ijk_2%j, ijk_1%k + ijk_

    endfunction add_ijk

    ! Include external files

    include 'swap_integer.f90'! Comments SHOULDN'T be added on include

    include 'swap_real.f90'

    endmodule GlobalModule

    Retrieved from "http://en.wikibooks.org/w/index.php?title=Fortran/Fortran_examples&oldid=2065810"

    This page was last modified on 6 March 2011, at 03:15.

    Text is available under the Creative Commons Attribution-ShareAlike License; additional terms may

    apply. See Terms of Use for details.

    an/Fortran examples - Wikibooks, open books for an open world http://en.wikibooks.org/wiki/Fortran/Fortran_

    20 10/28/2011

  • 8/3/2019 Fortran_Fortran Examples - Wiki Books, Open Books for an Open World

    20/20

    an/Fortran examples - Wikibooks, open books for an open world http://en.wikibooks.org/wiki/Fortran/Fortran_