File: a.18.1.f90

package info (click to toggle)
gcc-avr 1%3A5.4.0%2BAtmel3.6.2-1
  • links: PTS, VCS
  • area: main
  • in suites: bullseye
  • size: 589,872 kB
  • sloc: ansic: 2,775,581; ada: 756,757; cpp: 723,977; f90: 117,673; asm: 66,898; makefile: 62,755; xml: 44,466; sh: 29,549; exp: 23,315; objc: 15,216; fortran: 10,901; pascal: 4,185; python: 4,093; perl: 2,969; awk: 2,811; ml: 2,385; cs: 879; yacc: 316; lex: 198; haskell: 112; lisp: 8
file content (59 lines) | stat: -rw-r--r-- 1,741 bytes parent folder | download | duplicates (4)
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
! { dg-do run }
! { dg-options "-ffixed-form" }
      REAL FUNCTION FN1(I)
        INTEGER I
        FN1 = I * 2.0
        RETURN
      END FUNCTION FN1

      REAL FUNCTION FN2(A, B)
        REAL A, B
        FN2 = A + B
        RETURN
      END FUNCTION FN2

      PROGRAM A18
      INCLUDE "omp_lib.h"     ! or USE OMP_LIB
      INTEGER ISYNC(256)
      REAL    WORK(256)
      REAL    RESULT(256)
      INTEGER IAM, NEIGHBOR
!$OMP PARALLEL PRIVATE(IAM, NEIGHBOR) SHARED(WORK, ISYNC) NUM_THREADS(4)
          IAM = OMP_GET_THREAD_NUM() + 1
          ISYNC(IAM) = 0
!$OMP BARRIER
!     Do computation into my portion of work array
          WORK(IAM) = FN1(IAM)
!     Announce that I am done with my work.
!     The first flush ensures that my work is made visible before
!     synch. The second flush ensures that synch is made visible.
!$OMP FLUSH(WORK,ISYNC)
       ISYNC(IAM) = 1
!$OMP FLUSH(ISYNC)

!      Wait until neighbor is done. The first flush ensures that
!      synch is read from memory, rather than from the temporary
!      view of memory. The second flush ensures that work is read
!      from memory, and is done so after the while loop exits.
       IF (IAM .EQ. 1) THEN
            NEIGHBOR = OMP_GET_NUM_THREADS()
        ELSE
            NEIGHBOR = IAM - 1
        ENDIF
        DO WHILE (ISYNC(NEIGHBOR) .EQ. 0)
!$OMP FLUSH(ISYNC)
        END DO
!$OMP FLUSH(WORK, ISYNC)
        RESULT(IAM) = FN2(WORK(NEIGHBOR), WORK(IAM))
!$OMP END PARALLEL
        DO I=1,4
          IF (I .EQ. 1) THEN
                NEIGHBOR = 4
          ELSE
                NEIGHBOR = I - 1
          ENDIF
          IF (RESULT(I) .NE. I * 2 + NEIGHBOR * 2) THEN
            CALL ABORT
          ENDIF
        ENDDO
        END PROGRAM A18