The Queen's University of Belfast
Parallel Computer Centre

[Next] [Previous] [Top]

11 Pointer Variables


11.1 What are Pointers?

A pointer variable, or simply a pointer, is a new type of variable which may reference the data stored by other variables (called targets) or areas of dynamically allocated memory.

Pointers are a new feature to the Fortran standard and bring Fortran 90 into line with languages like C. The use of pointers can provide:

Pointers are an advanced feature of any language. Their use allows programmers to implement powerful algorithms and tailor the storage requirements exactly to the size of the problem in hand.

11.1.1 Pointers and targets

Pointers are best thought of as variables which are dynamically associated with (or aliased to) some target data. Pointers are said to `point to' their targets and valid targets include:

Pointers may take advantage of dynamic storage but do not require the ALLOCATABLE attribute. The ability to allocate and deallocate storage is an inherent property of pointer variables.

11.2 Specifications

The general form for pointer and target declaration statements are:

type, POINTER [,attr] :: variable list

type, TARGET [,attr] :: variable list

Where:

A pointer must have the same data type and rank as its target. For array pointers the declaration statement must specify the rank but not the shape (i.e. the bounds or extend of the array). In this respect array pointers are similar to allocatable arrays.

For example, the following three pairs of statements, all declare pointers and one or more variables which may be targets:

REAL, POINTER :: pt1

REAL, TARGET :: a, b, c, d, e

INTEGER, TARGET :: a(3), b(6), c(9)

INTEGER, DIMENSION(:), POINTER :: pt2

INTEGER, POINTER :: pt3(:,:)

INTEGER, TARGET :: b(:,:)

Note that the following is an examples of an illegal pointer declaration:

REAL, POINTER, DIMENSION(10) :: pt !illegal

The POINTER attribute is incompatible with the ALLOCATABLE, EXTERNAL, INTENT, INTRINSIC, PARAMETER and TARGET attributes. The TARGET attribute is incompatible with the EXTERNAL, INTRINSIC, PARAMETER and POINTER attributes.

11.3 Pointer assignment

There are two operators which may act on pointers:

To associate a pointer with a target use the pointer assignment operator (=>):

pointer => target

Where pointer is a pointer variable and target is any valid target. pointer may now be used as an alias to the data stored by target. The pointer assignment operator also allocates storage required by the pointer.

To change the value of a pointer's target (just like changing the value of a variable) use the usual assignment operator (=). This is just as it would be for other variable assignment with a pointer used as an alias to another variable.

The following are examples of pointer assignment:

INTEGER, POINTER :: pt

INTEGER, TARGET :: x=34, y=0

...

pt => x ! pt points to x

y = pt ! y equals x

pt => y ! pt points to y

pt = 17 ! y equals 17

The declaration statements specify a three variables, pt is an integer pointer, while x and y are possible pointer targets. The first executable statement associates a target with pt. The second executable statement changes the value of y to be the same as pt's target, this would only be allowed when pt has an associated target. The third executable statement re-assigns the pointer to another target. Finally, the fourth executable statement assigns a new value, 17, to pt's target (not pt itself!). The effect of the above statements is illustrated below.



It is possible to assign a target to a pointer by using another pointer. For example:

REAL, POINTER :: pt1, pt2

...

pt2 => pt1 !legal only if pt1 has an associated target

Although this may appear to be a pointer pointing to another pointer, pt2 does not point to pt1 itself but to pt1's target. It is wrong to think of `chains of pointers', one pointing to another. Instead all pointers become associated with the same target.

Beware, of using the following statements, they are both illegal:

pt1 => 17 !constant expression is not valid target

pt2 => pt1 + 3 !arithmetic expression is not valid target

11.3.1 Dereferencing

Where a pointer appears as an alias to a variable it is automatically dereferenced; that is the value of the target is used rather than the pointer itself. For a pointer to be dereferenced in this way requires that it be associated with a target.

Pointer are automatically dereferenced when they appear:

For example:

pt => a

b = pt !b equals a, pt is dereferenced

IF( pt<0 ) pt=0 !pt dereferenced twice

WRITE(6,*) pt !pt's target is written

READ(5,*) pt !value stored by pt's target

11.4 Pointer association status

Pointers may be in one of three possible states:

A pointer may become disassociated through the NULLIFY statement:

NULLIFY( list of pointers )

