Advanced Array Usage

Array Initialization

Arrays can be initialized to the same quantity by an array operation:

A=0.0 !equivalent to A(:)=0.0

For small arrays, an array constructor can be written.

I=[1,0,0,0]

The constructor can use the implied do construct:

X=[(real(i),i=1,100)]

If an array of characters is declared, then each element must be initialized to a string of the specified length. The compiler will not pad with blanks.

Array Slices

Subarrays, also known as slices, may be extracted using the colon operator.

REAL, DIMENSION(100)      :: A
REAL, DIMENSION(12)       :: B
INTEGER, DIMENSION(20,10) :: N
INTEGER, DIMENSION(20)    :: C
   ! Assign values to A and N
   B=A(1:12)
   C=N(:,i)  !ith column of N

The upper bound of the range is always included. If the first bound is omitted, it starts from 1. If the second bound is absent, the slice is extracted to the end of the range. A single colon : represents the full range along a dimension.

Allocatable Arrays

So far we have examined static arrays, whose size is fixed at compile time. Arrays may be sized at runtime by making them allocatable . They are declared with an ALLOCATABLE` attribute and a colon for each dimension.

REAL, ALLOCATABLE, DIMENSION(:)   :: A, B
REAL, ALLOCATABLE, DIMENSION(:,:) :: C

If any dimension is allocatable, all must be.

These arrays must be allocated before they are used, so their size must be known at runtime. More than one array may be allocated in a single ALLOCATE statement.

ALLOCATE(A(NMAX),B(MMAX),C(NMAX,MMAX))

Check whether an array is allocated with the intrinsic ALLOCATED(A)

if (allocated(A)) then
   do something
else
   allocate(A(some_size))
endif

or if we do not need to take any action if A is allocated:

if ( .not. allocated(A)) then
   allocate(A(some_size))

Advanced Array Indexing

Arrays can be addressed with arrays of integers (but not logicals).

integer, dimension(1)           :: maxtemp
real, dimension(365)            :: temps
character(len=5),dimension(365) :: dates

maxtemp=maxloc(temps)
print *, "maximum temp was at ",dates(maxtemp)

Conditionals with Arrays

Logical arrays can be assigned with conditionals derived from other arrays to construct masks. The maxval intrinsic finds the (first) maximum value in an array.

logical, dimension(365) ::is_max
integer                 :: day

   is_max=temps==maxval(temps)
   print *, 'Maximum temperature(s) were at'
   do day=1,size(is_max)
      if (is_max(day)) then
         write(*,advance='no'), dates(day)
      endif
   enddo
   write(*,*)

Example

Pulling the array indexing capabilities all together we have a complete program:

program arrayinds
integer, dimension(1)           :: maxtemp
integer, dimension(28)          :: feb
real,    dimension(365)         :: x, temps
integer, dimension(365)         :: nums
character(len=7),dimension(365) :: dates
character(len=3),dimension(12 ) :: months
integer, dimension(12 )         :: mons=[31,28,31,30,31,30,31,31,30,31,30,31]
character(len=3)                :: month
character(len=2)                :: day_of_month
integer                         :: i,m,mday,day
real, parameter                 :: pi=4.0*atan(1.0)

   months=['Jan','Feb','Mar','Apr','May','Jun','Jul','Aug','Sep','Oct','Nov', &
           'Dec']
   nums=[(real(i),i=1,365)]
   x=nums/365.
   ! Dates as characters
   day=0
   do m=1,12
       month=months(m)
       do mday=1,mons(m)
          day=day+1
          write(day_of_month,'(i2)') mday
          dates(day)=day_of_month//'-'//month
       enddo
   enddo
   !Very artificial temperatures (in deg C)
   temps=35.*sin(x*pi)
   print *, "Temperatures for February"
   feb=[(i,i=32,59)]
   write(*,*) temps(feb)
   maxtemp=maxloc(temps)
   print *, "Maximum temp was at ",dates(maxtemp)

end program

This code contains some features, such as string concatenation, that we will study later.

Exercises

  • 1 Download the program above. Add the code from the “Conditionals With Arrays” section appropriately. Compare your output to the maxloc (which returns an integer array of the indices of the maximum value).

  • 2 Make all arrays that should be the same size as temps allocatable, leaving temps static. Allocate all to the size and shape of the temps array. For convenience you may introduce an integer that represents the size of temps. This way we can accommodate data for a leap year by changing just the size of temps.

Example Solution

program arrayinds
integer, dimension(1)              :: maxtemp
integer, dimension(28)             :: feb
real,    dimension(365)            :: temps
real,    allocatable, dimension(:) :: x
integer, allocatable, dimension(:) :: nums
logical, allocatable, dimension(:) :: is_max
character(len=7),allocatable, dimension(:) :: dates
character(len=3),dimension(12 )    :: months
integer, dimension(12 )            :: mons=[31,28,31,30,31,30,31,31,30,31,30,31]
character(len=3)                   :: month
character(len=2)                   :: day_of_month
integer                            :: ndays
integer                            :: i,m,mday,day
real, parameter                    :: pi=4.0*atan(1.0)

   months=['Jan','Feb','Mar','Apr','May','Jun','Jul','Aug','Sep','Oct','Nov', &
           'Dec']

   ndays=size(temps)
   allocate(nums(ndays),x(ndays),dates(ndays),is_max(ndays))
   nums=[(real(i),i=1,size(temps))]
   x=nums/365.
   ! Dates as characters
   day=0
   do m=1,12
       month=months(m)
       do mday=1,mons(m)
          day=day+1
          write(day_of_month,'(i2)') mday
          dates(day)=day_of_month//'-'//month
       enddo
   enddo
   !Very artificial temperatures (in deg C)
   temps=35.*sin(x*pi)
   print *, "Temperatures for February"
   feb=[(i,i=32,59)]
   write(*,*) temps(feb)
   maxtemp=maxloc(temps)
   print *, "Maximum temp was at ",dates(maxtemp)

   is_max = temps==maxval(temps)
   print *, "Maximum temperature(s) were at"
   do day=1,size(temps)
      if (is_max(day)) then
         write(*,'(a)',advance='no') dates(day)
      endif
   enddo
   write(*,*)

end program

Previous
Next