SURFEX v8.1
General documentation of Surfex
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, IM, S, U, W, &
7  HPROGRAM,KI,KSW,PTIMEC,PTSTEP_SURF, &
8  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, &
45  lwater
46 !
47 USE modd_sfx_oasis, ONLY : lcpl_land, &
49  lcpl_sea, &
51 !
52 USE modd_off_surfex_n, ONLY : goto_model
53 !
54 USE modd_flake_n, ONLY : flake_t
55 USE modd_surfex_n, ONLY : isba_model_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 modi_get_luout
63 USE modi_sfx_oasis_recv
64 USE modi_put_sfx_land
65 USE modi_put_sfx_sea
66 USE modi_update_esm_surf_atm_n
67 !
68 USE yomhook ,ONLY : lhook, dr_hook
69 USE parkind1 ,ONLY : jprb
70 !
71 #ifdef AIX64
72 !$ USE OMP_LIB
73 #endif
74 !
75 IMPLICIT NONE
76 !
77 #ifndef AIX64
78 !$ INCLUDE 'omp_lib.h'
79 #endif
80 !
81 !* 0.1 Declarations of arguments
82 ! -------------------------
83 !
84 !
85 TYPE(flake_t), INTENT(INOUT) :: F
86 TYPE(isba_model_t), INTENT(INOUT) :: IM
87 TYPE(seaflux_t), INTENT(INOUT) :: S
88 TYPE(surf_atm_t), INTENT(INOUT) :: U
89 TYPE(watflux_t), INTENT(INOUT) :: W
90 !
91  CHARACTER(LEN=6), INTENT(IN) :: HPROGRAM ! program calling surf. schemes
92 !
93 INTEGER, INTENT(IN) :: KI ! number of points on this proc
94 INTEGER, INTENT(IN) :: KSW ! number of short-wave spectral bands
95 REAL, INTENT(IN) :: PTIMEC ! Cumulated run time step (s)
96 REAL, INTENT(IN) :: PTSTEP_SURF ! Surfex time step
97 !
98 REAL, DIMENSION(KI), INTENT(IN) :: PZENITH ! zenithal angle (radian from the vertical)
99 REAL, DIMENSION(KSW), INTENT(IN) :: PSW_BANDS ! mean wavelength of each shortwave band (m)
100 !
101 REAL, DIMENSION(KI), INTENT(OUT) :: PTSRAD ! radiative temperature (K)
102 REAL, DIMENSION(KI,KSW),INTENT(OUT) :: PDIR_ALB ! direct albedo for each spectral band (-)
103 REAL, DIMENSION(KI,KSW),INTENT(OUT) :: PSCA_ALB ! diffuse albedo for each spectral band (-)
104 REAL, DIMENSION(KI), INTENT(OUT) :: PEMIS ! emissivity (-)
105 REAL, DIMENSION(KI), INTENT(OUT) :: PTSURF ! surface effective temperature (K)
106 !
107 !
108 !* 0.2 Declarations of local variables
109 ! -------------------------------
110 !
111 REAL, DIMENSION(KI) :: ZLAND_WTD ! Land water table depth (m)
112 REAL, DIMENSION(KI) :: ZLAND_FWTD ! Land grid-cell fraction of water table rise (-)
113 REAL, DIMENSION(KI) :: ZLAND_FFLOOD ! Land Floodplains fraction (-)
114 REAL, DIMENSION(KI) :: ZLAND_PIFLOOD ! Land Potential flood infiltration (kg/m2/s)
115 REAL, DIMENSION(KI) :: ZSEA_SST ! Sea surface temperature (K)
116 REAL, DIMENSION(KI) :: ZSEA_UCU ! Sea u-current stress (Pa)
117 REAL, DIMENSION(KI) :: ZSEA_VCU ! Sea v-current stress (Pa)
118 REAL, DIMENSION(KI) :: ZSEAICE_SIT ! Sea-ice Temperature (K)
119 REAL, DIMENSION(KI) :: ZSEAICE_CVR ! Sea-ice cover (-)
120 REAL, DIMENSION(KI) :: ZSEAICE_ALB ! Sea-ice albedo (-)
121 !
122 REAL :: ZTIME_CPL
123 !
124 LOGICAL :: GRECV_LAND
125 LOGICAL :: GRECV_FLOOD
126 LOGICAL :: GRECV_SEA
127 !
128 INTEGER :: ILUOUT
129 !
130 REAL(KIND=JPRB) :: ZHOOK_HANDLE
131 !
132 !-------------------------------------------------------------------------------
133 !
134 IF (lhook) CALL dr_hook('SFX_OASIS_RECV_OL',0,zhook_handle)
135 !
136 !-------------------------------------------------------------------------------
137 !
138 !* 1. init coupling fields:
139 ! ----------------------------------
140 !
141 ztime_cpl = ptimec-ptstep_surf
142 !
143 grecv_land=(lcpl_land.AND.mod(ztime_cpl,xtstep_cpl_land)==0.0)
144 grecv_sea =(lcpl_sea .AND.mod(ztime_cpl,xtstep_cpl_sea )==0.0)
145 !
146 IF(.NOT.(grecv_land.OR.grecv_sea))THEN
147  IF (lhook) CALL dr_hook('SFX_OASIS_RECV_OL',1,zhook_handle)
148  RETURN
149 ENDIF
150 !
151  CALL get_luout(hprogram,iluout)
152 !
153 IF(grecv_land)THEN
154  zland_wtd(:) = xundef
155  zland_fwtd(:) = xundef
156  zland_fflood(:) = xundef
157  zland_piflood(:) = xundef
158 ENDIF
159 !
160 IF(grecv_sea)THEN
161  zsea_sst(:) = xundef
162  zsea_ucu(:) = xundef
163  zsea_vcu(:) = xundef
164  zseaice_sit(:) = xundef
165  zseaice_cvr(:) = xundef
166  zseaice_alb(:) = xundef
167 ENDIF
168 !
169 !* 2. Receive fields to other models proc by proc:
170 ! --------------------------------------------
171 !
172  CALL sfx_oasis_recv(hprogram,ki,ksw,ztime_cpl, &
173  grecv_land, grecv_sea, &
174  zland_wtd(:),zland_fwtd(:), &
175  zland_fflood(:),zland_piflood(:), &
176  zsea_sst(:),zsea_ucu(:), &
177  zsea_vcu(:),zseaice_sit(:), &
178  zseaice_cvr(:),zseaice_alb(:) )
179 !
180 !-------------------------------------------------------------------------------
181 ! Put variable over land tile
182 !-------------------------------------------------------------------------------
183 !
184 IF(grecv_land)THEN
185  CALL put_sfx_land(im%O, im%S, im%K, im%NK, im%NP, u, iluout,lcpl_gw,lcpl_flood, zland_wtd(:),&
186  zland_fwtd(:), zland_fflood(:),zland_piflood(:) )
187 ENDIF
188 !
189 !-------------------------------------------------------------------------------
190 ! Put variable over sea and/or water tile
191 !-------------------------------------------------------------------------------
192 !
193 IF(grecv_sea)THEN
194  CALL put_sfx_sea(s, u, w, iluout,lcpl_seaice,lwater, zsea_sst(:),zsea_ucu(:), &
195  zsea_vcu(:),zseaice_sit(:), zseaice_cvr(:),zseaice_alb(:) )
196 ENDIF
197 !
198 !-------------------------------------------------------------------------------
199 ! Update radiative properties at time t+1 for radiative scheme
200 !-------------------------------------------------------------------------------
201 !
202 grecv_flood=(grecv_land.AND.lcpl_flood)
203 !
204 IF(grecv_sea.OR.grecv_flood)THEN
205  CALL update_esm_surf_atm_n(f, im, s, u, w, hprogram, ki, ksw, pzenith, psw_bands, &
206  ptsrad, pdir_alb, psca_alb, pemis, ptsurf )
207 ENDIF
208 !
209 !-------------------------------------------------------------------------------
210 !
211 IF (lhook) CALL dr_hook('SFX_OASIS_RECV_OL',1,zhook_handle)
212 !
213 !-------------------------------------------------------------------------------
214 !
215 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 update_esm_surf_atm_n(F, IM, S, U, W, HPROGRAM, KI, KSW, PZENITH, PSW_BANDS, PTRAD, PDIR_ALB, PSCA_ALB, PEMIS, PTSURF)
real, parameter xundef
subroutine put_sfx_sea(S, U, W, KLUOUT, OCPL_SEAICE, OWATER, PSEA_SS
Definition: put_sfx_sea.F90:7
subroutine goto_model(KMODEL)
integer, parameter jprb
Definition: parkind1.F90:32
subroutine put_sfx_land(IO, S, K, NK, NP, U, KLUOUT, OCPL_WTD, OCPL_FLOOD, PWTD, PFWTD, PFFLOOD, PPIFLOOD)
Definition: put_sfx_land.F90:9
subroutine get_luout(HPROGRAM, KLUOUT)
Definition: get_luout.F90:7
logical lhook
Definition: yomhook.F90:15
subroutine sfx_oasis_recv_ol(F, IM, S, U, W, HPROGRAM, KI, KSW, PTIMEC, PTSTEP_SURF, PZENITH, PSW_BANDS, PTSRAD, PDIR_ALB, PSCA_ALB, PEMIS, PTSURF)