3.2.5 Program Example with PCF Directives

The following program example shows the use of the PARALLEL REGION and the PARALLEL DO directives:

        PROGRAM ATIMESB

        PARAMETER M=512, N=512, P=512

        REAL time1,time2
        REAL*8 A,B,C
        DIMENSION A(1:M,1:N), B(1:N,1:P), C(1:M,1:P)

C Initialize the matrices

C*KAP* PARALLEL REGION SHARED (A,B) LOCAL (J,I)
C*KAP* PARALLEL DO

        DO 10 J=1,N
          DO 10 I=1,M
          A(I,J) = 1.5
10      CONTINUE

C*KAP* PARALLEL DO

        DO 20 J=1,P
          DO 20 I=1,N
          B(I,J) = 3.0
20      CONTINUE

C*KAP* END PARALLEL REGION

C Compute C = A * B

        CALL CSETTIME()
        time1 = CTIMEC()
        CALL MATMUL(A, M, B, N, C, P)
        time2 = CTIMEC()
        write(*,*)'elapsed time in seconds is:',(time1-time2)
        END

        SUBROUTINE MATMUL(A, LDA, B, LDB, C, LL)
        REAL A(LDA,LDB), B(LDB,LL), C(LDA,LL)
        INTEGER LDA,LDB,LL

C*KAP* PARALLEL REGION SHARED (A,LDA,B,LDB,C,LL) LOCAL (J,K,I)

C*KAP* PARALLEL DO
        DO 20 J=1,LL
          DO 20 I=1,LDA
          C(I,J) =0.0
            DO 20 K=1,LDB
            C(I,J) = C(I,J) + ( A(I,K) * B(K,J) )
20      CONTINUE

C*KAP* END PARALLEL REGION
        RETURN

        END


Previous Page | Next Page | Contents | Index |
Command-Line Qualifiers