SURFEX  V8_0
Surfex V8_0 release
 All Classes Files Functions Variables
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 (I, UG, U, &
7  hprogram)
8 !###################################################
9 !
10 !!**** *SFX_OASIS_PREP* - Prepare grid areas and mask file for SFX-OASIS coupling
11 !!
12 !! PURPOSE
13 !! -------
14 !!
15 !!** METHOD
16 !! ------
17 !!
18 !! EXTERNAL
19 !! --------
20 !!
21 !!
22 !! IMPLICIT ARGUMENTS
23 !! ------------------
24 !!
25 !! REFERENCE
26 !! ---------
27 !!
28 !!
29 !! AUTHOR
30 !! ------
31 !! B. Decharme *Meteo France*
32 !!
33 !! MODIFICATIONS
34 !! -------------
35 !! Original 10/2013
36 !-------------------------------------------------------------------------------
37 !
38 !* 0. DECLARATIONS
39 ! ------------
40 !
41 !
42 USE modd_isba_n, ONLY : isba_t
44 USE modd_surf_atm_n, ONLY : surf_atm_t
45 !
46 USE modd_surf_par, ONLY : xundef
47 !
48 !
49 !
50 !
53 !
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 !
73 TYPE(isba_t), INTENT(INOUT) :: i
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 !
79 !
80 !* 0.2 Declarations of local parameter
81 ! -------------------------------
82 !
83 INTEGER, PARAMETER :: inc = 4 ! Number of grid-cell corners
84 !
85  CHARACTER(LEN=4), PARAMETER :: ysfx_land = 'slan'
86  CHARACTER(LEN=4), PARAMETER :: ysfx_qsb = 'sdra'
87  CHARACTER(LEN=4), PARAMETER :: ysfx_gw = 'sgw '
88  CHARACTER(LEN=4), PARAMETER :: ysfx_sea = 'ssea'
89  CHARACTER(LEN=4), PARAMETER :: ysfx_lake = 'slak'
90 !
91 !* 0.3 Declarations of local variables
92 ! -------------------------------
93 !
94 REAL, DIMENSION(U%NDIM_FULL) :: zgw ! groundwater mask
95 REAL, DIMENSION(U%NDIM_FULL) :: zmask_land ! land-sea mask for rrm coupling
96 REAL, DIMENSION(U%NDIM_FULL) :: zmask_lake ! lake mask for ogcm coupling
97 REAL, DIMENSION(U%NDIM_FULL) :: zmask_sea ! sea-land mask for ogcm coupling
98 !
99 REAL, DIMENSION(U%NDIM_FULL,1) :: zlon
100 REAL, DIMENSION(U%NDIM_FULL,1) :: zlat
101 REAL, DIMENSION(U%NDIM_FULL,1) :: zarea
102 INTEGER, DIMENSION(U%NDIM_FULL,1) :: imask
103 !
104 REAL, DIMENSION(U%NDIM_FULL,1,INC) :: zcorner_lon
105 REAL, DIMENSION(U%NDIM_FULL,1,INC) :: zcorner_lat
106 !
107 INTEGER, DIMENSION(2) :: ivar_shape ! indexes for the coupling field local dimension
108 !
109 INTEGER :: ipart_id ! Local partition ID
110 INTEGER :: ierr ! Error info
111 !
112 INTEGER :: iluout, iflag
113 !
114 INTEGER :: ji, jc
115 !
116 REAL(KIND=JPRB) :: zhook_handle
117 !
118 !-------------------------------------------------------------------------------
119 !
120 IF (lhook) CALL dr_hook('SFX_OASIS_PREP',0,zhook_handle)
121 !
122 !-------------------------------------------------------------------------------
123 #ifdef CPLOASIS
124 !-------------------------------------------------------------------------------
125 !
126 !
127 !* 0. Initialize :
128 ! ------------
129 !
130  CALL get_luout(hprogram,iluout)
131 !
132  CALL sfx_oasis_check(i, u, &
133  iluout)
134 !
135 !-------------------------------------------------------------------------------
136 !
137 !* 2. Get grid definition :
138 ! ---------------------
139 !
140  CALL get_mesh_corner(ug, &
141  iluout,zcorner_lat(:,1,:),zcorner_lon(:,1,:))
142 !
143 zlon(:,1)=ug%XLON(:)
144 zlat(:,1)=ug%XLAT(:)
145 !
146 IF(lcpl_gw.AND.i%LGW)THEN
147  CALL unpack_same_rank(u%NR_NATURE(:),i%XGW(:),zgw(:))
148  WHERE(zgw(:)==xundef)
149  zgw(:)=0.0
150  ELSEWHERE(zgw(:)>0.0)
151  zgw(:)=1.0
152  ENDWHERE
153 ELSE
154  zgw(:) = 0.0
155 ENDIF
156 !
157 !-------------------------------------------------------------------------------
158 !
159 !* 3. Comput masks :
160 ! --------------
161 !
162 zmask_land(:) = u%XNATURE(:)+u%XTOWN(:)
163 zmask_sea(:) = u%XSEA (:)
164 IF(u%CWATER=='FLAKE ')THEN
165  zmask_lake(:) = u%XWATER (:)
166 ELSE
167  zmask_lake(:) = xundef
168 ENDIF
169 IF(lcpl_sea.AND.lwater)THEN
170  zmask_sea(:) = u%XSEA (:)+u%XWATER(:)
171 ENDIF
172 !
173 !-------------------------------------------------------------------------------
174 !
175 !* 5. Write grid definition :
176 ! -----------------------
177 !
178 !
179 !
180  CALL oasis_start_grids_writing(iflag)
181 !
182 !* 1.1 Grid definition for Land surface :
183 ! ----------------------------------
184 !
185 IF(lcpl_land)THEN
186 !
187  zarea(:,1) = ug%XMESH_SIZE(:) * zmask_land(:)
188  !0 = not masked ; 1 = masked
189  WHERE(zarea(:,1)>0.0)
190  imask(:,1) = 0
191  ELSEWHERE
192  imask(:,1) = 1
193  ENDWHERE
194  CALL oasis_write_grid(ysfx_land,u%NDIM_FULL,1,zlon(:,:),zlat(:,:))
195  CALL oasis_write_corner(ysfx_land,u%NDIM_FULL,1,inc,zcorner_lon(:,:,:),zcorner_lat(:,:,:))
196  CALL oasis_write_area(ysfx_land,u%NDIM_FULL,1,zarea(:,:))
197  CALL oasis_write_mask(ysfx_land,u%NDIM_FULL,1,imask(:,:))
198 !
199  zarea(:,1) = ug%XMESH_SIZE(:) * zmask_land(:) * (1.0-zgw(:))
200  !0 = not masked ; 1 = masked
201  WHERE(zarea(:,1)>0.0)
202  imask(:,1) = 0
203  ELSEWHERE
204  imask(:,1) = 1
205  ENDWHERE
206  CALL oasis_write_grid(ysfx_qsb,u%NDIM_FULL,1,zlon(:,:),zlat(:,:))
207  CALL oasis_write_corner(ysfx_qsb,u%NDIM_FULL,1,inc,zcorner_lon(:,:,:),zcorner_lat(:,:,:))
208  CALL oasis_write_area(ysfx_qsb,u%NDIM_FULL,1,zarea(:,:))
209  CALL oasis_write_mask(ysfx_qsb,u%NDIM_FULL,1,imask(:,:))
210 !
211 ENDIF
212 !
213 ! groundwater surface coupling case
214 !
215 IF(lcpl_gw)THEN
216  zarea(:,1) = ug%XMESH_SIZE(:) * zgw(:)
217  !0 = not masked ; 1 = masked
218  WHERE(zarea(:,1)>0.0)
219  imask(:,1) = 0
220  ELSEWHERE
221  imask(:,1) = 1
222  ENDWHERE
223  CALL oasis_write_grid(ysfx_gw,u%NDIM_FULL,1,zlon(:,:),zlat(:,:))
224  CALL oasis_write_corner(ysfx_gw,u%NDIM_FULL,1,inc,zcorner_lon(:,:,:),zcorner_lat(:,:,:))
225  CALL oasis_write_area(ysfx_gw,u%NDIM_FULL,1,zarea(:,:))
226  CALL oasis_write_mask(ysfx_gw,u%NDIM_FULL,1,imask(:,:))
227 ENDIF
228 !
229 !* 1.2 Grid definition for lake surface :
230 ! ----------------------------------
231 !
232 IF(lcpl_lake)THEN
233  zarea(:,1) = ug%XMESH_SIZE(:) * zmask_lake(:)
234  !0 = not masked ; 1 = masked
235  WHERE(zarea(:,1)>0.0)
236  imask(:,1) = 0
237  ELSEWHERE
238  imask(:,1) = 1
239  ENDWHERE
240  CALL oasis_write_grid(ysfx_lake,u%NDIM_FULL,1,zlon(:,:),zlat(:,:))
241  CALL oasis_write_corner(ysfx_lake,u%NDIM_FULL,1,inc,zcorner_lon(:,:,:),zcorner_lat(:,:,:))
242  CALL oasis_write_area(ysfx_lake,u%NDIM_FULL,1,zarea(:,:))
243  CALL oasis_write_mask(ysfx_lake,u%NDIM_FULL,1,imask(:,:))
244 ENDIF
245 !
246 !* 1.3 Grid definition for sea/water :
247 ! -------------------------------
248 !
249 IF(lcpl_sea)THEN
250  zarea(:,1) = ug%XMESH_SIZE(:) * zmask_sea(:)
251  !0 = not masked ; 1 = masked
252  WHERE(zarea(:,1)>0.0)
253  imask(:,1) = 0
254  ELSEWHERE
255  imask(:,1) = 1
256  ENDWHERE
257  CALL oasis_write_grid(ysfx_sea,u%NDIM_FULL,1,zlon(:,:),zlat(:,:))
258  CALL oasis_write_corner(ysfx_sea,u%NDIM_FULL,1,inc,zcorner_lon(:,:,:),zcorner_lat(:,:,:))
259  CALL oasis_write_area(ysfx_sea,u%NDIM_FULL,1,zarea(:,:))
260  CALL oasis_write_mask(ysfx_sea,u%NDIM_FULL,1,imask(:,:))
261 ENDIF
262 !
263  CALL oasis_terminate_grids_writing()
264 !
265  CALL oasis_enddef(ierr)
266 !
267 IF(ierr/=oasis_ok)THEN
268  WRITE(iluout,*)'SFX_OASIS_PREP: OASIS enddef problem, err = ',ierr
269  CALL abor1_sfx('SFX_OASIS_PREP: OASIS enddef problem')
270 ENDIF
271 !
272 !-------------------------------------------------------------------------------
273 #endif
274 !-------------------------------------------------------------------------------
275 !
276 IF (lhook) CALL dr_hook('SFX_OASIS_PREP',1,zhook_handle)
277 !
278 !-------------------------------------------------------------------------------
279 !
280 END SUBROUTINE sfx_oasis_prep
subroutine get_mesh_corner(UG, KLUOUT, PCORNER_LAT, PCORNER_LON)
subroutine abor1_sfx(YTEXT)
Definition: abor1_sfx.F90:6
subroutine sfx_oasis_check(I, U, KLUOUT)
subroutine get_luout(HPROGRAM, KLUOUT)
Definition: get_luout.F90:6
subroutine sfx_oasis_prep(I, UG, U, HPROGRAM)