The Queen's University of Belfast
QUBPCCParallel Computer Centre

[Next] [Previous] [Top]

Sources
Types
Control Structures


Sources, types
and control structures

Topics

Source form

Free source form

Example

PROGRAM free_source_form
! Long names with underscores

! No special columns
IMPLICIT NONE

! upper and lower case letters
REAL :: tx, ty, tz ! trailing comment

! Multiple statements per line
tx = 1.0; ty = 2.0; tz = tx * ty;

! Continuation on line to be continued
PRINT *, &
tx, ty, tz

END PROGRAM free_source_form

Specifications

type [[,attribute]... ::] entity list

PARAMETER, PUBLIC, PRIVATE,
ALLOCATABLE, POINTER, TARGET,
INTENT(inout), DIMENSION (extent-list),
OPTIONAL, SAVE, EXTERNAL,
INTRINSIC

Examples

! Integer variables:
INTEGER :: ia, ib

! Parameters:
INTEGER, PARAMETER :: n=100, m=1000

! Initialisation of variables:
REAL :: a = 2.61828, b = 3.14159

! Character variable of length 8:
CHARACTER (LEN = 8) :: ch

! Integer array with negative lower bound:
INTEGER, DIMENSION(-3:5, 7) :: ia

! Integer array using default dimension:
INTEGER,DIMENSION(-3:5, 7) :: ia, ib, ic(5, 5)

IMPLICIT NONE

Kind values

REAL

REAL (KIND = wp) :: ra ! or
REAL(wp) :: ra
const = 1.0_wp

REAL

INTEGER, PARAMETER :: idp = KIND(1.0D0)
REAL (KIND = idp) :: ra

ra is declared as `double precision', but this is system dependent.

INTEGER, PARAMETER :: &
i10 = SELECTED_REAL_KIND(10, 200)
REAL (KIND = i10) :: a, b, c

a, b and c have at least 10 decimal digits of precision and the exponent range 200.

INTEGER

...
INTEGER, PARAMETER :: &
i8 = SELECTED_INT_KIND(8)
INTEGER (KIND = i8) :: ia, ib, ic
...

ia, ib and ic can have values between -108 and +108 at least (if permitted by processor).

Intrinsics

INTEGER, PARAMETER :: &
i8 = SELECTED_INT_KIND(8)
INTEGER (KIND = i8) :: ia
PRINT *, HUGE(ia), KIND(ia)

This will print the largest integer available for this integer type (2147483674), and its kind value.

INTEGER, PARAMETER :: &
i10 = SELECTED_REAL_KIND(10, 200)
REAL (KIND = i10) :: a
PRINT *, RANGE(a), PRECISION(a), KIND(a)

This will print the exponent range, the decimal digits of precision and the kind value of a.

Derived types

Examples

TYPE vreg
CHARACTER (LEN = 1) :: year
INTEGER :: number
CHARACTER (LEN = 3) :: place
END TYPE vreg
TYPE (vreg) mycar1, mycar2 mycar1 = vreg(`L', 240, 'VPX') mycar2%year = `R' TYPE (vreg), DIMENSION (n) :: mycars TYPE household
CHARACTER (LEN = 30) :: name
CHARACTER (LEN = 50) :: address
TYPE (vreg) :: car
END TYPE household

TYPE (household) :: myhouse
myhouse%car%year = `R'

Control structures

IF

[name:] IF (logical expression) THEN
block
[ELSE IF ( logical expression) THEN [name]
block]...
[ELSE [name]
block]
END IF [name]
select: IF (i < 0) THEN
CALL negative
ELSE IF (i == 0) THEN select
CALL zero
ELSE select
CALL positive
END IF select

DO loops

[name:] DO [control clause]
block
END DO [name]
count = initial, final [,inc] WHILE (logical expression) rows: DO i = 1, n
cols: DO j = 1, m
a(i, j) = i + j
END DO cols
END DO rows
true: DO WHILE (i <= 100)
...
body of loop
...
END DO true
outer: DO i = 1, n
middle: DO j = 1, m
inner: DO k = 1, l
IF (a(i,j,k) < 0.0) EXIT outer ! leave loops
IF (j == 5) CYCLE middle ! set j = 6
IF (i == 5) CYCLE ! skip rest of inner
...
END DO inner
END DO middle
END DO outer
DO
READ (*, *) x
IF (x < 0) EXIT
y = SQRT(x)
...
END DO

Notice that this form can have the same effect as a DO WHILE loop.

CASE construct

[name:] SELECT CASE (expression)
[CASE (selector) [name]
block]
...
END SELECT [name]
colour: SELECT CASE (ch)
CASE (`C', `D', `G':'M')
colour = `red'
CASE (`X':)
colour = `green'
CASE DEFAULT
colour = `blue'
END SELECT colour

[Next] [Previous] [Top]
All documents are the responsibility of, and copyright, © their authors and do not represent the views of The Parallel Computer Centre, nor of The Queen's University of Belfast.
Maintained by Alan Rea, email A.Rea@qub.ac.uk
Generated with CERN WebMaker