A pointer that has been nullified may be thought of as pointing `at nothing'.

The status of a pointer may be found using the intrinsic function:

ASSOCIATED ( list of pointers [,TARGET] )

The value returned by ASSOCIATED is either .TRUE. or .FALSE. When TARGET is absent, ASSOCIATED returns a value .TRUE. if the pointer is associated with a target and .FALSE. if the pointer has been nullified. When TARGET is present ASSOCIATED reports on whether the pointer points to the target in question. ASSOCIATED returns a value .TRUE. if the pointer is associated with TARGET and .FALSE. if the pointer points to another target or has been nullified.

It is an error to test the status of an undefined pointer, therefore it is good practice to nullify all pointers that are not immediately associated with a target after declaration.

The following example shows the use of the ASSOCIATED function and the NULLIFY statement:

REAL, POINTER :: pt1, pt2 !undefined status

REAL, TARGET :; t1, t2

LOGICAL :: test

pt1 => t1 !pt1 associated

pt2 => t2 !pt2 associated

test = ASSOCIATED( pt1 ) ! .T.

test = ASSOCIATED( pt2 ) ! .T.

...

NULLIFY( pt1 ) !pt1 disassociated

test = ASSOCIATED( pt1 ) ! .F.

test = ASSOCIATED( pt1, pt2 ) ! .F.

test = ASSOCIATED( pt2, TARGET=t2) ! .T.

test = ASSOCIATED( pt2, TARGET=t1) ! .F.

NULLIFY( pt1, pt2) !disassociated

The initial undefined status of the pointers is changed to associated by pointer assignment, there-after the ASSOCIATED function returns a value of .TRUE. for both pointers. Pointer pt1 is then nullified and its status tested again, note that more than one pointer status may be tested at once. The association status of pt2 with respect to a target is also tested. Finally both pointers are nullified in the same (last) statement.

11.5 Dynamic storage

As well as pointing to existing variables which have the TARGET attribute, pointers may be associated with blocks of dynamic memory. This memory is allocated through the ALLOCATE statement which creates an un-named variable or array of the specified size, and with the data type, rank, etc. of the pointer:

REAL, POINTER :: p, pa(:)

INTEGER :: n=100

...

ALLOCATE( p, pa(n) )

...

DEALLOCATE( p, pa )

In the above example p points to an area of dynamic memory and can hold a single, real number and pa points to a block of dynamic memory large enough to store 100 real numbers. When the memory is no longer required it may be deallocated using the DEALLOCATE statement. In this respect pointers behave very much like allocatable arrays.

11.5.1 Common errors

Allocating storage to pointers can provide a great degree of flexibility when programming, however care must be taken to avoid certain programming errors:

INTEGER, POINTER :: pt(:)

...

ALLOCATE( pt(25) )

NULLIFY( pt ) !wrong

Since the pointer is the only way to reference the allocated storage (i.e. the allocated storage has no associated variable name other than the pointer) reassigning the pointer means the allocated storage can no longer be released. Therefore all allocated storage should be deallocated before modifying the pointer to it.

REAL, POINTER :: p1, p2

...

ALLOCATE( p1 )

p2 => p1

DEALLOCATE( p1 ) !wrong

In the above example p2 points to the storage allocated to p1, however when that storage is deallocated p2 no longer has a valid target and its state becomes undefined. In this case dereferencing p2 would produce unpredictable results.

Programming errors like the above can be avoided by making sure that all pointers to a defunked target are nullified.

11.6 Array pointers

Pointers may act as dynamic aliases to arrays and array sections, such pointers are called array pointers. Array pointers can be useful when a particular section is referenced frequently and can save copying data. For example:

REAL, TARGET :: grid(10,10)

REAL, POINTER :: centre(:,:), row(:)

...

centre => grid(4:7,4:7)

row => grid(9,:)



An array pointer can be associated with the whole array or just a section. The size and extent of an array pointer may change as required, just as with allocatable arrays. For example:

centre => grid(5:5,5:6) !inner 4 elements of old centre

Note, an array pointer need not be deallocated before its extent or bounds are redefined.

INTEGER, TARGET :: list(-5:5)

INTEGER, POINTER :: pt(:)

INTEGER, DIMENSION(3) :: v = (/-1,4,-2/)

...

pt => list !note bounds of pt

pt => list(:) !note bounds of pt

pt => list(1:5:2)

pt => list( v ) !illegal



The extent (or bounds) of an array section are determined by the type of assignment used to assign the pointer. When an array pointer is aliased with an array the array pointer takes its extent form the target array; as with pt => list above, both have bounds -5:5. If the array pointer is aliased to an array section (even if the section covers the whole array) its lower bound in each dimension is 1; as with pt => list(:) above, pt's extent is 1:11 while list's extent is -5:5. So pt(1) is aliased to list(-5), pt(2) to list(-4), etc.

It is possible to associate an array pointer with an array section defined by a subscript triplet. It is not possible to associate one with an array section defined with a vector subscript, v above. The pointer assignment pt => list(1:5:2) is legal with pt(1) aliased to list(1), pt(2) aliased to list(3) and pt(3) aliased to list(5).

11.7 Derived data types

Pointers may be a component of a derived data type. They can take the place of allocatables arrays within a derived data type, or act as pointers to other objects, including other derived data types:

The dynamic nature of pointer arrays can provide varying amounts of storage for a derived data type:

TYPE data

REAL, POINTER :: a(:)

END TYPE data

TYPE( data ) :: event(3)

DO i=1,3

READ(5,*) n !n varies in loop

ALLOCATE( event(i)%a(n) )

READ(5,*) event(i)%a

END DO

The number of values differs for each event, the size of the array pointer depends on the input value n. When the data is no longer required the pointer arrays should be deallocated:

DO i=1,3

DEALLOCATE( event(i)%a )

END DO

11.7.1 Linked lists

Pointers may point to other members of the same data type, and in this way create `linked lists'. For example consider the following data type:

