source: trunk/LMDZ.MARS/libf/phy_common/ioipsl_getin_p_mod.F90 @ 1621

Last change on this file since 1621 was 1543, checked in by emillour, 9 years ago

All models: Further adaptations to keep up with changes in LMDZ5 concerning
physics/dynamics separation:

  • dyn3d:
  • adapted gcm.F so that all physics initializations are now done in iniphysiq.
  • dyn3dpar:
  • adapted gcm.F so that all physics initializations are now done in iniphysiq.
  • updated calfis_p.F to follow up with changes.
  • copied over updated "bands.F90" from LMDZ5.
  • dynphy_lonlat:
  • calfis_p.F90, mod_interface_dyn_phys.F90, follow up of changes in phy_common/mod_* routines
  • phy_common:
  • added "geometry_mod.F90" to store information about the grid (replaces phy*/comgeomphy.F90) and give variables friendlier names: rlond => longitude , rlatd => latitude, airephy => cell_area, cuphy => dx , cvphy => dy
  • added "physics_distribution_mod.F90"
  • updated "mod_grid_phy_lmdz.F90", "mod_phys_lmdz_mpi_data.F90", "mod_phys_lmdz_para.F90", "mod_phys_lmdz_mpi_transfert.F90", "mod_grid_phy_lmdz.F90", "mod_phys_lmdz_omp_data.F90", "mod_phys_lmdz_omp_transfert.F90", "write_field_phy.F90" and "ioipsl_getin_p_mod.F90" to LMDZ5 versions.
  • phy[venus/titan/mars/std]:
  • removed "init_phys_lmdz.F90", "comgeomphy.F90"; adapted routines to use geometry_mod (longitude, latitude, cell_area, etc.)

EM

