next up previous contents
Next: Vector-valued Subscripts Up: Arrays Previous: Masked Assignment - Where

 

Masked Assignment - Where Construct

Masked assignment may also be performed by a WHERE construct:

    WHERE(A > 0.0)
      B = LOG(A)
      C = SQRT(A)
    ELSEWHERE
      B = 0.0
    ENDWHERE

the effect of this code block is to perform the assignments B(j,k) = LOG(A(j,k)) and C(j,k) = SQRT(A(j,k) wherever (A(j,k) > 0.0) is .TRUE.. For the cases where the mask is .FALSE. the assignments in the ELSEWHERE block are made instead. Note that the WHERE ... END WHERE is not a control construct and cannot currently be nestedgif.

In all the above examples the mask, (the logical expression,) must conform to the implied shape of each assignment in the body, in other words, in the above example all arrays must all conform.

The execution sequence is as follows: evaluate the mask, execute the WHERE block (in full) then execute the ELSEWHERE block. The separate assignment statements are executed sequentially but the individual elemental assignments within each statement are (conceptually) executed in parallel. It is not possible to have a scalar on the LHS in a WHERE and all statements must be array assignments.

Consider the following example from the Fortran 90 standard (pp296-298).

The code is a 3-D Monte Carlo simulation of state transition. Each gridpoint is a logical variable whose value can be interpreted as spin-up or spin-down. The transition between states is governed by a local probabilistic process where all points change state at the same time. Each spin either flips to the opposite state or not depending on the state of its six nearest neighbours. Gridpoints on the edge of the cube are defined by cubic periodicity -- in other words the grid is taken to be replicated in all dimensions in space.

      MODULE Funkt
      CONTAINS
       FUNCTION RAND (m)
        INTEGER m
        REAL, DIMENSION(m,m,m) :: RAND
         CALL RANDOM_NUMBER(HARVEST = RAND)
        RETURN
       END FUNCTION RAND
      END MODULE Funkt

      PROGRAM TRANSITION
      USE Funkt
      IMPLICIT NONE
       INTEGER, PARAMETER :: n = 16
       INTEGER            :: iterations, i
       LOGICAL, DIMENSION(n,n,n) :: ising,     flips
       INTEGER, DIMENSION(n,n,n) :: ones,      count
       REAL, DIMENSION(n,n,n)    :: threshold
       REAL, DIMENSION(6)        :: p

       p = (/ 0.4, 0.5, 0.6, 0.7, 0.8, 0.9 /)

       iterations  = 10
       ising = RAND(n) .LE. 0.5

       DO i = 1,iterations
        ones = 0
        WHERE (ising) ones = 1
        count = CSHIFT(ones, -1, 1) + CSHIFT(ones, 1, 1) &
              + CSHIFT(ones, -1, 2) + CSHIFT(ones, 1, 2) &
              + CSHIFT(ones, -1, 3) + CSHIFT(ones, 1, 3)
        WHERE (.NOT.ising) count = 6 - count
        threshold = 1.0
        WHERE (count == 4) threshold = p(4)
        WHERE (count == 5) threshold = p(5)
        WHERE (count == 6) threshold = p(6)
        flips = RAND(n) .LE. threshold
        WHERE (flips) ising = .NOT. ising
       ENDDO
      END PROGRAM TRANSITION

Note CSHIFT performs a circular shift on an array, for example, if

displaymath27984

then

   CSHIFT(A,-1)

is A shifted one place to the left with the left-most number wrapping around to the right,

displaymath27985

and is A shifted one place to the right

   CSHIFT(A,1)

is

displaymath27986

It is also possible to specify a dimension for 2D and upward arrays. If

displaymath27987

then

   CSHIFT(B,1,1)

shifts the array one position in dimension 1 (downwards)

displaymath27988

and

   CSHIFT(B,1,2)

displaymath27989

and so on.

Now try this question gif

Return to corresponding overview page gif


next up previous contents
Next: Vector-valued Subscripts Up: Arrays Previous: Masked Assignment - Where

©University of Liverpool, 1997
Wed May 28 20:20:27 BST 1997
Not for commercial use.