TYPE node

REAL :: item

TYPE( node ), POINTER :: next

END TYPE node

The derived type node contains a single object item (the data in the list) and a pointer next to another instance of node. Note the recursion-like property in the declaration allowing the pointer to reference its own data type.

Linked lists are a very powerful programming concept, their dynamic nature means that they may grow or shrink as required. Care must be taken to ensure pointers are set up and maintained correctly, the last pointer in the list is usually nullified. Details of how to implement, use and manipulate a linked list can be found in some of the reading material associated with these notes.

11.8 Pointer arguments

Just like other data types, pointers may be passed as arguments to procedures. There are however a few points to remember when using pointers as actual or dummy arguments:

When both the actual and dummy arguments are pointers, the target (if there is one) and association status is passed on call and again on return. It is important to ensure that a target remains valid when returning from a procedure (i.e. the target is not a local procedure variable), otherwise the pointer is left `dangling'.

When the actual argument is a pointer and the corresponding dummy argument is not, the pointer is dereferenced and it is the target that is copied to the dummy argument. On return the target takes the value of the dummy argument. This requires the actual argument to be associated with a target when the procedure is referenced.

For example:

PROGRAM prog

INTERFACE !needed for external subroutine

SUBROTINE suba( a )

REAL, POINTER :: a(:)

END SUBROUTINE suba

END INTERFACE

REAL, POINTER :: pt(:)

REAL, TARGET :: data(100)

...

pt => data

CALL suba( pt )

CALL subb( pt )

...

CONTAINS

SUBROUTINE subb( b ) !internal

REAL, DIMENSION(:) :: b !assumed shape of 100

...

END SUBROUTINE subb

END PROGRAM prog

SUBROUTINE suba( a ) !external subroutine

REAL, POINTER :: a(:) !a points to data

...

END SUBROUTINE suba

It is not possible for a non-pointer actual argument to correspond with a pointer dummy argument.

11.9 Pointer functions

Functions may return pointers as their result. This is most useful where the size of the result depends on the function's calculation. Note that:

For example:

INTERFACE

FUNCTION max_row ( a )

REAl, TARGET :: a(:,:)

REAL, POINTER :: max_row(:)

END FUNCTION max_row

END INTERFACE

REAL, TARGET :: a(3,3)

REAL, POINTER :: p(:)

...

p => max_row ( a )

...

FUNCTION max_row ( a ) !external

REAL, TARGET :: a(:,:)

REAL, POINTER :: max_row(:) !function result

INTEGER :: location(2)

location = MAXLOC( a ) !row and column of max value

max_row => a(location(1),:) !pointer to max row

END FUNCTION max_row

Here the external function max_row returns the row of a matrix containing the largest value. The pointer result is only allowed to point to the dummy argument a because it is declared as a target, (otherwise it would have been a local array and left the pointer dangling on return). Notice the function result is used on the right hand side of a pointer assignment statement. A pointer result may be used as part of an expression in which case it must be associated with a target.

11.10 Exercises

  1. Write a declaration statement for each of the following pointers and their targets:

    (a) A pointer to a single element of an array of 20 integers.

    (b) A pointer to a character string of length 10.

    (c) An array pointer to a row of a 10 by 20 element real array.

    (d) A derived data type holding a real number three pointers to neighbouring nodes, left, right and up (this kind of derived data structure may be used to represent a binary tree).

  2. For the pointer and target in the following declarations write an expression to associate the pointer with:

    (a) The first row of the target.

    (b) A loop which associates the pointer with each column of the target in turn.

    REAL, POINTER :: pt(:)

    REAL, TARGET, DIMENSION(-10:10, -10:10) :: a

  3. Write a program containing an integer pointer and two targets. Nullify and report the initial status of the pointer (using the ASSOCIATED intrinsic function). Then associate the pointer with each of the targets in turn and output their values to the screen. Finally ensure the pointer ends with the status `not currently associated'.

  4. Write a program containing a derived data type. The data type represents different experiments and should hold the number of reading taken in an experiment (an integer) and values for each of the readings (real array pointer).

    Read in the number and values for a set of experimental readings, say 4, and output their mean. Deallocate all pointers before the program finishes.

  5. Write an internal function that takes a single rank one, integer array as an argument and returns an array pointer to all elements with non-zero values as a result. The function will need to count the number of zero's in the array (use the COUNT intrinsic), allocate the required storage and copy each non-zero value into that storage. Write a program to test the function.


[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