 
An array can certainly be passed to a function or a subroutine for further
processing.  Just recall that an array has
three components: a name, a type and an extent.
For the first two, they are similar to passing a variable, and the third one
can be made available when declaring an array formal argument.  However,
the problem is that since an extent consists of a lower bound and an upper
bound, in order to declare an array formal argument correctly, these
two bounds must also be passed.  
 
Now, the array formal arguments in subroutine First() have identical extents as their corresponding actual arguments in the main program.
PROGRAM  Example
   IMPLICIT  NONE
   INTEGER, PARAMETER                          :: LOWER_BOUND = 20
   INTEGER, PARAMETER                          :: UPPER_BOUND = 50
   INTEGER, DIMENSION(LOWER_BOUND:UPPER_BOUND) :: Data
   REAL, DIMENSION(1:LOWER_BOUND)              :: Values
   LOGICAL, DIMENSION(21:UPPER_BOUND)          :: Answers
      ..........
   CALL  First(Data, Value, Answers, LOWER_BOUND, UPPER_BOUND, 21)
      ..........
CONTAINS
   SUBROUTINE  First(x, y, z, Lower, Upper, LL)
      IMPLICIT  NONE
      INTEGER, INTENT(IN)                         :: Lower
      INTEGER, INTENT(IN)                         :: Upper
      INTEGER, INTENT(IN)                         :: LL
      INTEGER, DIMENSION(Lower:Upper), INTENT(IN) :: x
      REAL, DIMENSION(1:Lower), INTENT(OUT)       :: y
      LOGICAL, DIMENSION(LL:Upper), INTENT(INOUT) :: z
            ..........
   END SUBROUTINE  First
END PROGRAM   Example
     Data() is an array of 1000 elements. But, when it is read in with the first two READ(*,*)s, the actual number of elements may not be 1000 and in fact it could be very small, say 10! Therefore, when function Sum() is used to calculate the sum of all of these values, we need three actual arguments rather than two. The first passes the array, the second passes the actual size, and the third passes the extent.
For function Sum(), n receives the actual number of values in an array whose extent is 1:SIZE, where SIZE is received via the third formal argument.
PROGRAM  Test
   IMPLICIT  NONE
   INTEGER, PARAMETER          :: MAX_SIZE = 1000
   REAL, DIMENSION(1:MAX_SIZE) :: Data
   INTEGER                     :: ActualSize
   INTEGER                     :: i
   READ(*,*) ActualSize
   READ(*,*) (Data(i), i=1, ActualSize)
   WRITE(*,*) "Sum = ", Sum(Data, ActualSize, MAX_SIZE)
CONTAINS
   REAL FUNCTION  Sum(x, n, SIZE)
      IMPLICIT  NONE
      INTEGER, INTENT(IN)                 :: SIZE, n
      REAL, DIMENSION(1:SIZE), INTENT(IN) :: x
      REAL                                :: Total
      INTEGER                             :: i
      Total = 0.0
      DO i = 1, n
         Total = Total + x(i)
      END DO
      Sum = Total
   END FUNCTION  Sum
END PROGRAM  Test
     
PROGRAM  Elements
   IMPLICIT  NONE
   INTEGER, PARAMETER         :: BOUND_1 = 100
   INTEGER, PARAMETER         :: BOUND_2 = BOUND_1 - 2
   REAL, DIMENSION(1:BOUND_1) :: Input
   REAL, DIMENSION(1:BOUND_2) :: Avg
   INTEGER                    :: n, i
   READ(*,*) n, (Input(i), i=1, n)
   DO i = 1, n-2
      Avg(i) = Average(Input(i), Input(i+1), Input(i+2))
   END
   WRITE(*,*)  (Avg(i), i=1, n-2)
CONTAINS
   REAL FUNCTION  Average(a, b, c)
      IMPLICIT  NONE
      REAL, INTENT(IN) :: a, b, c
      Average = (a + b + c)/3.0
   END FUNCTION  Average
END PROGRAM Elements
          Array Input() and Avg() have extents 1:100 and
          1:98 (i.e., two elements less than that of
          Input()), respectively.  The READ(*,*) statement reads
          in the actual number of elements and the input data.
          The DO-loop only iterates n-2 times. For iteration i, Input(i), Input(i+1) and Input(i+2) are sent to function Average(). Thus, formal arguments a, b and c receive Input(i), Input(i+1) and Input(i+2), respectively. Function Average() returns the average of these three elements. The result is then stored in Avg(i).
In summary, Avg(1) contains the average of Input(1), Input(2) and Input(3); Avg(2) contains the average of Input(2), Input(3) and Input(4); Avg(3) contains the average of Input(3), Input(4) and Input(5); and so on.
 
SUBROUTINE  Bad(x, m, n)
   IMPLICIT  NONE
   INTEGER, INTENT(INOUT)                 :: m, n
   INTEGER, DIMENSION(m:n), INTENT(INOUT) :: x
        ..........
   m = .....        ! BAD MOVE
   n = .....        ! BAD MOVE
END SUBROUTINE  Bad