File: collectives_3.f90

package info (click to toggle)
gcc-arm-none-eabi 15%3A14.2.rel1-1
  • links: PTS, VCS
  • area: main
  • in suites: forky, sid, trixie
  • size: 1,099,328 kB
  • sloc: cpp: 3,627,108; ansic: 2,571,498; ada: 834,230; f90: 235,082; makefile: 79,231; asm: 74,984; xml: 51,692; exp: 39,736; sh: 33,298; objc: 15,629; python: 15,069; fortran: 14,429; pascal: 7,003; awk: 5,070; perl: 3,106; ml: 285; lisp: 253; lex: 204; haskell: 135
file content (136 lines) | stat: -rw-r--r-- 3,998 bytes parent folder | download | duplicates (3)
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
60
61
62
63
64
65
66
67
68
69
70
71
72
73
74
75
76
77
78
79
80
81
82
83
84
85
86
87
88
89
90
91
92
93
94
95
96
97
98
99
100
101
102
103
104
105
106
107
108
109
110
111
112
113
114
115
116
117
118
119
120
121
122
123
124
125
126
127
128
129
130
131
132
133
134
135
136
! { dg-do run }
!
! CO_BROADCAST
!
program test
  implicit none
  intrinsic co_broadcast

  type t
    integer :: i
    character(len=1) :: c
    real(8) :: x(3), y(3)
  end type t

  integer :: i, j(10), stat
  complex :: a(5,5)
  character(kind=1, len=5) :: str1, errstr
  character(kind=4, len=8) :: str2(2)
  type(t) :: dt(4)

  i = 1
  j = 55
  a = 99.0
  str1 = 1_"XXXXX"
  str2 = 4_"YYYYYYYY"
  dt = t(1, 'C', [1.,2.,3.], [3,3,3])
  errstr = "ZZZZZ"

  if (this_image() == num_images()) then
    i = 2
    j = 66
    a = -99.0
    str1 = 1_"abcd"
    str2 = 4_"12 3 4 5"
    dt = t(-1, 'a', [3.,1.,8.], [99,24,5])
  end if
  sync all

  call co_broadcast(i, source_image=num_images(), stat=stat, errmsg=errstr)
  if (stat /= 0) STOP 1
  if (errstr /= "ZZZZZ") STOP 2
  if (i /= 2) STOP 3

  call co_broadcast(j, source_image=num_images(), stat=stat, errmsg=errstr)
  if (stat /= 0) STOP 4
  if (errstr /= "ZZZZZ") STOP 5
  if (any (j /= 66)) STOP 1

  call co_broadcast(a, source_image=num_images(), stat=stat, errmsg=errstr)
  if (stat /= 0) STOP 6
  if (errstr /= "ZZZZZ") STOP 7
  if (any (a /= -99.0)) STOP 2

  call co_broadcast(str1, source_image=num_images(), stat=stat, errmsg=errstr)
  if (stat /= 0) STOP 8
  if (errstr /= "ZZZZZ") STOP 9
  if (str1 /= "abcd") STOP 10

  call co_broadcast(str2, source_image=num_images(), stat=stat, errmsg=errstr)
  if (stat /= 0) STOP 11
  if (errstr /= "ZZZZZ") STOP 12
  if (any (str2 /= 4_"12 3 4 5")) STOP 3

  call co_broadcast(dt, source_image=num_images(), stat=stat, errmsg=errstr)
  if (stat /= 0) STOP 13
  if (errstr /= "ZZZZZ") STOP 14
  if (any (dt(:)%i /= -1)) STOP 15
  if (any (dt(:)%c /= 'a')) STOP 16
  if (any (dt(:)%x(1) /= 3.)) STOP 17
  if (any (dt(:)%x(2) /= 1.)) STOP 18
  if (any (dt(:)%x(3) /= 8.)) STOP 19
  if (any (dt(:)%y(1) /= 99.)) STOP 20
  if (any (dt(:)%y(2) /= 24.)) STOP 21
  if (any (dt(:)%y(3) /= 5.)) STOP 22

  sync all
  dt = t(1, 'C', [1.,2.,3.], [3,3,3])
  sync all
  if (this_image() == num_images()) then
    str2 = 4_"001122"
    dt(2:4) = t(-2, 'i', [9.,2.,3.], [4,44,321])
  end if

  call co_broadcast(str2(::2), source_image=num_images(), stat=stat, &
                    errmsg=errstr)
  if (stat /= 0) STOP 23
  if (errstr /= "ZZZZZ") STOP 24
  if (str2(1) /= 4_"001122") STOP 25
  if (this_image() == num_images()) then
    if (str2(1) /= 4_"001122") STOP 26
  else
    if (str2(2) /= 4_"12 3 4 5") STOP 27
  end if

  call co_broadcast(dt(2::2), source_image=num_images(), stat=stat, &
                    errmsg=errstr)
  if (stat /= 0) STOP 28
  if (errstr /= "ZZZZZ") STOP 29
  if (this_image() == num_images()) then
    if (any (dt(1:1)%i /= 1)) STOP 30
    if (any (dt(1:1)%c /= 'C')) STOP 31
    if (any (dt(1:1)%x(1) /= 1.)) STOP 32
    if (any (dt(1:1)%x(2) /= 2.)) STOP 33
    if (any (dt(1:1)%x(3) /= 3.)) STOP 34
    if (any (dt(1:1)%y(1) /= 3.)) STOP 35
    if (any (dt(1:1)%y(2) /= 3.)) STOP 36
    if (any (dt(1:1)%y(3) /= 3.)) STOP 37

    if (any (dt(2:)%i /= -2)) STOP 38
    if (any (dt(2:)%c /= 'i')) STOP 39
    if (any (dt(2:)%x(1) /= 9.)) STOP 40
    if (any (dt(2:)%x(2) /= 2.)) STOP 41
    if (any (dt(2:)%x(3) /= 3.)) STOP 42
    if (any (dt(2:)%y(1) /= 4.)) STOP 43
    if (any (dt(2:)%y(2) /= 44.)) STOP 44
    if (any (dt(2:)%y(3) /= 321.)) STOP 45
  else
    if (any (dt(1::2)%i /= 1)) STOP 46
    if (any (dt(1::2)%c /= 'C')) STOP 47
    if (any (dt(1::2)%x(1) /= 1.)) STOP 48
    if (any (dt(1::2)%x(2) /= 2.)) STOP 49
    if (any (dt(1::2)%x(3) /= 3.)) STOP 50
    if (any (dt(1::2)%y(1) /= 3.)) STOP 51
    if (any (dt(1::2)%y(2) /= 3.)) STOP 52
    if (any (dt(1::2)%y(3) /= 3.)) STOP 53

    if (any (dt(2::2)%i /= -2)) STOP 54
    if (any (dt(2::2)%c /= 'i')) STOP 55
    if (any (dt(2::2)%x(1) /= 9.)) STOP 56
    if (any (dt(2::2)%x(2) /= 2.)) STOP 57
    if (any (dt(2::2)%x(3) /= 3.)) STOP 58
    if (any (dt(2::2)%y(1) /= 4.)) STOP 59
    if (any (dt(2::2)%y(2) /= 44.)) STOP 60
    if (any (dt(2::2)%y(3) /= 321.)) STOP 61
  endif
end program test