Download as pdf or txt
Download as pdf or txt
You are on page 1of 5

SAMPLE PROGRAMS WEEK 4 1. Input and output 2.

Modules

AUTUMN 2004

1. Input and Output Example 1.1 Formatted output and writing to file.
PROGRAM TRIG_TABLE ! Compiles a table of SIN, COS, TAN against angle in DEGREES IMPLICIT NONE INTEGER DEG ! angle in degrees REAL RAD ! angle in radians REAL PI ! mathematical pi INTEGER I ! a counter INTEGER :: STEP = 5 ! angular increment in degrees INTEGER :: NSTEP = 17 ! number of intervals CHARACTER (LEN=*), PARAMETER :: FMTHEAD = '( 1X, A3, 3( 2X, A7 ) )' CHARACTER (LEN=*), PARAMETER :: FMTDATA = '( 1X, I3, 3( 2X, F7.4 ) )' ! formats for headings and data

WRITE ( *, FMTHEAD ) 'Deg', 'Sin', 'Cos', 'Tan' PI = 4.0 * ATAN( 1.0 ) DO I = 0, NSTEP DEG = I * STEP RAD = DEG * PI / 180.0 WRITE ( *, FMTDATA ) DEG, SIN( RAD ), COS( RAD ), TAN( RAD ) END DO END PROGRAM TRIG_TABLE

Alternatively:
WRITE ( *,'( 1X, A3, 3( 2X, A7 ) )' ) 'Deg', 'Sin', 'Cos', 'Tan' WRITE ( *,'( 1X, I3,3( 2X, F7.4 ) )' ) DEG, SIN( RAD ), COS( RAD ),TAN( RAD )

or:
100 FORMAT 110 FORMAT WRITE ( *, WRITE ( ( 1X, A3, 3( 2X, A7 ) ) ( 1X, I3, 3( 2X, F7.4 ) ) 100 ) 'Deg', 'Sin', 'Cos', 'Tan' *, 110 ) DEG, SIN( RAD ), COS( RAD ), TAN( RAD )

Writing to file:
OPEN ( 33, FILE = 'trig.out' ) ! open file for output WRITE ( 33, FMTHEAD ) 'Deg', 'Sin', 'Cos', 'Tan' WRITE ( 33, FMTDATA ) DEG, SIN( RAD ), COS( RAD ), TAN( RAD ) CLOSE ( 33 ) ! close file (tidiness is a virtue)

Fortran

Week 4 - 1

David Apsley

Example 1.2 Floating-point output.


PROGRAM POWER ! Program tabulates a power-series expansion for EXP(X) IMPLICIT NONE REAL, EXTERNAL :: NEW_EXP INTEGER :: NSTEP = 15 REAL :: XMIN = 0.0, XMAX = 3.0 REAL DELTAX REAL X INTEGER I ! power series for EXP ! ! ! ! ! number of steps interval limits step size current X value a counter

! Format specifiers CHARACTER (LEN=*), PARAMETER :: FMT1 = '( 1X, A4 , 2( 2X, A10 ) )' CHARACTER (LEN=*), PARAMETER :: FMT2 = '( 1X, F4.2, 2( 2X, 1PE10.3 ) )'

DELTAX = ( XMAX - XMIN ) / NSTEP WRITE ( *, FMT1 ) 'X', 'EXP', 'NEW_EXP' DO I = 0, NSTEP X = XMIN + I * DELTAX WRITE ( *, FMT2 ) X, EXP( X ), NEW_EXP( X ) END DO END PROGRAM POWER

! calculate step size ! write headers

! set X value ! write data

!===============================================

REAL FUNCTION NEW_EXP( X ) ! X X**2 X**3 ! Power series: NEW_EXP(X) = 1 + --- + ---- + ---- + ... ! 1! 2! 3! IMPLICIT NONE REAL, INTENT(IN) :: X INTEGER N REAL TERM REAL, PARAMETER :: TOLERANCE = 1.0E-07 ! argument of function ! number of a term ! a term in the series ! truncation level

! First term N = 0; TERM = 1;

NEW_EXP = TERM

! first term

! Add successive terms until they become negligible DO WHILE ( ABS( TERM ) > TOLERANCE ) ! criterion for continuing N = N + 1 ! index of next term TERM = TERM * X / N ! new term is a multiple of last NEW_EXP = NEW_EXP + TERM ! add to sum END DO END FUNCTION NEW_EXP

Fortran

Week 4 - 2

David Apsley

Example 1.3 Illustrating formatted READ, non-advancing i/o and the IOSTAT= specifier. Note: An input file text.dat is required: any favourite piece of literature will do!
PROGRAM ANALYSE_TEXT IMPLICIT NONE INTEGER :: IO = 0 ! holds i/o status INTEGER :: NLETTERS = 0 ! number of letters read INTEGER :: NWORDS = 0 ! number of words read CHARACTER CH, LAST_CH ! successive characters CHARACTER (LEN=*), PARAMETER :: ALPHABET = & 'ABCDEFGHIJKLMNOPQRSTUVWXYZabcdefghijklmnopqrstuvwxyz' CHARACTER, PARAMETER :: SPACE=' '

