SURFEX v8.1
General documentation of Surfex
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, IM, S, U, W, &
7  HPROGRAM,KI,PTIMEC,PSTEP_SURF)
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 !! B. Decharme 10/2016 bug surface/groundwater coupling
37 !-------------------------------------------------------------------------------
38 !
39 !* 0. DECLARATIONS
40 ! ------------
41 !
42 !
43 !
44 USE modd_off_surfex_n, ONLY : goto_model
45 !
46 USE modd_flake_n, ONLY : flake_t
47 USE modd_surfex_n, ONLY : isba_model_t
48 USE modd_seaflux_n, ONLY : seaflux_t
49 USE modd_surf_atm_n, ONLY : surf_atm_t
50 USE modd_watflux_n, ONLY : watflux_t
51 !
52 USE modd_surf_par, ONLY : xundef
53 !
54 USE modn_sfx_oasis, ONLY : xtstep_cpl_land, &
56  xtstep_cpl_sea , &
57  lwater
58 !
59 USE modd_sfx_oasis, ONLY : lcpl_land,lcpl_gw, &
61  lcpl_lake, &
63 !
64 USE modi_get_sfx_land
65 USE modi_get_sfx_lake
66 USE modi_get_sfx_sea
67 !
68 USE modi_get_luout
69 USE modi_sfx_oasis_send
70 !
71 USE yomhook ,ONLY : lhook, dr_hook
72 USE parkind1 ,ONLY : jprb
73 !
74 #ifdef AIX64
75 !$ USE OMP_LIB
76 #endif
77 !
78 IMPLICIT NONE
79 !
80 #ifndef AIX64
81 !$ INCLUDE 'omp_lib.h'
82 #endif
83 !
84 !* 0.1 Declarations of arguments
85 ! -------------------------
86 !
87 !
88 TYPE(flake_t), INTENT(INOUT) :: F
89 TYPE(isba_model_t), INTENT(INOUT) :: IM
90 TYPE(seaflux_t), INTENT(INOUT) :: S
91 TYPE(surf_atm_t), INTENT(INOUT) :: U
92 TYPE(watflux_t), INTENT(INOUT) :: W
93 !
94  CHARACTER(LEN=*), INTENT(IN) :: HPROGRAM
95 INTEGER, INTENT(IN) :: KI ! number of points
96 REAL, INTENT(IN) :: PTIMEC ! Cumulated run time step (s)
97 REAL, INTENT(IN) :: PSTEP_SURF ! Model time step (s)
98 !
99 !
100 !* 0.2 Declarations of local variables
101 ! -------------------------------
102 !
103 REAL, DIMENSION(KI) :: ZLAND_RUNOFF ! Cumulated Surface runoff (kg/m2)
104 REAL, DIMENSION(KI) :: ZLAND_DRAIN ! Cumulated Deep drainage (kg/m2)
105 REAL, DIMENSION(KI) :: ZLAND_CALVING ! Cumulated Calving flux (kg/m2)
106 REAL, DIMENSION(KI) :: ZLAND_WATFLD ! Cumulated net freshwater rate (kg/m2)
107 !
108 REAL, DIMENSION(KI) :: ZLAKE_EVAP ! Cumulated Evaporation (kg/m2)
109 REAL, DIMENSION(KI) :: ZLAKE_RAIN ! Cumulated Rainfall rate (kg/m2)
110 REAL, DIMENSION(KI) :: ZLAKE_SNOW ! Cumulated Snowfall rate (kg/m2)
111 REAL, DIMENSION(KI) :: ZLAKE_WATF ! Cumulated net freshwater rate (kg/m2)
112 !
113 REAL, DIMENSION(KI) :: ZSEA_FWSU ! Cumulated zonal wind stress (Pa.s)
114 REAL, DIMENSION(KI) :: ZSEA_FWSV ! Cumulated meridian wind stress (Pa.s)
115 REAL, DIMENSION(KI) :: ZSEA_HEAT ! Cumulated Non solar net heat flux (J/m2)
116 REAL, DIMENSION(KI) :: ZSEA_SNET ! Cumulated Solar net heat flux (J/m2)
117 REAL, DIMENSION(KI) :: ZSEA_WIND ! Cumulated 10m wind speed (m)
118 REAL, DIMENSION(KI) :: ZSEA_FWSM ! Cumulated wind stress (Pa.s)
119 REAL, DIMENSION(KI) :: ZSEA_EVAP ! Cumulated Evaporation (kg/m2)
120 REAL, DIMENSION(KI) :: ZSEA_RAIN ! Cumulated Rainfall rate (kg/m2)
121 REAL, DIMENSION(KI) :: ZSEA_SNOW ! Cumulated Snowfall rate (kg/m2)
122 REAL, DIMENSION(KI) :: ZSEA_WATF ! Cumulated net freshwater rate (kg/m2)
123 !
124 REAL, DIMENSION(KI) :: ZSEAICE_HEAT ! Cumulated Sea-ice non solar net heat flux (J/m2)
125 REAL, DIMENSION(KI) :: ZSEAICE_SNET ! Cumulated Sea-ice solar net heat flux (J/m2)
126 REAL, DIMENSION(KI) :: ZSEAICE_EVAP ! Cumulated Sea-ice sublimation (kg/m2)
127 !
128 INTEGER :: IDATE ! current coupling time step (s)
129 INTEGER :: ILUOUT
130 INTEGER :: INKPROMA
131 !
132 LOGICAL :: GSEND_LAND
133 LOGICAL :: GSEND_LAKE
134 LOGICAL :: GSEND_SEA
135 !
136 REAL(KIND=JPRB) :: ZHOOK_HANDLE
137 !
138 !-------------------------------------------------------------------------------
139 !
140 IF (lhook) CALL dr_hook('SFX_OASIS_SEND_OL',0,zhook_handle)
141 !
142 !-------------------------------------------------------------------------------
143 !
144 !* 1. Initialize proc by proc :
145 ! -------------------------
146 !
147  CALL get_luout(hprogram,iluout)
148 !
149 idate = int(ptimec-pstep_surf)
150 !
151 gsend_land=(lcpl_land.AND.mod(ptimec,xtstep_cpl_land)==0.0)
152 gsend_lake=(lcpl_lake.AND.mod(ptimec,xtstep_cpl_lake)==0.0)
153 gsend_sea =(lcpl_sea .AND.mod(ptimec,xtstep_cpl_sea )==0.0)
154 !
155 !-------------------------------------------------------------------------------
156 !
157 IF(.NOT.(gsend_land.OR.gsend_lake.OR.gsend_sea))THEN
158  IF (lhook) CALL dr_hook('SFX_OASIS_SEND_OL',1,zhook_handle)
159  RETURN
160 ENDIF
161 !
162 !-------------------------------------------------------------------------------
163 !
164 IF(gsend_land)THEN
165  zland_runoff(:) = xundef
166  zland_drain(:) = xundef
167  zland_calving(:) = xundef
168  zland_watfld(:) = xundef
169 ENDIF
170 !
171 IF(gsend_lake)THEN
172  zlake_evap(:) = xundef
173  zlake_rain(:) = xundef
174  zlake_snow(:) = xundef
175  zsea_watf(:) = xundef
176 ENDIF
177 !
178 IF(gsend_sea)THEN
179  zsea_fwsu(:) = xundef
180  zsea_fwsv(:) = xundef
181  zsea_heat(:) = xundef
182  zsea_snet(:) = xundef
183  zsea_wind(:) = xundef
184  zsea_fwsm(:) = xundef
185  zsea_evap(:) = xundef
186  zsea_rain(:) = xundef
187  zsea_snow(:) = xundef
188  zsea_watf(:) = xundef
189  !
190  zseaice_heat(:) = xundef
191  zseaice_snet(:) = xundef
192  zseaice_evap(:) = xundef
193 ENDIF
194 !
195 !-------------------------------------------------------------------------------
196 !
197 !* 2. get local fields :
198 ! ------------------
199 !
200 IF(gsend_land)THEN
201 !
202 ! * Get river output fields
203 !
204  CALL get_sfx_land(im%O, im%S, u, &
206  zland_runoff(:),zland_drain(:),&
207  zland_calving(:),zland_watfld(:))
208 !
209 ENDIF
210 !
211 IF(gsend_lake)THEN
212 !
213 ! * Get output fields
214 !
215  CALL get_sfx_lake(f, u, &
216  zlake_evap(:),zlake_rain(:), &
217  zlake_snow(:),zlake_watf(:) )
218 !
219 ENDIF
220 !
221 IF(gsend_sea)THEN
222 !
223 ! * Get sea output fields
224 !
225  CALL get_sfx_sea(s, u, w, &
227  zsea_fwsu(:),zsea_fwsv(:),zsea_heat(:),&
228  zsea_snet(:),zsea_wind(:),zsea_fwsm(:),&
229  zsea_evap(:),zsea_rain(:),zsea_snow(:),&
230  zsea_watf(:), &
231  zseaice_heat(:),zseaice_snet(:),zseaice_evap(:) )
232 !
233 ENDIF
234 !
235 !-------------------------------------------------------------------------------
236 !
237 !* 3. Send fields to OASIS proc by proc:
238 ! ----------------------------------
239 !
240  CALL sfx_oasis_send(iluout,ki,idate,gsend_land,gsend_lake,gsend_sea, &
241  zland_runoff,zland_drain,zland_calving,zland_watfld, &
242  zlake_evap,zlake_rain,zlake_snow,zlake_watf, &
243  zsea_fwsu,zsea_fwsv,zsea_heat,zsea_snet,zsea_wind, &
244  zsea_fwsm,zsea_evap,zsea_rain,zsea_snow,zsea_watf, &
245  zseaice_heat,zseaice_snet,zseaice_evap )
246 !
247 !-------------------------------------------------------------------------------
248 !
249 IF (lhook) CALL dr_hook('SFX_OASIS_SEND_OL',1,zhook_handle)
250 !
251 !-------------------------------------------------------------------------------
252 !
253 END SUBROUTINE sfx_oasis_send_ol
subroutine sfx_oasis_send_ol(F, IM, S, U, W, HPROGRAM, KI, PTIMEC, PSTEP_SURF)
subroutine get_sfx_lake(F, U, PLAKE_EVAP, PLAKE_RAIN, PLAKE_SNOW, PLAKE_WA
Definition: get_sfx_lake.F90:8
real, parameter xundef
subroutine goto_model(KMODEL)
integer, parameter jprb
Definition: parkind1.F90:32
subroutine get_sfx_land(IO, S, U, OCPL_GW, OCPL_FLOOD, OCPL_CALVING, PRUNOFF, PDRAIN, PCALVING, PSRCFLOOD)
Definition: get_sfx_land.F90:9
subroutine get_luout(HPROGRAM, KLUOUT)
Definition: get_luout.F90:7
subroutine sfx_oasis_send(KLUOUT, KI, KDATE, OSEND_LAND, OSEND_LAKE, OSEND_SEA, PLAND_RUNOFF, PLAND_DRAIN, PLAND_CALVING, 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)
subroutine get_sfx_sea(S, U, W, OCPL_SEAICE, OWATER,
Definition: get_sfx_sea.F90:8
logical lhook
Definition: yomhook.F90:15