The introduction of pointer variables brings Fortran 90 into the league of languages like Pascal and C. But they are quite different from, for example, pointers in C. In Fortran 90, a pointer variable does not contain any data itself and should not be thought of as an address. Instead, it should be thought of as a variable associated dynamically with or aliased to another data object where the data is actually stored - the target.
The use of pointers provides several benefits, of which the two most important are:
type [[,attribute]...] POINTER :: list of pointer variables
type [[,attribute]...] TARGET :: list of target variables
where
Thus, the statement
REAL,DIMENSION(:), POINTER :: p
declares a pointer, p, which can point to any rank one, default-real arrays.
But, the statement
REAL,DIMENSION(20), POINTER :: p
is an illegal statement, which is not allowed.
pointer => target
where pointer is a variable with the pointer attribute and target is a variable which has either the target attribute or the pointer attribute.
Once a pointer is set up as an alias of a target, its use in a situation where a value is expected (for example, as one of the operands of an operator) is as if it were the associated target, i.e., the object being pointed to.
The following code and figure illustrate some pointer assignment statements and their effects:
REAL, POINTER :: p1, p2
REAL, TARGET :: t1 = 3.4, t2 = 4.5
p1 => t1 ! p1 points to t1
p2 => t2 ! p2 points to t2
p2 => p1 ! p2 points to the target of p1
The first line here declares two variables p1 and p2 to be pointers to areas of memory able to store real variables. The second line declares t1 and t2 to be real variables and specifies that they might be targets of pointers.
The next two pointer assignment statements make p1 points to t1 and p2 point to t2, which results the following situation:
After the last pointer assignment statement is executed, the target of p2 is changed to that of p1, so that p1 and p2 are now both alias of t1 and leaves the value t2 unchanged:
Note that the statement
p2 => p1 + 4.3 ! illegal
is illegal because we cannot associate a pointer with an arithmetic expression.
REAL, POINTER :: p1, p2
REAL, TARGET :: t1 = 3.4, t2 = 4.5
p1 => t1 ! p1 points to t1
p2 => t2 ! p2 points to t2
p2 = p1 ! ordinary assignment, equivalent to t2 = t1
After the last ordinary assignment (versus pointer assignment) statement is executed, the situation is as follows:
Note that this assignment has exactly the same effect as
t2 = t1
since p1 is an alias of t1 and p2 is an alias of t2.
REAL, DIMENSION (:), POINTER :: pv1
REAL, DIMENSION (:, :), POINTER :: pv2
REAL, DIMENSION (-3:5), TARGET :: tv1
REAL, DIMENSION (5, 10), TARGET :: tv2
INTEGER, DIMENSION(3) :: v = (/ 4, 1, -3 /)
pv1 => tv1 ! pv1 aliased to tv1
pv1 => tv1(:) ! pv1 points to tv1 with section subscript
pv1 => tv2(4, :) ! pv1 points to the 4th row of tv1
pv2 => tv2(2:4, 4:8) ! pv2 points to a section of tv2
pv1 => tv1(1:5:2) ! pv1 points to a section of tv1
pv1 => tv1(v) ! invalid
There are several important points to observe:
NULLIFY(list of pointers)
The intrinsic function ASSOCIATED can be used to test the association status of a pointer with one argument or with two:
ASSOCIATED(p, [,t])
When t is absent, it returns the logical value .TRUE. if the pointer p is currently associated with a target and .FALSE. otherwise. If t is present and is a target variable, it returns .TRUE. if the pointer p is associated with t and .FALSE. otherwise. The second argument t may itself be a pointer, in which case it returns .TRUE. if both pointers are associated to the same target or disassociated and .FALSE. otherwise.
There is one restriction concerning the use of this function, that is the pointer argument must not have an undefined pointer association status. Therefore, it is recommended that a pointer should always be either associated with a target immediately after its declaration, or nullified by the NULLIFY statement to ensure its null status.
The following code shows the status of pointers at different stages:
REAL, POINTER :: p, q ! undefined association status
REAL, TARGET :: t = 3.4
p => t ! p points to t1
q => t ! q also points to t1
PRINT *, "After p => t, ASSOCIATED(p) = ", ASSOCIATED(p) ! .T.
PRINT *, "ASSOCIATED(p, q) = ", ASSOCIATED(p, q) ! .T.
NULLIFY(p)
PRINT *, "After NULLIFY(p), ASSOCIATED(p) = ", ASSOCIATED(p) ! .F.
PRINT *, "ASSOCIATED(p, q) = ", ASSOCIATED(p, q) ! .F.
...
p => t ! p points to t2
NULLIFY(p, q)
Note that the disassociation of p did not affect q even though they were both pointing at the same object. After being nullified, p can be associated again either with the same or different object later. The last line just illustrates that a NULLIFY statement can have more than one pointer argument.
REAL, POINTER :: p
REAL, DIMENSION (:, :), POINTER :: pv
INTEGER :: m, n
...
ALLOCATE (p, pv(m, n))
In this example, the pointer p is set to point to a dynamically allocated area of memory able to store a real variable, and the pointer pv to a dynamically allocated real array of size m by n.
The area of memory which was created by a pointer allocate statement can be released when no longer required by means of the DEALLOCATE statement:
DEALLOCATE(pv)
Here when the area of memory allocated for pv is deallocated, the association status of pv becomes null.
The general forms of the ALLOCATE and DEALLOCATE statements are
ALLOCATE(pointer[(dimension specification)]... [,STAT = status])
DEALLOCATE(pointer... [,STAT = status]
where pointer is a pointer variable, dimension specification is the specification of the extents for each dimension if the pointer variable has both the dimension and pointer attributes (array pointer), and status is an integer variable which will be assigned the value zero after a successful allocation/deallocation, or a positive value after an unsuccessful allocation/deallocation. Note that both statements can allocate/deallocate memory for more than one pointer.
The ability to create dynamic memory brings greater versatility and freedom to programming, but also brings its own problems if care is not taken. In particular there are two potential dangers which need to be avoided.
The first is the dangling pointer. Consider the following
...
REAL, POINTER :: p1, p2
ALLOCATE (p1)
p1 = 3.4
p2 => p1
...
DEALLOCATE (p1)
...
The pointers p1 and p2 both are alias of the same dynamic variable. After the execution of the DEALLOCATE statement, it is clear that p1 is disassociated and the dynamic variable to which it was pointing is destroyed. Since the dynamic variable that p2 was aliasing has disappeared, p2 becomes a dangling pointer and a reference to p2 will produce unpredictable results. In this case, the solution is to make sure that p2 is nullified after the deallocation.
The second is that of unreferenced storage. Consider the following
...
REAL, DIMENSION(:), POINTER :: p
ALLOCATE ( p(1000) )
...
If p is nullified or set to point to somewhere else, or the subprogram is exited (note that p has no SAVE attribute), without first deallocating it, there is no way to refer to that block of memory and so it can not be released. The solution is to deallocate a dynamic object before modifying a pointer to it.
... ! program unit which calls sub1 and sub2
INTERFACE ! interface block for sub2
SUBROUTINE sub2(b)
REAL, DIMENSION(:, :), POINTER :: b
END SUBROUTINE sub2
END INTERFACE
REAL, DIMENSION(:, :), POINTER :: p
...
ALLOCATE (p(50, 50))
CALL sub1(p)
CALL sub2(p)
...
SUBROUTINE sub1(a) ! a is not a pointer but an assumed shape array
REAL, DIMENSION(:, :) :: a
...
END SUBROUTINE sub1
SUBROUTINE sub2(b) ! b is a pointer
REAL, DIMENSION(:, :), POINTER :: b
...
DEALLCATE(b)
...
END SUBROUTINE sub2
The important points here are:
...
IMPLICIT NONE
INTEGER, DIMENSION(100) :: x
INTEGER, DIMENSION(:), POINTER :: p
...
p => gtzero(x)
...
CONTAINS
FUNCTION gtzero(a) ! function to get all values .gt. 0 from a
INTEGER, DIMENSION(:), POINTER :: gtzero
INTEGER, DIMENSION(:) :: a
INTEGER :: n
... ! find the number of values .gt. 0, n
IF (n == 0)
NULLIFY(gtzero)
ELSE
ALLOCATE (gtzero(n))
ENDIF
... ! put the found values into gt0
END FUNCTION gtzero
...
There are two points which need to be mentioned in the above example:
Suppose an array of pointers to reals is required. A derived type real_pointer can be defined, whose only component is a pointer to reals:
TYPE real_pointer
REAL, DIMENSION(:), POINTER :: p
END TYPE real_pointer
Then an array of variables of this type can be defined:
TYPE(real_pointer), DIMENSION(100) :: a
It is now possible to refer to the ith pointer by writing a(i)%p.
The following example shows each row of a lower-triangular matrix may be represented by a dynamic array of increasing size:
INTEGER, PARAMETER :: n=10
TYPE(real_pointer), DIMENSION(n) :: a
INTEGER :: i
DO i = 1, n
ALLOCATE (a(i)%p(i)) ! refer to the ith pointer by a(i)%p
END DO
Note that a(i)%p points to a dynamically allocated real array of size i and therefore this representation uses only half the storage of conventional two dimensional array.
In this section we will give a simple example to explain how to build a linked list. Note that tree or other dynamic data structures can be constructed similarly as linked list.
A pointer component of a derived type can point at an object of the same type; this enables a linked list to be created:
TYPE node
INTEGER :: value ! data field
TYPE (node), POINTER :: next ! pointer field
END TYPE node
As shown above, a linked list typically consists of objects of a derived type containing fields for the data plus a filed that is a pointer to the next object of the same type in the list. It is convenient to represent a linked list in diagrammatic form, as shown in following figure:
Conventionally, the first node in the list is referred to as the head of the list, while the last node is called the tail.
Consider the following example:
PROGRAM simple_linked_list
IMPLICIT NONE
TYPE node
INTEGER :: value ! data filed
TYPE (node), POINTER :: next ! pointer field
END TYPE node
INTEGER :: num
TYPE (node), POINTER :: list, current
! build up the list
NULLIFY(list) ! initially nullify list (empty)
DO
READ *, num ! read num from keyboard
IF (num == 0) EXIT ! until 0 is entered
ALLOCATE(current) ! create new node
current%value = num ! giving the value
current%next => list ! point to previous one
list => current ! update head of list
END DO
! transverse the list and print the values
current => list ! make current as alias of list
DO
IF (.NOT. ASSOCIATED(current)) EXIT ! exit if null pointer
PRINT *, current%value ! print the value
current => current%next ! make current alias of next node
END DO
END PROGRAM simple_linked_list
Firstly, we define the type of node which contains an integer value as a data field and a pointer component which can point to the next node.
Then two variables of this type are declared, list and current, where list will be used to point to the head of the list and current to a general node of the list.
The procedure of building up this linked list is illustrated progressively as follows:
Having built up the linked list, the next thing is to traverse it and print all the values:
! transverse the list and deallocate each node
current => list ! make current point to head of list
DO
IF (.NOT. ASSOCIATED(current)) EXIT ! exit if null pointer
list => current%next ! make list point to next node of head
DEALLOCATE(current) ! deallocate current head node
current => list ! make current point to new head
END DO
Note that the linked list built up stores the reading values in reverse order. If the order of reading values are to be preserved in the linked list, more housekeeping work is required, and this is left as an exercise.