LAST_CH = SPACE ! Open the text file OPEN ( 10, FILE = 'text.dat' ) ! Read characters one-by-one until end of file is reached DO WHILE ( IO /= -1 ) ! IO=-1 means EOF ! Read one character READ ( 10, '( A1 )', IOSTAT = IO, ADVANCE = 'NO' ) CH IF ( IO == 0 ) THEN PRINT *, 'Character = ', CH ! a character has been read

! Is it a new word? IF (LAST_CH == SPACE .AND. CH /= SPACE ) NWORDS = NWORDS + 1 ! Is it a letter of the alphabet or something else? IF ( INDEX( ALPHABET, CH ) /= 0 ) NLETTERS = NLETTERS + 1 LAST_CH = CH ELSE PRINT *, 'IO = ', IO LAST_CH = SPACE END IF END DO ! update last character ! end of line or end of file

! Close the text file CLOSE (10)

! Output the analysis PRINT *, 'Number of letters = ', NLETTERS PRINT *, 'Number of words = ', NWORDS END PROGRAM ANALYSE_TEXT

Fortran

Week 4 - 3

David Apsley

2. Modules Example 2.1 Illustrating modules used to share related parameters and variables. Compilation and linking commands: ftn95 conversion.f95 ftn95 distance.f95 slink distance.obj conversion.obj conversion.f95
MODULE CONVERSION ! Length conversion factors IMPLICIT NONE REAL, REAL, REAL, REAL, PARAMETER PARAMETER PARAMETER PARAMETER :: :: :: :: MILES_TO_METRES YARDS_TO_METRES FEET_TO_METRES INCHES_TO_METRES = = = = 1609.0 0.9144 0.3048 0.0254

END MODULE CONVERSION

distance.f95
PROGRAM DISTANCE USE CONVERSION IMPLICIT NONE REAL METRES REAL AMOUNT CHARACTER UNITS ! distance in metres ! numerical quantity ! units (i-inches, f-feet, y-yards, m-miles) ! make conversion factors available

PRINT *, 'Input amount and units (i-inches, f-feet, y-yard, m-mile)' READ *, AMOUNT, UNITS SELECT CASE (UNITS) CASE ( 'i' , 'I' CASE ( 'f' , 'F' CASE ( 'y' , 'Y' CASE ( 'm' , 'M' END SELECT

); ); ); );

METRES METRES METRES METRES

= = = =

AMOUNT AMOUNT AMOUNT AMOUNT

* * * *

INCHES_TO_METRES FEET_TO_METRES YARDS_TO_METRES MILES_TO_METRES

PRINT *, 'Distance in metres = ', METRES END PROGRAM DISTANCE

Fortran

Week 4 - 4

David Apsley

Example 2.2 Illustrating modules as CONTAINers of useful routines. Compilation and linking commands: ftn95 physics.f95 ftn95 gas.f95 slink gas.obj physics.obj physics.f95
MODULE PHYSICS ! Physical constants and some useful subprograms IMPLICIT NONE REAL, REAL, REAL, REAL, REAL, REAL, REAL, REAL, PARAMETER PARAMETER PARAMETER PARAMETER PARAMETER PARAMETER PARAMETER PARAMETER :: :: :: :: :: :: :: :: SPEED_OF_LIGHT PLANCKS_CONSTANT GRAVITATIONAL_CONSTANT ELECTRON_MASS ELECTRON_CHARGE STEFAN_BOLTZMANN_CONSTANT IDEAL_GAS_CONSTANT AVOGADRO_NUMBER = = = = = = = = 3.00E+08 6.63E-34 6.67E-11 9.11E-31 1.60E-19 5.67E-08 8.31E+00 6.02E+23 ! ! ! ! ! ! ! ! (m/s) (J s) (N m2/kg2) (kg) (C) (W/m2/K4) (J/K) (/mol)

CONTAINS REAL FUNCTION PRESSURE( n, T, V ) ! Computes pressure by ideal gas law (pV=nRT) REAL n, T, V ! moles, temperature, volume PRESSURE = n * IDEAL_GAS_CONSTANT * T / V END FUNCTION PRESSURE END MODULE PHYSICS

gas.f95
PROGRAM IDEAL_GAS ! Program to test module <physics> USE PHYSICS IMPLICIT NONE REAL REAL REAL REAL REAL RMM MASS TEMPERATURE VOLUME MOLES ! ! ! ! ! relative molecular mass mass (kg) temperature (K) volume (m3) moles of gas ! access module

PRINT *, 'Input relative molecular mass' READ *, RMM PRINT *, 'Input mass(kg), temperature(K), volume(m3)' READ *, MASS, TEMPERATURE, VOLUME MOLES = 1000.0 * MASS / RMM ! calculate moles of gas

PRINT *, 'Pressure = ', PRESSURE( MOLES, TEMPERATURE, VOLUME ), 'Pa' END PROGRAM IDEAL_GAS

Fortran

Week 4 - 5

David Apsley

You might also like