source: codes/icosagcm/branches/SATURN_DYNAMICO/ICOSAGCM/src/transfert_omp.f90 @ 267

Last change on this file since 267 was 267, checked in by ymipsl, 10 years ago

Synchronize trunk and Saturn branch.
Merge modification from trunk branch to Saturn branch.

YM

File size: 16.7 KB
Line 
1MODULE transfert_omp_mod
2  PRIVATE
3 
4  INTEGER,PARAMETER :: grow_factor=1.5
5  INTEGER,PARAMETER :: size_min=1024
6 
7  CHARACTER(LEN=size_min),SAVE            :: buffer_c
8!  INTEGER,SAVE                            :: size_c=0
9  INTEGER,SAVE,ALLOCATABLE,DIMENSION(:)   :: buffer_i
10  INTEGER,SAVE                            :: size_i=0
11  REAL,SAVE,ALLOCATABLE,DIMENSION(:)      :: buffer_r
12  INTEGER,SAVE                            :: size_r=0
13  LOGICAL,SAVE,ALLOCATABLE,DIMENSION(:)   :: buffer_l
14  INTEGER,SAVE                            :: size_l=0
15
16
17 
18 
19  INTERFACE bcast_omp
20    MODULE PROCEDURE bcast_omp_c,                                                     &
21                     bcast_omp_i,bcast_omp_i1,bcast_omp_i2,bcast_omp_i3,bcast_omp_i4, &
22                     bcast_omp_r,bcast_omp_r1,bcast_omp_r2,bcast_omp_r3,bcast_omp_r4, &
23                     bcast_omp_l,bcast_omp_l1,bcast_omp_l2,bcast_omp_l3,bcast_omp_l4
24  END INTERFACE
25
26  INTERFACE reduce_sum_omp
27    MODULE PROCEDURE reduce_sum_omp_i,reduce_sum_omp_i1,reduce_sum_omp_i2,reduce_sum_omp_i3,reduce_sum_omp_i4, &
28                     reduce_sum_omp_r,reduce_sum_omp_r1,reduce_sum_omp_r2,reduce_sum_omp_r3,reduce_sum_omp_r4
29  END INTERFACE
30
31  INTERFACE allreduce_sum_omp
32    MODULE PROCEDURE allreduce_sum_omp_i,allreduce_sum_omp_i1,allreduce_sum_omp_i2,allreduce_sum_omp_i3,allreduce_sum_omp_i4, &
33                     allreduce_sum_omp_r,allreduce_sum_omp_r1,allreduce_sum_omp_r2,allreduce_sum_omp_r3,allreduce_sum_omp_r4
34  END INTERFACE
35
36  PUBLIC bcast_omp, reduce_sum_omp, allreduce_sum_omp
37 
38CONTAINS
39
40  SUBROUTINE check_buffer_i(buff_size)
41  IMPLICIT NONE
42  INTEGER :: buff_size
43
44!$OMP BARRIER
45!$OMP MASTER
46    IF (buff_size>size_i) THEN
47      IF (ALLOCATED(buffer_i)) DEALLOCATE(buffer_i)
48      size_i=MAX(size_min,INT(grow_factor*buff_size))
49      ALLOCATE(buffer_i(size_i))
50    ENDIF
51!$OMP END MASTER
52!$OMP BARRIER
53 
54  END SUBROUTINE check_buffer_i
55 
56  SUBROUTINE check_buffer_r(buff_size)
57  IMPLICIT NONE
58  INTEGER :: buff_size
59
60!$OMP BARRIER
61!$OMP MASTER
62    IF (buff_size>size_r) THEN
63      IF (ALLOCATED(buffer_r)) DEALLOCATE(buffer_r)
64      size_r=MAX(size_min,INT(grow_factor*buff_size))
65      ALLOCATE(buffer_r(size_r))
66    ENDIF
67!$OMP END MASTER
68!$OMP BARRIER
69 
70  END SUBROUTINE check_buffer_r
71 
72  SUBROUTINE check_buffer_l(buff_size)
73  IMPLICIT NONE
74  INTEGER :: buff_size
75
76!$OMP BARRIER
77!$OMP MASTER
78    IF (buff_size>size_l) THEN
79      IF (ALLOCATED(buffer_l)) DEALLOCATE(buffer_l)
80      size_l=MAX(size_min,INT(grow_factor*buff_size))
81      ALLOCATE(buffer_l(size_l))
82    ENDIF
83!$OMP END MASTER
84!$OMP BARRIER
85 
86  END SUBROUTINE check_buffer_l
87   
88!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
89!! Definition des Broadcast --> 4D   !!
90!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
91
92!! -- Les chaine de charactère -- !!
93
94  SUBROUTINE bcast_omp_c(var)
95  IMPLICIT NONE
96    CHARACTER(LEN=*),INTENT(INOUT) :: Var
97    INTEGER :: lenvar
98    lenvar=len(Var)
99    CALL bcast_omp_i(lenvar)
100    CALL bcast_omp_cgen(Var,lenvar,buffer_c)   
101  END SUBROUTINE bcast_omp_c
102
103!! -- Les entiers -- !!
104 
105  SUBROUTINE bcast_omp_i(var)
106  IMPLICIT NONE
107    INTEGER,INTENT(INOUT) :: Var
108    INTEGER :: Var_tmp(1)
109   
110    Var_tmp(1)=Var
111    CALL check_buffer_i(1)
112    CALL bcast_omp_igen(Var_tmp,1,buffer_i)
113    Var=Var_tmp(1)
114
115  END SUBROUTINE bcast_omp_i
116
117
118  SUBROUTINE bcast_omp_i1(var)
119  IMPLICIT NONE
120    INTEGER,INTENT(INOUT) :: Var(:)
121   
122    CALL check_buffer_i(size(Var))
123    CALL bcast_omp_igen(Var,size(Var),buffer_i)
124
125  END SUBROUTINE bcast_omp_i1
126
127
128  SUBROUTINE bcast_omp_i2(var)
129  IMPLICIT NONE
130    INTEGER,INTENT(INOUT) :: Var(:,:)
131   
132    CALL check_buffer_i(size(Var))
133    CALL bcast_omp_igen(Var,size(Var),buffer_i)
134
135  END SUBROUTINE bcast_omp_i2
136
137
138  SUBROUTINE bcast_omp_i3(var)
139  IMPLICIT NONE
140    INTEGER,INTENT(INOUT) :: Var(:,:,:)
141
142    CALL check_buffer_i(size(Var))
143    CALL bcast_omp_igen(Var,size(Var),buffer_i)
144
145  END SUBROUTINE bcast_omp_i3
146
147
148  SUBROUTINE bcast_omp_i4(var)
149  IMPLICIT NONE
150    INTEGER,INTENT(INOUT) :: Var(:,:,:,:)
151   
152    CALL check_buffer_i(size(Var))
153    CALL bcast_omp_igen(Var,size(Var),buffer_i)
154
155  END SUBROUTINE bcast_omp_i4
156
157
158!! -- Les reels -- !!
159
160  SUBROUTINE bcast_omp_r(var)
161  IMPLICIT NONE
162    REAL,INTENT(INOUT) :: Var
163    REAL :: Var_tmp(1)
164   
165    Var_tmp(1)=Var
166    CALL check_buffer_r(1)
167    CALL bcast_omp_rgen(Var_tmp,1,buffer_r)
168    Var=Var_tmp(1)
169
170  END SUBROUTINE bcast_omp_r
171
172
173  SUBROUTINE bcast_omp_r1(var)
174  IMPLICIT NONE
175    REAL,INTENT(INOUT) :: Var(:)
176   
177    CALL check_buffer_r(size(Var))
178    CALL bcast_omp_rgen(Var,size(Var),buffer_r)
179
180  END SUBROUTINE bcast_omp_r1
181
182
183  SUBROUTINE bcast_omp_r2(var)
184  IMPLICIT NONE
185    REAL,INTENT(INOUT) :: Var(:,:)
186   
187    CALL check_buffer_r(size(Var))
188    CALL bcast_omp_rgen(Var,size(Var),buffer_r)
189
190  END SUBROUTINE bcast_omp_r2
191
192
193  SUBROUTINE bcast_omp_r3(var)
194  IMPLICIT NONE
195    REAL,INTENT(INOUT) :: Var(:,:,:)
196
197    CALL check_buffer_r(size(Var))
198    CALL bcast_omp_rgen(Var,size(Var),buffer_r)
199
200  END SUBROUTINE bcast_omp_r3
201
202
203  SUBROUTINE bcast_omp_r4(var)
204  IMPLICIT NONE
205    REAL,INTENT(INOUT) :: Var(:,:,:,:)
206   
207    CALL check_buffer_r(size(Var))
208    CALL bcast_omp_rgen(Var,size(Var),buffer_r)
209
210  END SUBROUTINE bcast_omp_r4
211
212 
213!! -- Les booleans -- !!
214
215  SUBROUTINE bcast_omp_l(var)
216  IMPLICIT NONE
217    LOGICAL,INTENT(INOUT) :: Var
218    LOGICAL :: Var_tmp(1)
219   
220    Var_tmp(1)=Var
221    CALL check_buffer_l(1)
222    CALL bcast_omp_lgen(Var_tmp,1,buffer_l)
223    Var=Var_tmp(1)
224
225  END SUBROUTINE bcast_omp_l
226
227
228  SUBROUTINE bcast_omp_l1(var)
229  IMPLICIT NONE
230    LOGICAL,INTENT(INOUT) :: Var(:)
231   
232    CALL check_buffer_l(size(Var))
233    CALL bcast_omp_lgen(Var,size(Var),buffer_l)
234
235  END SUBROUTINE bcast_omp_l1
236
237
238  SUBROUTINE bcast_omp_l2(var)
239  IMPLICIT NONE
240    LOGICAL,INTENT(INOUT) :: Var(:,:)
241   
242    CALL check_buffer_l(size(Var))
243    CALL bcast_omp_lgen(Var,size(Var),buffer_l)
244
245  END SUBROUTINE bcast_omp_l2
246
247
248  SUBROUTINE bcast_omp_l3(var)
249  IMPLICIT NONE
250    LOGICAL,INTENT(INOUT) :: Var(:,:,:)
251
252    CALL check_buffer_l(size(Var))
253    CALL bcast_omp_lgen(Var,size(Var),buffer_l)
254
255  END SUBROUTINE bcast_omp_l3
256
257
258  SUBROUTINE bcast_omp_l4(var)
259  IMPLICIT NONE
260    LOGICAL,INTENT(INOUT) :: Var(:,:,:,:)
261   
262    CALL check_buffer_l(size(Var))
263    CALL bcast_omp_lgen(Var,size(Var),buffer_l)
264
265  END SUBROUTINE bcast_omp_l4
266 
267
268
269
270  SUBROUTINE reduce_sum_omp_i(VarIn, VarOut)
271    IMPLICIT NONE
272 
273    INTEGER,INTENT(IN)  :: VarIn
274    INTEGER,INTENT(OUT) :: VarOut
275    INTEGER             :: VarIn_tmp(1)
276    INTEGER             :: VarOut_tmp(1)
277   
278    VarIn_tmp(1)=VarIn
279    CALL Check_buffer_i(1)   
280    CALL reduce_sum_omp_igen(VarIn_tmp,Varout_tmp,1,buffer_i)
281    VarOut=VarOut_tmp(1)
282   
283  END SUBROUTINE reduce_sum_omp_i
284
285  SUBROUTINE reduce_sum_omp_i1(VarIn, VarOut)
286    IMPLICIT NONE
287 
288    INTEGER,INTENT(IN),DIMENSION(:)  :: VarIn
289    INTEGER,INTENT(OUT),DIMENSION(:) :: VarOut
290   
291    CALL Check_buffer_i(size(VarIn))   
292    CALL reduce_sum_omp_igen(VarIn,Varout,Size(VarIn),buffer_i)
293   
294  END SUBROUTINE reduce_sum_omp_i1
295 
296 
297  SUBROUTINE reduce_sum_omp_i2(VarIn, VarOut)
298    IMPLICIT NONE
299 
300    INTEGER,INTENT(IN),DIMENSION(:,:)  :: VarIn
301    INTEGER,INTENT(OUT),DIMENSION(:,:) :: VarOut
302
303    CALL Check_buffer_i(size(VarIn))   
304    CALL reduce_sum_omp_igen(VarIn,Varout,Size(VarIn),buffer_i)
305 
306  END SUBROUTINE reduce_sum_omp_i2
307
308
309  SUBROUTINE reduce_sum_omp_i3(VarIn, VarOut)
310    IMPLICIT NONE
311 
312    INTEGER,INTENT(IN),DIMENSION(:,:,:)  :: VarIn
313    INTEGER,INTENT(OUT),DIMENSION(:,:,:) :: VarOut
314   
315    CALL Check_buffer_i(size(VarIn))   
316    CALL reduce_sum_omp_igen(VarIn,Varout,Size(VarIn),buffer_i)
317 
318  END SUBROUTINE reduce_sum_omp_i3
319
320
321  SUBROUTINE reduce_sum_omp_i4(VarIn, VarOut)
322    IMPLICIT NONE
323
324    INTEGER,INTENT(IN),DIMENSION(:,:,:,:)  :: VarIn
325    INTEGER,INTENT(OUT),DIMENSION(:,:,:,:) :: VarOut
326 
327    CALL Check_buffer_i(size(VarIn))   
328    CALL reduce_sum_omp_igen(VarIn,Varout,Size(VarIn),buffer_i)
329 
330  END SUBROUTINE reduce_sum_omp_i4
331
332
333  SUBROUTINE reduce_sum_omp_r(VarIn, VarOut)
334    IMPLICIT NONE
335 
336    REAL,INTENT(IN)  :: VarIn
337    REAL,INTENT(OUT) :: VarOut
338    REAL             :: VarIn_tmp(1)
339    REAL             :: VarOut_tmp(1)
340   
341    VarIn_tmp(1)=VarIn
342    CALL Check_buffer_r(1)   
343    CALL reduce_sum_omp_rgen(VarIn_tmp,Varout_tmp,1,buffer_r)
344    VarOut=VarOut_tmp(1)
345 
346  END SUBROUTINE reduce_sum_omp_r
347
348  SUBROUTINE reduce_sum_omp_r1(VarIn, VarOut)
349    IMPLICIT NONE
350 
351    REAL,INTENT(IN),DIMENSION(:)  :: VarIn
352    REAL,INTENT(OUT),DIMENSION(:) :: VarOut
353   
354    CALL Check_buffer_r(size(VarIn))   
355    CALL reduce_sum_omp_rgen(VarIn,Varout,Size(VarIn),buffer_r)
356   
357  END SUBROUTINE reduce_sum_omp_r1
358 
359 
360  SUBROUTINE reduce_sum_omp_r2(VarIn, VarOut)
361    IMPLICIT NONE
362 
363    REAL,INTENT(IN),DIMENSION(:,:)  :: VarIn
364    REAL,INTENT(OUT),DIMENSION(:,:) :: VarOut
365   
366    CALL Check_buffer_r(size(VarIn))   
367    CALL reduce_sum_omp_rgen(VarIn,Varout,Size(VarIn),buffer_r)
368 
369  END SUBROUTINE reduce_sum_omp_r2
370
371
372  SUBROUTINE reduce_sum_omp_r3(VarIn, VarOut)
373    IMPLICIT NONE
374 
375    REAL,INTENT(IN),DIMENSION(:,:,:)  :: VarIn
376    REAL,INTENT(OUT),DIMENSION(:,:,:) :: VarOut
377   
378    CALL Check_buffer_r(size(VarIn))   
379    CALL reduce_sum_omp_rgen(VarIn,Varout,Size(VarIn),buffer_r)
380 
381  END SUBROUTINE reduce_sum_omp_r3
382
383
384  SUBROUTINE reduce_sum_omp_r4(VarIn, VarOut)
385    IMPLICIT NONE
386
387    REAL,INTENT(IN),DIMENSION(:,:,:,:)  :: VarIn
388    REAL,INTENT(OUT),DIMENSION(:,:,:,:) :: VarOut
389 
390    CALL Check_buffer_r(size(VarIn))   
391    CALL reduce_sum_omp_rgen(VarIn,Varout,Size(VarIn),buffer_r)
392 
393  END SUBROUTINE reduce_sum_omp_r4 
394 
395 
396 
397 
398    SUBROUTINE allreduce_sum_omp_i(VarIn, VarOut)
399    IMPLICIT NONE
400 
401    INTEGER,INTENT(IN)  :: VarIn
402    INTEGER,INTENT(OUT) :: VarOut
403    INTEGER             :: VarIn_tmp(1)
404    INTEGER             :: VarOut_tmp(1)
405   
406    VarIn_tmp(1)=VarIn
407    CALL Check_buffer_i(1)   
408    CALL allreduce_sum_omp_igen(VarIn_tmp,Varout_tmp,1,buffer_i)
409    VarOut=VarOut_tmp(1)
410   
411  END SUBROUTINE allreduce_sum_omp_i
412
413  SUBROUTINE allreduce_sum_omp_i1(VarIn, VarOut)
414    IMPLICIT NONE
415 
416    INTEGER,INTENT(IN),DIMENSION(:)  :: VarIn
417    INTEGER,INTENT(OUT),DIMENSION(:) :: VarOut
418   
419    CALL Check_buffer_i(size(VarIn))   
420    CALL allreduce_sum_omp_igen(VarIn,Varout,Size(VarIn),buffer_i)
421   
422  END SUBROUTINE allreduce_sum_omp_i1
423 
424 
425  SUBROUTINE allreduce_sum_omp_i2(VarIn, VarOut)
426    IMPLICIT NONE
427 
428    INTEGER,INTENT(IN),DIMENSION(:,:)  :: VarIn
429    INTEGER,INTENT(OUT),DIMENSION(:,:) :: VarOut
430
431    CALL Check_buffer_i(size(VarIn))   
432    CALL allreduce_sum_omp_igen(VarIn,Varout,Size(VarIn),buffer_i)
433 
434  END SUBROUTINE allreduce_sum_omp_i2
435
436
437  SUBROUTINE allreduce_sum_omp_i3(VarIn, VarOut)
438    IMPLICIT NONE
439 
440    INTEGER,INTENT(IN),DIMENSION(:,:,:)  :: VarIn
441    INTEGER,INTENT(OUT),DIMENSION(:,:,:) :: VarOut
442   
443    CALL Check_buffer_i(size(VarIn))   
444    CALL allreduce_sum_omp_igen(VarIn,Varout,Size(VarIn),buffer_i)
445 
446  END SUBROUTINE allreduce_sum_omp_i3
447
448
449  SUBROUTINE allreduce_sum_omp_i4(VarIn, VarOut)
450    IMPLICIT NONE
451
452    INTEGER,INTENT(IN),DIMENSION(:,:,:,:)  :: VarIn
453    INTEGER,INTENT(OUT),DIMENSION(:,:,:,:) :: VarOut
454 
455    CALL Check_buffer_i(size(VarIn))   
456    CALL allreduce_sum_omp_igen(VarIn,Varout,Size(VarIn),buffer_i)
457 
458  END SUBROUTINE allreduce_sum_omp_i4
459
460
461  SUBROUTINE allreduce_sum_omp_r(VarIn, VarOut)
462    IMPLICIT NONE
463 
464    REAL,INTENT(IN)  :: VarIn
465    REAL,INTENT(OUT) :: VarOut
466    REAL             :: VarIn_tmp(1)
467    REAL             :: VarOut_tmp(1)
468   
469    VarIn_tmp(1)=VarIn
470    CALL Check_buffer_r(1)   
471    CALL allreduce_sum_omp_rgen(VarIn_tmp,Varout_tmp,1,buffer_r)
472    VarOut=VarOut_tmp(1)
473 
474  END SUBROUTINE allreduce_sum_omp_r
475
476  SUBROUTINE allreduce_sum_omp_r1(VarIn, VarOut)
477    IMPLICIT NONE
478 
479    REAL,INTENT(IN),DIMENSION(:)  :: VarIn
480    REAL,INTENT(OUT),DIMENSION(:) :: VarOut
481   
482    CALL Check_buffer_r(size(VarIn))   
483    CALL allreduce_sum_omp_rgen(VarIn,Varout,Size(VarIn),buffer_r)
484   
485  END SUBROUTINE allreduce_sum_omp_r1
486 
487 
488  SUBROUTINE allreduce_sum_omp_r2(VarIn, VarOut)
489    IMPLICIT NONE
490 
491    REAL,INTENT(IN),DIMENSION(:,:)  :: VarIn
492    REAL,INTENT(OUT),DIMENSION(:,:) :: VarOut
493   
494    CALL Check_buffer_r(size(VarIn))   
495    CALL allreduce_sum_omp_rgen(VarIn,Varout,Size(VarIn),buffer_r)
496 
497  END SUBROUTINE allreduce_sum_omp_r2
498
499
500  SUBROUTINE allreduce_sum_omp_r3(VarIn, VarOut)
501    IMPLICIT NONE
502 
503    REAL,INTENT(IN),DIMENSION(:,:,:)  :: VarIn
504    REAL,INTENT(OUT),DIMENSION(:,:,:) :: VarOut
505   
506    CALL Check_buffer_r(size(VarIn))   
507    CALL allreduce_sum_omp_rgen(VarIn,Varout,Size(VarIn),buffer_r)
508 
509  END SUBROUTINE allreduce_sum_omp_r3
510
511
512  SUBROUTINE allreduce_sum_omp_r4(VarIn, VarOut)
513    IMPLICIT NONE
514
515    REAL,INTENT(IN),DIMENSION(:,:,:,:)  :: VarIn
516    REAL,INTENT(OUT),DIMENSION(:,:,:,:) :: VarOut
517 
518    CALL Check_buffer_r(size(VarIn))   
519    CALL allreduce_sum_omp_rgen(VarIn,Varout,Size(VarIn),buffer_r)
520 
521  END SUBROUTINE allreduce_sum_omp_r4 
522 
523 
524!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
525!    LES ROUTINES GENERIQUES    !
526!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
527
528  SUBROUTINE bcast_omp_cgen(Var,Nb,Buff)
529  IMPLICIT NONE
530   
531    CHARACTER(LEN=*),INTENT(INOUT) :: Var
532    CHARACTER(LEN=*),INTENT(INOUT) :: Buff
533    INTEGER,INTENT(IN) :: Nb
534   
535    INTEGER :: i
536 
537  !$OMP MASTER
538      Buff=Var
539  !$OMP END MASTER
540  !$OMP BARRIER
541
542    DO i=1,Nb
543      Var=Buff
544    ENDDO
545  !$OMP BARRIER     
546 
547  END SUBROUTINE bcast_omp_cgen
548
549
550     
551  SUBROUTINE bcast_omp_igen(Var,Nb,Buff)
552  IMPLICIT NONE
553   
554    INTEGER,DIMENSION(Nb),INTENT(INOUT) :: Var
555    INTEGER,DIMENSION(Nb),INTENT(INOUT) :: Buff
556    INTEGER,INTENT(IN) :: Nb
557
558    INTEGER :: i
559   
560  !$OMP MASTER
561    DO i=1,Nb
562      Buff(i)=Var(i)
563    ENDDO
564  !$OMP END MASTER
565  !$OMP BARRIER
566
567    DO i=1,Nb
568      Var(i)=Buff(i)
569    ENDDO
570  !$OMP BARRIER       
571
572  END SUBROUTINE bcast_omp_igen
573
574
575  SUBROUTINE bcast_omp_rgen(Var,Nb,Buff)
576  IMPLICIT NONE
577   
578    REAL,DIMENSION(Nb),INTENT(INOUT) :: Var
579    REAL,DIMENSION(Nb),INTENT(INOUT) :: Buff
580    INTEGER,INTENT(IN) :: Nb
581
582    INTEGER :: i
583   
584  !$OMP MASTER
585    DO i=1,Nb
586      Buff(i)=Var(i)
587    ENDDO
588  !$OMP END MASTER
589  !$OMP BARRIER
590
591    DO i=1,Nb
592      Var(i)=Buff(i)
593    ENDDO
594  !$OMP BARRIER       
595
596  END SUBROUTINE bcast_omp_rgen
597
598  SUBROUTINE bcast_omp_lgen(Var,Nb,Buff)
599  IMPLICIT NONE
600   
601    LOGICAL,DIMENSION(Nb),INTENT(INOUT) :: Var
602    LOGICAL,DIMENSION(Nb),INTENT(INOUT) :: Buff
603    INTEGER,INTENT(IN) :: Nb
604 
605    INTEGER :: i
606   
607  !$OMP MASTER
608    DO i=1,Nb
609      Buff(i)=Var(i)
610    ENDDO
611  !$OMP END MASTER
612  !$OMP BARRIER
613
614    DO i=1,Nb
615      Var(i)=Buff(i)
616    ENDDO
617  !$OMP BARRIER       
618
619  END SUBROUTINE bcast_omp_lgen
620 
621
622  SUBROUTINE reduce_sum_omp_igen(VarIn,VarOut,dimsize,Buff)
623  IMPLICIT NONE
624
625    INTEGER,INTENT(IN) :: dimsize
626    INTEGER,INTENT(IN),DIMENSION(dimsize) :: VarIn
627    INTEGER,INTENT(OUT),DIMENSION(dimsize) :: VarOut
628    INTEGER,INTENT(INOUT),DIMENSION(dimsize) :: Buff
629
630    INTEGER :: i
631
632  !$OMP MASTER
633    Buff(:)=0
634  !$OMP END MASTER
635  !$OMP BARRIER
636 
637  !$OMP CRITICAL     
638    DO i=1,dimsize
639      Buff(i)=Buff(i)+VarIn(i)
640    ENDDO
641  !$OMP END CRITICAL
642  !$OMP BARRIER 
643 
644  !$OMP MASTER
645    DO i=1,dimsize
646      VarOut(i)=Buff(i)
647    ENDDO
648  !$OMP END MASTER
649  !$OMP BARRIER
650 
651  END SUBROUTINE reduce_sum_omp_igen
652
653  SUBROUTINE reduce_sum_omp_rgen(VarIn,VarOut,dimsize,Buff)
654  IMPLICIT NONE
655
656    INTEGER,INTENT(IN) :: dimsize
657    REAL,INTENT(IN),DIMENSION(dimsize) :: VarIn
658    REAL,INTENT(OUT),DIMENSION(dimsize) :: VarOut
659    REAL,INTENT(INOUT),DIMENSION(dimsize) :: Buff
660
661    INTEGER :: i
662
663  !$OMP MASTER
664    Buff(:)=0
665  !$OMP END MASTER
666  !$OMP BARRIER
667 
668  !$OMP CRITICAL     
669    DO i=1,dimsize
670      Buff(i)=Buff(i)+VarIn(i)
671    ENDDO
672  !$OMP END CRITICAL
673  !$OMP BARRIER 
674 
675    DO i=1,dimsize
676      VarOut(i)=Buff(i)
677    ENDDO
678  !$OMP BARRIER
679 
680  END SUBROUTINE reduce_sum_omp_rgen
681
682
683
684  SUBROUTINE allreduce_sum_omp_igen(VarIn,VarOut,dimsize,Buff)
685  IMPLICIT NONE
686
687    INTEGER,INTENT(IN) :: dimsize
688    INTEGER,INTENT(IN),DIMENSION(dimsize) :: VarIn
689    INTEGER,INTENT(OUT),DIMENSION(dimsize) :: VarOut
690    INTEGER,INTENT(INOUT),DIMENSION(dimsize) :: Buff
691
692    INTEGER :: i
693
694  !$OMP MASTER
695    Buff(:)=0
696  !$OMP END MASTER
697  !$OMP BARRIER
698 
699  !$OMP CRITICAL     
700    DO i=1,dimsize
701      Buff(i)=Buff(i)+VarIn(i)
702    ENDDO
703  !$OMP END CRITICAL
704  !$OMP BARRIER 
705 
706    DO i=1,dimsize
707      VarOut(i)=Buff(i)
708    ENDDO
709  !$OMP BARRIER
710 
711  END SUBROUTINE allreduce_sum_omp_igen
712
713  SUBROUTINE allreduce_sum_omp_rgen(VarIn,VarOut,dimsize,Buff)
714  IMPLICIT NONE
715
716    INTEGER,INTENT(IN) :: dimsize
717    REAL,INTENT(IN),DIMENSION(dimsize) :: VarIn
718    REAL,INTENT(OUT),DIMENSION(dimsize) :: VarOut
719    REAL,INTENT(INOUT),DIMENSION(dimsize) :: Buff
720
721    INTEGER :: i
722
723  !$OMP MASTER
724    Buff(:)=0
725  !$OMP END MASTER
726  !$OMP BARRIER
727 
728  !$OMP CRITICAL     
729    DO i=1,dimsize
730      Buff(i)=Buff(i)+VarIn(i)
731    ENDDO
732  !$OMP END CRITICAL
733  !$OMP BARRIER 
734 
735    DO i=1,dimsize
736      VarOut(i)=Buff(i)
737    ENDDO
738
739  !$OMP BARRIER
740 
741  END SUBROUTINE allreduce_sum_omp_rgen
742   
743END MODULE transfert_omp_mod
Note: See TracBrowser for help on using the repository browser.