SURFEX v8.1
General documentation of Surfex
sfx_oasis_prep.F90
Go to the documentation of this file.
1 !SFX_LIC Copyright 1994-2014 CNRS, Meteo-France and Universite Paul Sabatier
2 !SFX_LIC This is part of the SURFEX software governed by the CeCILL-C licence
3 !SFX_LIC version 1. See LICENSE, CeCILL-C_V1-en.txt and CeCILL-C_V1-fr.txt
4 !SFX_LIC for details. version 1.
5 !#########
6 SUBROUTINE sfx_oasis_prep (IO, S, UG, U, HPROGRAM, KNPTS, KPARAL)
7 !###################################################
8 !
9 !!**** *SFX_OASIS_PREP* - Prepare grid areas and mask file for SFX-OASIS coupling
10 !!
11 !! PURPOSE
12 !! -------
13 !!
14 !!** METHOD
15 !! ------
16 !!
17 !! EXTERNAL
18 !! --------
19 !!
20 !!
21 !! IMPLICIT ARGUMENTS
22 !! ------------------
23 !!
24 !! REFERENCE
25 !! ---------
26 !!
27 !!
28 !! AUTHOR
29 !! ------
30 !! B. Decharme *Meteo France*
31 !!
32 !! MODIFICATIONS
33 !! -------------
34 !! Original 10/2013
35 !! 10/2016 B. Decharme : bug surface/groundwater coupling
36 !-------------------------------------------------------------------------------
37 !
38 !* 0. DECLARATIONS
39 ! ------------
40 !
42 USE modd_isba_n, ONLY : isba_s_t
44 USE modd_surf_atm_n, ONLY : surf_atm_t
45 !
46 USE modd_surf_par, ONLY : xundef
47 !
48 USE modd_surfex_mpi, ONLY : nrank, npio
49 !
52 !
54 USE modi_get_luout
55 USE modi_abor1_sfx
56 USE modi_get_mesh_corner
58 USE modi_sfx_oasis_check
59 !
60 #ifdef CPLOASIS
61 USE mod_oasis
62 #endif
63 !
64 USE yomhook ,ONLY : lhook, dr_hook
65 USE parkind1 ,ONLY : jprb
66 !
67 IMPLICIT NONE
68 !
69 !* 0.1 Declarations of arguments
70 ! -------------------------
71 !
72 TYPE(isba_options_t), INTENT(INOUT) :: IO
73 TYPE(isba_s_t), INTENT(INOUT) :: S
74 TYPE(surf_atm_grid_t), INTENT(INOUT) :: UG
75 TYPE(surf_atm_t), INTENT(INOUT) :: U
76 !
77  CHARACTER(LEN=6), INTENT(IN) :: HPROGRAM ! program calling surf. schemes
78 INTEGER, INTENT(IN) :: KNPTS ! Number of grid point on this proc
79 INTEGER, DIMENSION(:), INTENT(IN) :: KPARAL
80 !
81 !* 0.2 Declarations of local parameter
82 ! -------------------------------
83 !
84 INTEGER, PARAMETER :: INC = 4 ! Number of grid-cell corners
85 !
86  CHARACTER(LEN=4), PARAMETER :: YSFX_LAND = 'slan'
87  CHARACTER(LEN=4), PARAMETER :: YSFX_SEA = 'ssea'
88  CHARACTER(LEN=4), PARAMETER :: YSFX_LAKE = 'slak'
89 !
90 !* 0.3 Declarations of local variables
91 ! -------------------------------
92 !
93 REAL, DIMENSION(U%NSIZE_FULL) :: ZMASK_LAND ! land-sea mask for rrm coupling
94 REAL, DIMENSION(U%NSIZE_FULL) :: ZMASK_LAKE ! lake mask for ogcm coupling
95 REAL, DIMENSION(U%NSIZE_FULL) :: ZMASK_SEA ! sea-land mask for ogcm coupling
96 !
97 REAL, DIMENSION(U%NSIZE_FULL,1) :: ZLON
98 REAL, DIMENSION(U%NSIZE_FULL,1) :: ZLAT
99 REAL, DIMENSION(U%NSIZE_FULL,1) :: ZAREA
100 INTEGER, DIMENSION(U%NSIZE_FULL,1) :: IMASK
101 !
102 REAL, DIMENSION(U%NSIZE_FULL,1,INC) :: ZCORNER_LON
103 REAL, DIMENSION(U%NSIZE_FULL,1,INC) :: ZCORNER_LAT
104 !
105 REAL, DIMENSION(U%NDIM_FULL) :: ZMASK_LAND_TOT ! land-sea mask for rrm coupling
106 REAL, DIMENSION(U%NDIM_FULL) :: ZMASK_LAKE_TOT ! lake mask for ogcm coupling
107 REAL, DIMENSION(U%NDIM_FULL) :: ZMASK_SEA_TOT ! sea-land mask for ogcm coupling
108 !
109 REAL, DIMENSION(U%NDIM_FULL,1) :: ZLON_TOT
110 REAL, DIMENSION(U%NDIM_FULL,1) :: ZLAT_TOT
111 REAL, DIMENSION(U%NDIM_FULL,1) :: ZAREA_TOT
112 INTEGER, DIMENSION(U%NDIM_FULL,1) :: IMASK_TOT
113 !
114 REAL, DIMENSION(U%NDIM_FULL,1,INC) :: ZCORNER_LON_TOT
115 REAL, DIMENSION(U%NDIM_FULL,1,INC) :: ZCORNER_LAT_TOT
116 !
117 INTEGER, DIMENSION(2) :: IVAR_SHAPE ! indexes for the coupling field local dimension
118 !
119 INTEGER :: IPART_ID ! Local partition ID
120 INTEGER :: IERR ! Error info
121 !
122 INTEGER :: ILUOUT, IFLAG
123 !
124 INTEGER :: JI, JC
125 !
126 REAL(KIND=JPRB) :: ZHOOK_HANDLE
127 !
128 !-------------------------------------------------------------------------------
129 !
130 IF (lhook) CALL dr_hook('SFX_OASIS_PREP',0,zhook_handle)
131 !
132 !-------------------------------------------------------------------------------
133 #ifdef CPLOASIS
134 !-------------------------------------------------------------------------------
135 !
136 !
137 !* 0. Initialize :
138 ! ------------
139 !
140  CALL get_luout(hprogram,iluout)
141 !
142  CALL sfx_oasis_check(io, u, iluout)
143 !
144 !-------------------------------------------------------------------------------
145 !
146 !* 1. Define parallel partitions:
147 ! ---------------------------
148 !
149  CALL oasis_def_partition(ipart_id,kparal(:),ierr)
150 !
151 IF(ierr/=oasis_ok)THEN
152  WRITE(iluout,*)'SFX_OASIS_DEFINE: OASIS def partition problem, err = ',ierr
153  CALL abor1_sfx('SFX_OASIS_DEFINE: OASIS def partition problem')
154 ENDIF
155 !
156 !-------------------------------------------------------------------------------
157 !
158 !* 2. Get grid definition :
159 ! ---------------------
160 !
161  CALL get_mesh_corner(ug, iluout,zcorner_lat(:,1,:),zcorner_lon(:,1,:))
162 !
163 zlon(:,1)=ug%G%XLON(:)
164 zlat(:,1)=ug%G%XLAT(:)
165 !
166 !-------------------------------------------------------------------------------
167 !
168 !* 3. Comput masks :
169 ! --------------
170 !
171 zmask_land(:) = u%XNATURE(:)+u%XTOWN(:)
172 zmask_sea(:) = u%XSEA (:)
173 IF(u%CWATER=='FLAKE ')THEN
174  zmask_lake(:) = u%XWATER (:)
175 ELSE
176  zmask_lake(:) = xundef
177 ENDIF
178 IF(lcpl_sea.AND.lwater)THEN
179  zmask_sea(:) = u%XSEA (:)+u%XWATER(:)
180 ENDIF
181 !
182 !-------------------------------------------------------------------------------
183 !
184 !* 5. Write grid definition :
185 ! -----------------------
186 !
187 !
188 !
189 IF (nrank==npio) CALL oasis_start_grids_writing(iflag)
190 !
191 !* 1.1 Grid definition for Land surface :
192 ! ----------------------------------
193 !
194 IF(lcpl_land)THEN
195  !
196  zarea(:,1) = ug%G%XMESH_SIZE(:) * zmask_land(:)
197  !0 = not masked ; 1 = masked
198  WHERE(zarea(:,1)>0.0)
199  imask(:,1) = 0
200  ELSEWHERE
201  imask(:,1) = 1
202  ENDWHERE
203  !
204  CALL gather_and_write_mpi(zlon,zlon_tot)
205  CALL gather_and_write_mpi(zlat,zlat_tot)
206  CALL gather_and_write_mpi(zcorner_lon,zcorner_lon_tot)
207  CALL gather_and_write_mpi(zcorner_lat,zcorner_lat_tot)
208  CALL gather_and_write_mpi(zarea,zarea_tot)
209  CALL gather_and_write_mpi(imask,imask_tot)
210  !
211  IF (nrank==npio) THEN
212  CALL oasis_write_grid (ysfx_land,u%NDIM_FULL,1,zlon_tot(:,:),zlat_tot(:,:))
213  CALL oasis_write_corner(ysfx_land,u%NDIM_FULL,1,inc,zcorner_lon_tot(:,:,:),zcorner_lat_tot(:,:,:))
214  CALL oasis_write_area (ysfx_land,u%NDIM_FULL,1,zarea_tot(:,:))
215  CALL oasis_write_mask (ysfx_land,u%NDIM_FULL,1,imask_tot(:,:))
216  ENDIF
217  !
218 ENDIF
219 !
220 !* 1.2 Grid definition for lake surface :
221 ! ----------------------------------
222 !
223 IF(lcpl_lake)THEN
224  !
225  zarea(:,1) = ug%G%XMESH_SIZE(:) * zmask_lake(:)
226  !0 = not masked ; 1 = masked
227  WHERE(zarea(:,1)>0.0)
228  imask(:,1) = 0
229  ELSEWHERE
230  imask(:,1) = 1
231  ENDWHERE
232  !
233  CALL gather_and_write_mpi(zlon,zlon_tot)
234  CALL gather_and_write_mpi(zlat,zlat_tot)
235  CALL gather_and_write_mpi(zcorner_lon,zcorner_lon_tot)
236  CALL gather_and_write_mpi(zcorner_lat,zcorner_lat_tot)
237  CALL gather_and_write_mpi(zarea,zarea_tot)
238  CALL gather_and_write_mpi(imask,imask_tot)
239  !
240  IF (nrank==npio) THEN
241  CALL oasis_write_grid (ysfx_lake,u%NDIM_FULL,1,zlon_tot(:,:),zlat_tot(:,:))
242  CALL oasis_write_corner(ysfx_lake,u%NDIM_FULL,1,inc,zcorner_lon_tot(:,:,:),zcorner_lat_tot(:,:,:))
243  CALL oasis_write_area (ysfx_lake,u%NDIM_FULL,1,zarea_tot(:,:))
244  CALL oasis_write_mask (ysfx_lake,u%NDIM_FULL,1,imask_tot(:,:))
245  ENDIF
246  !
247 ENDIF
248 !
249 !* 1.3 Grid definition for sea/water :
250 ! -------------------------------
251 !
252 IF(lcpl_sea)THEN
253  !
254  zarea(:,1) = ug%G%XMESH_SIZE(:) * zmask_sea(:)
255  !0 = not masked ; 1 = masked
256  WHERE(zarea(:,1)>0.0)
257  imask(:,1) = 0
258  ELSEWHERE
259  imask(:,1) = 1
260  ENDWHERE
261  !
262  CALL gather_and_write_mpi(zlon,zlon_tot)
263  CALL gather_and_write_mpi(zlat,zlat_tot)
264  CALL gather_and_write_mpi(zcorner_lon,zcorner_lon_tot)
265  CALL gather_and_write_mpi(zcorner_lat,zcorner_lat_tot)
266  CALL gather_and_write_mpi(zarea,zarea_tot)
267  CALL gather_and_write_mpi(imask,imask_tot)
268  !
269  IF (nrank==npio) THEN
270  CALL oasis_write_grid (ysfx_sea,u%NDIM_FULL,1,zlon_tot(:,:),zlat_tot(:,:))
271  CALL oasis_write_corner(ysfx_sea,u%NDIM_FULL,1,inc,zcorner_lon_tot(:,:,:),zcorner_lat_tot(:,:,:))
272  CALL oasis_write_area (ysfx_sea,u%NDIM_FULL,1,zarea_tot(:,:))
273  CALL oasis_write_mask (ysfx_sea,u%NDIM_FULL,1,imask_tot(:,:))
274  ENDIF
275  !
276 ENDIF
277 !
278 IF (nrank==npio) CALL oasis_terminate_grids_writing()
279 !
280  CALL oasis_enddef(ierr)
281 !
282 IF(ierr/=oasis_ok)THEN
283  WRITE(iluout,*)'SFX_OASIS_PREP: OASIS enddef problem, err = ',ierr
284  CALL abor1_sfx('SFX_OASIS_PREP: OASIS enddef problem')
285 ENDIF
286 !
287 !-------------------------------------------------------------------------------
288 #endif
289 !-------------------------------------------------------------------------------
290 !
291 IF (lhook) CALL dr_hook('SFX_OASIS_PREP',1,zhook_handle)
292 !
293 !-------------------------------------------------------------------------------
294 !
295 END SUBROUTINE sfx_oasis_prep
subroutine get_mesh_corner(UG, KLUOUT, PCORNER_LAT, PCORNER_LON)
subroutine sfx_oasis_check(IO, U, KLUOUT)
subroutine abor1_sfx(YTEXT)
Definition: abor1_sfx.F90:7
subroutine sfx_oasis_prep(IO, S, UG, U, HPROGRAM, KNPTS, KPARAL)
real, parameter xundef
integer, parameter jprb
Definition: parkind1.F90:32
subroutine get_luout(HPROGRAM, KLUOUT)
Definition: get_luout.F90:7
logical lhook
Definition: yomhook.F90:15