next up previous contents
Next: FORTRAN 77 Callee Up: Programming Example Using F77-Callable Previous: Programming Example Using F77-Callable

HPF Caller

      PROGRAM EXAMPLE

      INTEGER, PARAMETER :: NX = 100, NY = 100
      REAL, DIMENSION(NX,NY) :: X
!HPF$ DISTRIBUTE(BLOCK,BLOCK) :: X
! Local subgrid parameters are declared per processor
! for a rank -two array
      INTEGER, DIMENSION(NUMBER_OF_PROCESSORS(),2) ::
      & LB, UB, LB_EMBED, UB_EMBED
!HPF$ DISTRIBUTE(BLOCK,*) :: LB, UB, LB_EMBED, UB_EMBED
! Define interfaces
      INTERFACE
        EXTRINSIC(F77_LOCAL) SUBROUTINE LOCAL1(
      &    LB1, UB1, LB_EMBED1, UB_EMBED1,
      &    LB2, UB2, LB_EMBED2, UB_EMBED2, X, X_DESC )
        INTEGER, DIMENSION(:) ::
      &    LB1, UB1, LB_EMBED1, UB_EMBED1,
      &    LB2, UB2, LB_EMBED2, UB_EMBED2
! X is passed twice, both times without local reordering.
! First, it is passed by reference for accessing array elements.
          REAL, DIMENSION(:,:), LAYOUT('HPF_ARRAY'),
      &         PASS_BY('*') :: X
! It is also passed by descriptor for use in F77 LOCAL
! LIBRARY subroutines only.
          REAL, DIMENSION(:,:), LAYOUT('HPF_ARRAY'),
      &         PASS_BY('HPF_HANDLE') :: X_DESC
!HPF$ DISTRIBUTE(BLOCK) :: LB1, UB1, LB_EMBED1, UB_EMBED1
!HPF$ DISTRIBUTE(BLOCK) :: LB2, UB2, LB_EMBED2, UB_EMBED2
!HPF$ DISTRIBUTE(BLOCK,BLOCK) :: X
          END
      END INTERFACE
! Initialize values
! ( Assume stride = 1 and no axis permutation )
      CALL HPF_SUBGRID_INFO( X, IERR,
      & LB=LB, LB_EMBED=LB_EMBED,
      & UB=UB, UB_EMBED=UB_EMBED)
      IF (IERR.NE.0) STOP 'ERROR!'
      CALL LOCAL1(
      & LB(:,1), UB(:,1), LB_EMBED(:,1), UB_EMBED(:,1),
      & LB(:,2), UB(:,2), LB_EMBED(:,2), UB_EMBED(:,2), X, X )
      END