File size: 3.9 KB
Line 
1!
2! $Id$
3!
4MODULE ioipsl_getin_p_mod
5! To use getin in a parallel context
6!---------------------------------------------------------------------
7#ifdef CPP_IOIPSL
8USE ioipsl, ONLY: getin
9#else
10USE ioipsl_getincom, ONLY: getin
11#endif
12USE mod_phys_lmdz_mpi_data, ONLY :  is_mpi_root
13USE mod_phys_lmdz_omp_data, ONLY :  is_omp_root
14USE mod_phys_lmdz_transfert_para, ONLY : bcast
15!-
16IMPLICIT NONE
17!-
18PRIVATE
19PUBLIC :: getin_p
20!-
21INTERFACE getin_p
22
23  MODULE PROCEDURE getinrs_p, getinr1d_p, getinr2d_p, &
24 &                 getinis_p, getini1d_p, getini2d_p, &
25 &                 getincs_p,                         &
26 &                 getinls_p, getinl1d_p, getinl2d_p
27END INTERFACE
28!-
29CONTAINS
30
31
32!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
33!!   Definition des getin -> bcast      !!
34!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
35
36!! -- Les chaines de caracteres -- !!
37 
38  SUBROUTINE getincs_p(VarIn,VarOut)
39    IMPLICIT NONE   
40    CHARACTER(LEN=*),INTENT(IN) :: VarIn
41    CHARACTER(LEN=*),INTENT(INOUT) :: VarOut   
42
43!$OMP BARRIER
44    IF (is_mpi_root .AND. is_omp_root) THEN
45        CALL getin(VarIn,VarOut)
46    ENDIF
47    CALL bcast(VarOut)
48  END SUBROUTINE getincs_p
49
50!! -- Les entiers -- !!
51 
52  SUBROUTINE getinis_p(VarIn,VarOut)
53    IMPLICIT NONE   
54    CHARACTER(LEN=*),INTENT(IN) :: VarIn
55    INTEGER,INTENT(INOUT) :: VarOut   
56
57!$OMP BARRIER
58    IF (is_mpi_root .AND. is_omp_root) THEN
59        CALL getin(VarIn,VarOut)
60    ENDIF
61    CALL bcast(VarOut)
62  END SUBROUTINE getinis_p
63
64  SUBROUTINE getini1d_p(VarIn,VarOut)
65    IMPLICIT NONE   
66    CHARACTER(LEN=*),INTENT(IN) :: VarIn
67    INTEGER,INTENT(INOUT) :: VarOut(:)
68
69!$OMP BARRIER
70    IF (is_mpi_root .AND. is_omp_root) THEN
71        CALL getin(VarIn,VarOut)
72    ENDIF
73    CALL bcast(VarOut)
74  END SUBROUTINE getini1d_p
75
76  SUBROUTINE getini2d_p(VarIn,VarOut)
77    IMPLICIT NONE   
78    CHARACTER(LEN=*),INTENT(IN) :: VarIn
79    INTEGER,INTENT(INOUT) :: VarOut(:,:)
80
81!$OMP BARRIER
82    IF (is_mpi_root .AND. is_omp_root) THEN
83        CALL getin(VarIn,VarOut)
84    ENDIF
85    CALL bcast(VarOut)
86  END SUBROUTINE getini2d_p
87
88!! -- Les flottants -- !!
89 
90  SUBROUTINE getinrs_p(VarIn,VarOut)
91    IMPLICIT NONE   
92    CHARACTER(LEN=*),INTENT(IN) :: VarIn
93    REAL,INTENT(INOUT) :: VarOut
94
95!$OMP BARRIER
96    IF (is_mpi_root .AND. is_omp_root) THEN
97        CALL getin(VarIn,VarOut)
98    ENDIF
99    CALL bcast(VarOut)
100  END SUBROUTINE getinrs_p
101
102  SUBROUTINE getinr1d_p(VarIn,VarOut)
103    IMPLICIT NONE   
104    CHARACTER(LEN=*),INTENT(IN) :: VarIn
105    REAL,INTENT(INOUT) :: VarOut(:)
106
107!$OMP BARRIER
108    IF (is_mpi_root .AND. is_omp_root) THEN
109        CALL getin(VarIn,VarOut)
110    ENDIF
111    CALL bcast(VarOut)
112  END SUBROUTINE getinr1d_p
113
114  SUBROUTINE getinr2d_p(VarIn,VarOut)
115    IMPLICIT NONE   
116    CHARACTER(LEN=*),INTENT(IN) :: VarIn
117    REAL,INTENT(INOUT) :: VarOut(:,:)
118
119!$OMP BARRIER
120    IF (is_mpi_root .AND. is_omp_root) THEN
121        CALL getin(VarIn,VarOut)
122    ENDIF
123    CALL bcast(VarOut)
124  END SUBROUTINE getinr2d_p
125
126!! -- Les Booleens -- !!
127 
128  SUBROUTINE getinls_p(VarIn,VarOut)
129    IMPLICIT NONE   
130    CHARACTER(LEN=*),INTENT(IN) :: VarIn
131    LOGICAL,INTENT(INOUT) :: VarOut
132
133!$OMP BARRIER
134    IF (is_mpi_root .AND. is_omp_root) THEN
135        CALL getin(VarIn,VarOut)
136    ENDIF
137    CALL bcast(VarOut)
138  END SUBROUTINE getinls_p
139
140  SUBROUTINE getinl1d_p(VarIn,VarOut)
141    IMPLICIT NONE   
142    CHARACTER(LEN=*),INTENT(IN) :: VarIn
143    LOGICAL,INTENT(INOUT) :: VarOut(:)
144
145!$OMP BARRIER
146    IF (is_mpi_root .AND. is_omp_root) THEN
147        CALL getin(VarIn,VarOut)
148    ENDIF
149    CALL bcast(VarOut)
150  END SUBROUTINE getinl1d_p
151
152  SUBROUTINE getinl2d_p(VarIn,VarOut)
153    IMPLICIT NONE   
154    CHARACTER(LEN=*),INTENT(IN) :: VarIn
155    LOGICAL,INTENT(INOUT) :: VarOut(:,:)
156
157!$OMP BARRIER
158    IF (is_mpi_root .AND. is_omp_root) THEN
159        CALL getin(VarIn,VarOut)
160    ENDIF
161    CALL bcast(VarOut)
162  END SUBROUTINE getinl2d_p
163!-
164!-----------------------------
165!-----------------------------
166!-----------------------------
167
168END MODULE ioipsl_getin_p_mod
169
Note: See TracBrowser for help on using the repository browser.