source: codes/icosagcm/trunk/src/getin.f90 @ 190

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

Add new openMP parallelism based on distribution of domains on threads. There is no more limitation of number of threads by MPI process.

YM

File size: 1.4 KB
Line 
1MODULE getin_mod
2
3PRIVATE
4
5  INTERFACE getin
6    MODULE PROCEDURE getin_c , getin_l, getin_i, getin_r
7  END INTERFACE getin
8 
9PUBLIC getin
10 
11CONTAINS
12
13  SUBROUTINE getin_c(name,value)
14  USE ioipsl, ONLY : getin_=>getin
15  USE transfert_omp_mod
16  USE omp_para
17  IMPLICIT NONE
18    CHARACTER(LEN=*) :: name
19    CHARACTER(LEN=*) :: value
20
21!$OMP MASTER   
22    CALL getin_(name,value)
23!$OMP END MASTER
24    IF (omp_in_parallel()) CALL bcast_omp(value)
25  END SUBROUTINE getin_c
26
27  SUBROUTINE getin_l(name,value)
28  USE ioipsl, ONLY : getin_=>getin
29  USE transfert_omp_mod
30  USE omp_para
31  IMPLICIT NONE
32    CHARACTER(LEN=*) :: name
33    LOGICAL          :: value
34
35!$OMP MASTER   
36    CALL getin_(name,value)
37!$OMP END MASTER
38    IF (omp_in_parallel()) CALL bcast_omp(value)
39  END SUBROUTINE getin_l
40
41  SUBROUTINE getin_i(name,value)
42  USE ioipsl, ONLY : getin_=>getin
43  USE transfert_omp_mod
44  USE omp_para
45  IMPLICIT NONE
46    CHARACTER(LEN=*) :: name
47    INTEGER          :: value
48
49!$OMP MASTER   
50    CALL getin_(name,value)
51!$OMP END MASTER
52    IF (omp_in_parallel()) CALL bcast_omp(value)
53  END SUBROUTINE getin_i
54 
55 
56  SUBROUTINE getin_r(name,value)
57  USE ioipsl, ONLY : getin_=>getin
58  USE omp_para
59  USE transfert_omp_mod
60  IMPLICIT NONE
61    CHARACTER(LEN=*) :: name
62    REAL             :: value
63
64!$OMP MASTER   
65    CALL getin_(name,value)
66!$OMP END MASTER
67    IF (omp_in_parallel()) CALL bcast_omp(value)
68  END SUBROUTINE getin_r
69 
70END MODULE getin_mod
Note: See TracBrowser for help on using the repository browser.