SURFEX  V8_0
Surfex V8_0 release
 All Classes Files Functions Variables
sfx_oasis_send_ol.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_send_ol (F, I, S, U, W, &
7  hprogram,ki,ptimec,pstep_surf,ksize_omp)
8 !###########################################
9 !
10 !!**** *SFX_OASIS_SEND_OL* - Offline driver to send coupling fields
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 !
43 USE modd_off_surfex_n, ONLY : goto_model
44 !
45 USE modd_flake_n, ONLY : flake_t
46 USE modd_isba_n, ONLY : isba_t
47 USE modd_seaflux_n, ONLY : seaflux_t
48 USE modd_surf_atm_n, ONLY : surf_atm_t
49 USE modd_watflux_n, ONLY : watflux_t
50 !
51 USE modd_surfex_omp, ONLY : nindx1sfx, nindx2sfx, nblock, nblocktot, &
53 !
54 USE modd_surf_par, ONLY : xundef
55 !
56 USE modn_sfx_oasis, ONLY : xtstep_cpl_land, &
57  xtstep_cpl_lake, &
58  xtstep_cpl_sea , &
59  lwater
60 !
61 USE modd_sfx_oasis, ONLY : lcpl_land,lcpl_gw, &
62  lcpl_flood,lcpl_calving, &
63  lcpl_lake, &
64  lcpl_sea,lcpl_seaice
65 !
66 USE modi_get_sfx_land
67 USE modi_get_sfx_lake
68 USE modi_get_sfx_sea
69 !
70 USE modi_get_luout
71 USE modi_sfx_oasis_send
72 !
73 USE yomhook ,ONLY : lhook, dr_hook
74 USE parkind1 ,ONLY : jprb
75 !
76 #ifdef AIX64
77 !$ USE OMP_LIB
78 #endif
79 !
80 IMPLICIT NONE
81 !
82 #ifndef AIX64
83 !$ INCLUDE 'omp_lib.h'
84 #endif
85 !
86 !* 0.1 Declarations of arguments
87 ! -------------------------
88 !
89 !
90 TYPE(flake_t), INTENT(INOUT) :: f
91 TYPE(isba_t), INTENT(INOUT) :: i
92 TYPE(seaflux_t), INTENT(INOUT) :: s
93 TYPE(surf_atm_t), INTENT(INOUT) :: u
94 TYPE(watflux_t), INTENT(INOUT) :: w
95 !
96  CHARACTER(LEN=*), INTENT(IN) :: hprogram
97 INTEGER, INTENT(IN) :: ki ! number of points
98 REAL, INTENT(IN) :: ptimec ! Cumulated run time step (s)
99 REAL, INTENT(IN) :: pstep_surf ! Model time step (s)
100 INTEGER, DIMENSION(:), INTENT(IN) :: ksize_omp
101 !
102 !
103 !* 0.2 Declarations of local variables
104 ! -------------------------------
105 !
106 REAL, DIMENSION(KI) :: zland_runoff ! Cumulated Surface runoff (kg/m2)
107 REAL, DIMENSION(KI) :: zland_drain ! Cumulated Deep drainage (kg/m2)
108 REAL, DIMENSION(KI) :: zland_calving ! Cumulated Calving flux (kg/m2)
109 REAL, DIMENSION(KI) :: zland_recharge ! Cumulated Recharge to groundwater (kg/m2)
110 REAL, DIMENSION(KI) :: zland_watfld ! Cumulated net freshwater rate (kg/m2)
111 !
112 REAL, DIMENSION(KI) :: zlake_evap ! Cumulated Evaporation (kg/m2)
113 REAL, DIMENSION(KI) :: zlake_rain ! Cumulated Rainfall rate (kg/m2)
114 REAL, DIMENSION(KI) :: zlake_snow ! Cumulated Snowfall rate (kg/m2)
115 REAL, DIMENSION(KI) :: zlake_watf ! Cumulated net freshwater rate (kg/m2)
116 !
117 REAL, DIMENSION(KI) :: zsea_fwsu ! Cumulated zonal wind stress (Pa.s)
118 REAL, DIMENSION(KI) :: zsea_fwsv ! Cumulated meridian wind stress (Pa.s)
119 REAL, DIMENSION(KI) :: zsea_heat ! Cumulated Non solar net heat flux (J/m2)
120 REAL, DIMENSION(KI) :: zsea_snet ! Cumulated Solar net heat flux (J/m2)
121 REAL, DIMENSION(KI) :: zsea_wind ! Cumulated 10m wind speed (m)
122 REAL, DIMENSION(KI) :: zsea_fwsm ! Cumulated wind stress (Pa.s)
123 REAL, DIMENSION(KI) :: zsea_evap ! Cumulated Evaporation (kg/m2)
124 REAL, DIMENSION(KI) :: zsea_rain ! Cumulated Rainfall rate (kg/m2)
125 REAL, DIMENSION(KI) :: zsea_snow ! Cumulated Snowfall rate (kg/m2)
126 REAL, DIMENSION(KI) :: zsea_watf ! Cumulated net freshwater rate (kg/m2)
127 !
128 REAL, DIMENSION(KI) :: zseaice_heat ! Cumulated Sea-ice non solar net heat flux (J/m2)
129 REAL, DIMENSION(KI) :: zseaice_snet ! Cumulated Sea-ice solar net heat flux (J/m2)
130 REAL, DIMENSION(KI) :: zseaice_evap ! Cumulated Sea-ice sublimation (kg/m2)
131 !
132 INTEGER :: idate ! current coupling time step (s)
133 INTEGER :: iluout
134 INTEGER :: inkproma
135 !
136 LOGICAL :: gsend_land
137 LOGICAL :: gsend_lake
138 LOGICAL :: gsend_sea
139 !
140 REAL(KIND=JPRB) :: zhook_handle
141 !
142 !-------------------------------------------------------------------------------
143 !
144 IF (lhook) CALL dr_hook('SFX_OASIS_SEND_OL',0,zhook_handle)
145 !
146 !-------------------------------------------------------------------------------
147 !
148 !* 1. Initialize proc by proc :
149 ! -------------------------
150 !
151  CALL get_luout(hprogram,iluout)
152 !
153 idate = int(ptimec-pstep_surf)
154 !
155 gsend_land=(lcpl_land.AND.mod(ptimec,xtstep_cpl_land)==0.0)
156 gsend_lake=(lcpl_lake.AND.mod(ptimec,xtstep_cpl_lake)==0.0)
157 gsend_sea =(lcpl_sea .AND.mod(ptimec,xtstep_cpl_sea )==0.0)
158 !
159 !-------------------------------------------------------------------------------
160 !
161 IF(.NOT.(gsend_land.OR.gsend_lake.OR.gsend_sea))THEN
162  IF (lhook) CALL dr_hook('SFX_OASIS_SEND_OL',1,zhook_handle)
163  RETURN
164 ENDIF
165 !
166 !-------------------------------------------------------------------------------
167 !
168 IF(gsend_land)THEN
169  zland_runoff(:) = xundef
170  zland_drain(:) = xundef
171  zland_calving(:) = xundef
172  zland_recharge(:) = xundef
173  zland_watfld(:) = xundef
174 ENDIF
175 !
176 IF(gsend_lake)THEN
177  zlake_evap(:) = xundef
178  zlake_rain(:) = xundef
179  zlake_snow(:) = xundef
180  zsea_watf(:) = xundef
181 ENDIF
182 !
183 IF(gsend_sea)THEN
184  zsea_fwsu(:) = xundef
185  zsea_fwsv(:) = xundef
186  zsea_heat(:) = xundef
187  zsea_snet(:) = xundef
188  zsea_wind(:) = xundef
189  zsea_fwsm(:) = xundef
190  zsea_evap(:) = xundef
191  zsea_rain(:) = xundef
192  zsea_snow(:) = xundef
193  zsea_watf(:) = xundef
194  !
195  zseaice_heat(:) = xundef
196  zseaice_snet(:) = xundef
197  zseaice_evap(:) = xundef
198 ENDIF
199 !
200 !-------------------------------------------------------------------------------
201 !
202 !$OMP PARALLEL PRIVATE(INKPROMA)
203 !
204 !$ NBLOCK = OMP_GET_THREAD_NUM()
205 !
206 IF (nblock==nblocktot) THEN
207  CALL init_dim(ksize_omp,0,inkproma,nindx1sfx,nindx2sfx)
208 ELSE
209  CALL init_dim(ksize_omp,nblock,inkproma,nindx1sfx,nindx2sfx)
210 ENDIF
211 !
212 IF (nblock==0) THEN
213  CALL goto_model(nblocktot)
214 ELSE
215  CALL goto_model(nblock)
216 ENDIF
217 !
218 !* 2. get local fields :
219 ! ------------------
220 !
221 IF(gsend_land)THEN
222 !
223 ! * Get river output fields
224 !
225  CALL get_sfx_land(i, u, &
226  lcpl_gw,lcpl_flood,lcpl_calving, &
227  zland_runoff(nindx1sfx:nindx2sfx),zland_drain(nindx1sfx:nindx2sfx),&
228  zland_calving(nindx1sfx:nindx2sfx),zland_recharge(nindx1sfx:nindx2sfx),&
229  zland_watfld(nindx1sfx:nindx2sfx))
230 !
231 ENDIF
232 !
233 IF(gsend_lake)THEN
234 !
235 ! * Get output fields
236 !
237  CALL get_sfx_lake(f, u, &
238  zlake_evap(nindx1sfx:nindx2sfx),zlake_rain(nindx1sfx:nindx2sfx), &
239  zlake_snow(nindx1sfx:nindx2sfx),zlake_watf(nindx1sfx:nindx2sfx) )
240 !
241 ENDIF
242 !
243 IF(gsend_sea)THEN
244 !
245 ! * Get sea output fields
246 !
247  CALL get_sfx_sea(s, u, w, &
248  lcpl_seaice,lwater, &
249  zsea_fwsu(nindx1sfx:nindx2sfx),zsea_fwsv(nindx1sfx:nindx2sfx),zsea_heat(nindx1sfx:nindx2sfx),&
250  zsea_snet(nindx1sfx:nindx2sfx),zsea_wind(nindx1sfx:nindx2sfx),zsea_fwsm(nindx1sfx:nindx2sfx),&
251  zsea_evap(nindx1sfx:nindx2sfx),zsea_rain(nindx1sfx:nindx2sfx),zsea_snow(nindx1sfx:nindx2sfx),&
252  zsea_watf(nindx1sfx:nindx2sfx), &
253  zseaice_heat(nindx1sfx:nindx2sfx),zseaice_snet(nindx1sfx:nindx2sfx),zseaice_evap(nindx1sfx:nindx2sfx) )
254 !
255 ENDIF
256 !
257  CALL reset_dim(ki,inkproma,nindx1sfx,nindx2sfx)
258 !
259 !$OMP END PARALLEL
260 !
261 !-------------------------------------------------------------------------------
262 !
263 !* 3. Send fields to OASIS proc by proc:
264 ! ----------------------------------
265 !
266 !
267  CALL sfx_oasis_send(iluout,ki,idate,gsend_land,gsend_lake,gsend_sea, &
268  zland_runoff,zland_drain,zland_calving,zland_recharge,&
269  zland_watfld, &
270  zlake_evap,zlake_rain,zlake_snow,zlake_watf, &
271  zsea_fwsu,zsea_fwsv,zsea_heat,zsea_snet,zsea_wind, &
272  zsea_fwsm,zsea_evap,zsea_rain,zsea_snow,zsea_watf, &
273  zseaice_heat,zseaice_snet,zseaice_evap )
274 !
275 !-------------------------------------------------------------------------------
276 !
277 IF (lhook) CALL dr_hook('SFX_OASIS_SEND_OL',1,zhook_handle)
278 !
279 !-------------------------------------------------------------------------------
280 !
281 END SUBROUTINE sfx_oasis_send_ol
subroutine get_sfx_land(I, U, OCPL_GW, OCPL_FLOOD, OCPL_CALVING, PRUNOFF, PDRAIN, PCALVING, PRECHARGE, PSRCFLOOD)
Definition: get_sfx_land.F90:6
subroutine get_sfx_sea(S, U, W, OCPL_SEAICE, OWATER, PSEA_FWSU, PSEA_FWSV, PSEA_HEAT, PSEA_SNET, PSEA_WIND, PSEA_FWSM, PSEA_EVAP, PSEA_RAIN, PSEA_SNOW, PSEA_WATF, PSEAICE_HEAT, PSEAICE_SNET, PSEAICE_EVAP)
Definition: get_sfx_sea.F90:6
subroutine sfx_oasis_send_ol(F, I, S, U, W, HPROGRAM, KI, PTIMEC, PSTEP_SURF, KSIZE_OMP)
subroutine goto_model(KMODEL)
subroutine get_luout(HPROGRAM, KLUOUT)
Definition: get_luout.F90:6
subroutine init_dim(KSIZE_OMP, KBLOCK, KKPROMA, KINDX1, KINDX2)
subroutine get_sfx_lake(F, U, PLAKE_EVAP, PLAKE_RAIN, PLAKE_SNOW, PLAKE_WATF)
Definition: get_sfx_lake.F90:6
subroutine reset_dim(KNI, KKPROMA, KINDX1, KINDX2)
subroutine sfx_oasis_send(KLUOUT, KI, KDATE, OSEND_LAND, OSEND_LAKE, OSEND_SEA, PLAND_RUNOFF, PLAND_DRAIN, PLAND_CALVING, PLAND_RECHARGE, PLAND_SRCFLOOD, PLAKE_EVAP, PLAKE_RAIN, PLAKE_SNOW, PLAKE_WATF, PSEA_FWSU, PSEA_FWSV, PSEA_HEAT, PSEA_SNET, PSEA_WIND, PSEA_FWSM, PSEA_EVAP, PSEA_RAIN, PSEA_SNOW, PSEA_WATF, PSEAICE_HEAT, PSEAICE_SNET, PSEAICE_EVAP)