SURFEX  V8_0
Surfex V8_0 release
 All Classes Files Functions Variables
sfx_oasis_recv_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_recv_ol (F, I, S, U, W, &
7  hprogram,ki,ksw,ptimec,ptstep_surf, &
8  ksize_omp,pzenith,psw_bands, &
9  ptsrad,pdir_alb,psca_alb,pemis,ptsurf )
10 !#############################################
11 !
12 !!**** *SFX_OASIS_RECV_OL* - Offline driver that receive coupling fields from oasis
13 !!
14 !! PURPOSE
15 !! -------
16 !!
17 !!** METHOD
18 !! ------
19 !!
20 !! EXTERNAL
21 !! --------
22 !!
23 !!
24 !! IMPLICIT ARGUMENTS
25 !! ------------------
26 !!
27 !! REFERENCE
28 !! ---------
29 !!
30 !!
31 !! AUTHOR
32 !! ------
33 !! B. Decharme *Meteo France*
34 !!
35 !! MODIFICATIONS
36 !! -------------
37 !! Original 10/2013
38 !-------------------------------------------------------------------------------
39 !
40 !* 0. DECLARATIONS
41 ! ------------
42 !
43 USE modn_sfx_oasis, ONLY : xtstep_cpl_land, &
44  xtstep_cpl_sea, &
45  lwater
46 !
47 USE modd_sfx_oasis, ONLY : lcpl_land, &
48  lcpl_gw,lcpl_flood,&
49  lcpl_sea, &
50  lcpl_seaice
51 !
52 USE modd_off_surfex_n, ONLY : goto_model
53 !
54 USE modd_flake_n, ONLY : flake_t
55 USE modd_isba_n, ONLY : isba_t
56 USE modd_seaflux_n, ONLY : seaflux_t
57 USE modd_surf_atm_n, ONLY : surf_atm_t
58 USE modd_watflux_n, ONLY : watflux_t
59 !
60 USE modd_surf_par, ONLY : xundef
61 !
62 USE modd_surfex_omp, ONLY : nindx1sfx, nindx2sfx, nblock, nblocktot, &
64 !
65 USE modi_get_luout
66 USE modi_sfx_oasis_recv
67 USE modi_put_sfx_land
68 USE modi_put_sfx_sea
69 USE modi_update_esm_surf_atm_n
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_t), INTENT(INOUT) :: i
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=6), INTENT(IN) :: hprogram ! program calling surf. schemes
95 !
96 INTEGER, INTENT(IN) :: ki ! number of points on this proc
97 INTEGER, INTENT(IN) :: ksw ! number of short-wave spectral bands
98 REAL, INTENT(IN) :: ptimec ! Cumulated run time step (s)
99 REAL, INTENT(IN) :: ptstep_surf ! Surfex time step
100 INTEGER, DIMENSION(:), INTENT(IN) :: ksize_omp
101 !
102 REAL, DIMENSION(KI), INTENT(IN) :: pzenith ! zenithal angle (radian from the vertical)
103 REAL, DIMENSION(KSW), INTENT(IN) :: psw_bands ! mean wavelength of each shortwave band (m)
104 !
105 REAL, DIMENSION(KI), INTENT(OUT) :: ptsrad ! radiative temperature (K)
106 REAL, DIMENSION(KI,KSW),INTENT(OUT) :: pdir_alb ! direct albedo for each spectral band (-)
107 REAL, DIMENSION(KI,KSW),INTENT(OUT) :: psca_alb ! diffuse albedo for each spectral band (-)
108 REAL, DIMENSION(KI), INTENT(OUT) :: pemis ! emissivity (-)
109 REAL, DIMENSION(KI), INTENT(OUT) :: ptsurf ! surface effective temperature (K)
110 !
111 !
112 !* 0.2 Declarations of local variables
113 ! -------------------------------
114 !
115 REAL, DIMENSION(KI) :: zland_wtd ! Land water table depth (m)
116 REAL, DIMENSION(KI) :: zland_fwtd ! Land grid-cell fraction of water table rise (-)
117 REAL, DIMENSION(KI) :: zland_fflood ! Land Floodplains fraction (-)
118 REAL, DIMENSION(KI) :: zland_piflood ! Land Potential flood infiltration(kg/m2/s)
119 REAL, DIMENSION(KI) :: zsea_sst ! Sea surface temperature (K)
120 REAL, DIMENSION(KI) :: zsea_ucu ! Sea u-current stress (Pa)
121 REAL, DIMENSION(KI) :: zsea_vcu ! Sea v-current stress (Pa)
122 REAL, DIMENSION(KI) :: zseaice_sit ! Sea-ice Temperature (K)
123 REAL, DIMENSION(KI) :: zseaice_cvr ! Sea-ice cover (-)
124 REAL, DIMENSION(KI) :: zseaice_alb ! Sea-ice albedo (-)
125 !
126 REAL :: ztime_cpl
127 !
128 LOGICAL :: grecv_land
129 LOGICAL :: grecv_flood
130 LOGICAL :: grecv_sea
131 !
132 INTEGER :: inkproma, iluout
133 !
134 REAL(KIND=JPRB) :: zhook_handle
135 !
136 !-------------------------------------------------------------------------------
137 !
138 IF (lhook) CALL dr_hook('SFX_OASIS_RECV_OL',0,zhook_handle)
139 !
140 !-------------------------------------------------------------------------------
141 !
142 !* 1. init coupling fields:
143 ! ----------------------------------
144 !
145 ztime_cpl = ptimec-ptstep_surf
146 !
147 grecv_land=(lcpl_land.AND.mod(ztime_cpl,xtstep_cpl_land)==0.0)
148 grecv_sea =(lcpl_sea .AND.mod(ztime_cpl,xtstep_cpl_sea )==0.0)
149 !
150 IF(.NOT.(grecv_land.OR.grecv_sea))THEN
151  IF (lhook) CALL dr_hook('SFX_OASIS_RECV_OL',1,zhook_handle)
152  RETURN
153 ENDIF
154 !
155  CALL get_luout(hprogram,iluout)
156 !
157 IF(grecv_land)THEN
158  zland_wtd(:) = xundef
159  zland_fwtd(:) = xundef
160  zland_fflood(:) = xundef
161  zland_piflood(:) = xundef
162 ENDIF
163 !
164 IF(grecv_sea)THEN
165  zsea_sst(:) = xundef
166  zsea_ucu(:) = xundef
167  zsea_vcu(:) = xundef
168  zseaice_sit(:) = xundef
169  zseaice_cvr(:) = xundef
170  zseaice_alb(:) = xundef
171 ENDIF
172 !
173 !* 2. Receive fields to other models proc by proc:
174 ! --------------------------------------------
175 !
176  CALL sfx_oasis_recv(hprogram,ki,ksw,ztime_cpl, &
177  grecv_land, grecv_sea, &
178  zland_wtd(:),zland_fwtd(:), &
179  zland_fflood(:),zland_piflood(:), &
180  zsea_sst(:),zsea_ucu(:), &
181  zsea_vcu(:),zseaice_sit(:), &
182  zseaice_cvr(:),zseaice_alb(:) )
183 !
184 !* 3. Put definitions for exchange of coupling fields :
185 ! -------------------------------------------------
186 !
187 !$OMP PARALLEL PRIVATE(INKPROMA)
188 !
189 !$ NBLOCK = OMP_GET_THREAD_NUM()
190 !
191 IF (nblock==nblocktot) THEN
192  CALL init_dim(ksize_omp,0,inkproma,nindx1sfx,nindx2sfx)
193 ELSE
194  CALL init_dim(ksize_omp,nblock,inkproma,nindx1sfx,nindx2sfx)
195 ENDIF
196 !
197 IF (nblock==0) THEN
198  CALL goto_model(nblocktot)
199 ELSE
200  CALL goto_model(nblock)
201 ENDIF
202 !
203 !-------------------------------------------------------------------------------
204 ! Put variable over land tile
205 !-------------------------------------------------------------------------------
206 !
207 IF(grecv_land)THEN
208  CALL put_sfx_land(i, u, &
209  iluout,lcpl_gw,lcpl_flood, &
210  zland_wtd(nindx1sfx:nindx2sfx),zland_fwtd(nindx1sfx:nindx2sfx), &
211  zland_fflood(nindx1sfx:nindx2sfx),zland_piflood(nindx1sfx:nindx2sfx) )
212 ENDIF
213 !
214 !-------------------------------------------------------------------------------
215 ! Put variable over sea and/or water tile
216 !-------------------------------------------------------------------------------
217 !
218 IF(grecv_sea)THEN
219  CALL put_sfx_sea(s, u, w, &
220  iluout,lcpl_seaice,lwater, &
221  zsea_sst(nindx1sfx:nindx2sfx),zsea_ucu(nindx1sfx:nindx2sfx), &
222  zsea_vcu(nindx1sfx:nindx2sfx),zseaice_sit(nindx1sfx:nindx2sfx), &
223  zseaice_cvr(nindx1sfx:nindx2sfx),zseaice_alb(nindx1sfx:nindx2sfx) )
224 ENDIF
225 !
226 !-------------------------------------------------------------------------------
227 ! Update radiative properties at time t+1 for radiative scheme
228 !-------------------------------------------------------------------------------
229 !
230 grecv_flood=(grecv_land.AND.lcpl_flood)
231 !
232 IF(grecv_sea.OR.grecv_flood)THEN
233  CALL update_esm_surf_atm_n(f, i, s, u, w, &
234  hprogram, inkproma, ksw, pzenith(nindx1sfx:nindx2sfx), psw_bands, &
235  ptsrad(nindx1sfx:nindx2sfx), pdir_alb(nindx1sfx:nindx2sfx,:), &
236  psca_alb(nindx1sfx:nindx2sfx,:), pemis(nindx1sfx:nindx2sfx), &
237  ptsurf(nindx1sfx:nindx2sfx) )
238 ENDIF
239 !
240  CALL reset_dim(ki,inkproma,nindx1sfx,nindx2sfx)
241 !
242 !$OMP END PARALLEL
243 !
244 !-------------------------------------------------------------------------------
245 !
246 IF (lhook) CALL dr_hook('SFX_OASIS_RECV_OL',1,zhook_handle)
247 !
248 !-------------------------------------------------------------------------------
249 !
250 END SUBROUTINE sfx_oasis_recv_ol
subroutine sfx_oasis_recv(HPROGRAM, KI, KSW, PTIMEC, ORECV_LAND, ORECV_SEA, PLAND_WTD, PLAND_FWTD, PLAND_FFLOOD, PLAND_PIFLOOD, PSEA_SST, PSEA_UCU, PSEA_VCU, PSEAICE_SIT, PSEAICE_CVR, PSEAICE_ALB)
subroutine put_sfx_land(I, U, KLUOUT, OCPL_WTD, OCPL_FLOOD, PWTD, PFWTD, PFFLOOD, PPIFLOOD)
Definition: put_sfx_land.F90:6
subroutine put_sfx_sea(S, U, W, KLUOUT, OCPL_SEAICE, OWATER, PSEA_SST, PSEA_UCU, PSEA_VCU, PSEAICE_SIT, PSEAICE_CVR, PSEAICE_ALB)
Definition: put_sfx_sea.F90:6
subroutine sfx_oasis_recv_ol(F, I, S, U, W, HPROGRAM, KI, KSW, PTIMEC, PTSTEP_SURF, KSIZE_OMP, PZENITH, PSW_BANDS, PTSRAD, PDIR_ALB, PSCA_ALB, PEMIS, PTSURF)
subroutine update_esm_surf_atm_n(F, I, S, U, W, HPROGRAM, KI, KSW, PZENITH, PSW_BANDS, PTRAD, PDIR_ALB, PSCA_ALB, PEMIS, PTSURF)
subroutine goto_model(KMODEL)
subroutine get_luout(HPROGRAM, KLUOUT)
Definition: get_luout.F90:6
subroutine init_dim(KSIZE_OMP, KBLOCK, KKPROMA, KINDX1, KINDX2)
subroutine reset_dim(KNI, KKPROMA, KINDX1, KINDX2)