SURFEX  V8_0
Surfex V8_0 release
 All Classes Files Functions Variables
sfx_oasis_recv.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(HPROGRAM,KI,KSW,PTIMEC, &
7  orecv_land, orecv_sea, &
8  pland_wtd,pland_fwtd, &
9  pland_fflood,pland_piflood, &
10  psea_sst,psea_ucu,psea_vcu, &
11  pseaice_sit,pseaice_cvr,pseaice_alb )
12 !########################################
13 !
14 !!**** *SFX_OASIS_RECV* - Receive coupling fields from oasis
15 !!
16 !! PURPOSE
17 !! -------
18 !!
19 !!** METHOD
20 !! ------
21 !!
22 !! EXTERNAL
23 !! --------
24 !!
25 !!
26 !! IMPLICIT ARGUMENTS
27 !! ------------------
28 !!
29 !! REFERENCE
30 !! ---------
31 !!
32 !!
33 !! AUTHOR
34 !! ------
35 !! B. Decharme *Meteo France*
36 !!
37 !! MODIFICATIONS
38 !! -------------
39 !! Original 10/2013
40 !-------------------------------------------------------------------------------
41 !
42 !* 0. DECLARATIONS
43 ! ------------
44 !
45 USE modd_surf_par, ONLY : xundef
46 !
48 !
49 USE modd_sgh_par, ONLY :
50 !
51 USE modi_get_luout
52 !
53 USE yomhook ,ONLY : lhook, dr_hook
54 USE parkind1 ,ONLY : jprb
55 !
56 #ifdef CPLOASIS
57 USE mod_oasis
58 #endif
59 !
60 IMPLICIT NONE
61 !
62 !* 0.1 Declarations of arguments
63 ! -------------------------
64 !
65  CHARACTER(LEN=*), INTENT(IN) :: hprogram ! program calling surf. schemes
66 INTEGER, INTENT(IN) :: ki ! number of points on this proc
67 INTEGER, INTENT(IN) :: ksw ! number of short-wave spectral bands
68 REAL, INTENT(IN) :: ptimec ! Cumulated run time step (s)
69 !
70 LOGICAL, INTENT(IN) :: orecv_land
71 LOGICAL, INTENT(IN) :: orecv_sea
72 !
73 REAL, DIMENSION(KI), INTENT(OUT) :: pland_wtd ! Land water table depth (m)
74 REAL, DIMENSION(KI), INTENT(OUT) :: pland_fwtd ! Land grid-cell fraction of water table rise (-)
75 REAL, DIMENSION(KI), INTENT(OUT) :: pland_fflood ! Land Floodplains fraction (-)
76 REAL, DIMENSION(KI), INTENT(OUT) :: pland_piflood ! Land Potential flood infiltration (kg/m2/s)
77 !
78 REAL, DIMENSION(KI), INTENT(OUT) :: psea_sst ! Sea surface temperature (K)
79 REAL, DIMENSION(KI), INTENT(OUT) :: psea_ucu ! Sea u-current stress (Pa)
80 REAL, DIMENSION(KI), INTENT(OUT) :: psea_vcu ! Sea v-current stress (Pa)
81 !
82 REAL, DIMENSION(KI), INTENT(OUT) :: pseaice_sit ! Sea-ice Temperature (K)
83 REAL, DIMENSION(KI), INTENT(OUT) :: pseaice_cvr ! Sea-ice cover (-)
84 REAL, DIMENSION(KI), INTENT(OUT) :: pseaice_alb ! Sea-ice albedo (-)
85 !
86 !
87 !* 0.2 Declarations of local variables
88 ! -------------------------------
89 !
90 REAL, DIMENSION(KI,1) :: zread
91 !
92 INTEGER :: idate ! current coupling time step (s)
93 INTEGER :: ierr ! Error info
94 INTEGER :: iluout
95  CHARACTER(LEN=50) :: ycomment
96 !
97 REAL(KIND=JPRB) :: zhook_handle
98 !
99 !-------------------------------------------------------------------------------
100 #ifdef CPLOASIS
101 !-------------------------------------------------------------------------------
102 !
103 IF (lhook) CALL dr_hook('SFX_OASIS_RECV',0,zhook_handle)
104 !
105 !* 1. Initialize :
106 ! ------------
107 !
108  CALL get_luout(hprogram,iluout)
109 !
110 idate = int(ptimec)
111 !
112 !-------------------------------------------------------------------------------
113 !
114 !* 2. Get Land surface variable :
115 ! ------------------------------------
116 !
117 IF(orecv_land)THEN
118 !
119 ! * Init river input fields
120 !
121  zread(:,:) = xundef
122 !
123  pland_wtd(:) = xundef
124  pland_fwtd(:) = xundef
125  pland_fflood(:) = xundef
126  pland_piflood(:) = xundef
127 !
128 ! * Receive river input fields
129 !
130  IF(lcpl_gw)THEN
131 !
132  ycomment='water table depth'
133  CALL oasis_get(nwtd_id,idate,zread(:,:),ierr)
134  CALL check_recv(iluout,ierr,ycomment)
135  pland_wtd(:)=zread(:,1)
136 !
137  ycomment='fraction of water table rise'
138  CALL oasis_get(nfwtd_id,idate,zread(:,:),ierr)
139  CALL check_recv(iluout,ierr,ycomment)
140  pland_fwtd(:)=zread(:,1)
141 !
142  ENDIF
143 !
144  IF(lcpl_flood)THEN
145 !
146  ycomment='Flood fraction'
147  CALL oasis_get(nfflood_id,idate,zread(:,:),ierr)
148  CALL check_recv(iluout,ierr,ycomment)
149  pland_fflood(:)=zread(:,1)
150 !
151  ycomment='Potential flood infiltration'
152  CALL oasis_get(npiflood_id,idate,zread(:,:),ierr)
153  CALL check_recv(iluout,ierr,ycomment)
154  pland_piflood(:)=zread(:,1)
155 !
156  WHERE(pland_piflood(:)==0.0)pland_fflood(:)=0.0
157 !
158  ENDIF
159 !
160 ENDIF
161 !
162 !-------------------------------------------------------------------------------
163 !
164 !* 3. Get Sea variables :
165 ! -----------------------------
166 !
167 !
168 IF(orecv_sea)THEN
169 !
170 ! * Init ocean input fields
171 !
172  zread(:,:) = xundef
173 !
174  psea_sst(:) = xundef
175  psea_ucu(:) = xundef
176  psea_vcu(:) = xundef
177 !
178  pseaice_sit(:) = xundef
179  pseaice_cvr(:) = xundef
180  pseaice_alb(:) = xundef
181 !
182 ! * Receive ocean input fields
183 !
184  ycomment='Sea surface temperature'
185  CALL oasis_get(nsea_sst_id,idate,zread(:,:),ierr)
186  CALL check_recv(iluout,ierr,ycomment)
187  psea_sst(:)=zread(:,1)
188 !
189  ycomment='Sea u-current stress'
190  CALL oasis_get(nsea_ucu_id,idate,zread(:,:),ierr)
191  CALL check_recv(iluout,ierr,ycomment)
192  psea_ucu(:)=zread(:,1)
193 !
194  ycomment='Sea v-current stress'
195  CALL oasis_get(nsea_vcu_id,idate,zread(:,:),ierr)
196  CALL check_recv(iluout,ierr,ycomment)
197  psea_vcu(:)=zread(:,1)
198 !
199  IF(lcpl_seaice)THEN
200 !
201  ycomment='Sea-ice Temperature'
202  CALL oasis_get(nseaice_sit_id,idate,zread(:,:),ierr)
203  CALL check_recv(iluout,ierr,ycomment)
204  pseaice_sit(:)=zread(:,1)
205 !
206  ycomment='Sea-ice cover'
207  CALL oasis_get(nseaice_cvr_id,idate,zread(:,:),ierr)
208  CALL check_recv(iluout,ierr,ycomment)
209  pseaice_cvr(:)=zread(:,1)
210 !
211  ycomment='Sea-ice albedo'
212  CALL oasis_get(nseaice_alb_id,idate,zread(:,:),ierr)
213  CALL check_recv(iluout,ierr,ycomment)
214  pseaice_alb(:)=zread(:,1)
215 !
216  ENDIF
217 !
218 ENDIF
219 !-------------------------------------------------------------------------------
220 !
221 IF (lhook) CALL dr_hook('SFX_OASIS_RECV',1,zhook_handle)
222 !
223 !-------------------------------------------------------------------------------
224  CONTAINS
225 !-------------------------------------------------------------------------------
226 !
227 SUBROUTINE check_recv(KLUOUT,KERR,HCOMMENT)
228 !
229 USE modi_abor1_sfx
230 !
231 IMPLICIT NONE
232 !
233 INTEGER, INTENT(IN) :: kluout
234 INTEGER, INTENT(IN) :: kerr
235  CHARACTER(LEN=*), INTENT(IN) :: hcomment
236 !
237 REAL(KIND=JPRB) :: zhook_handle
238 !
239 IF (lhook) CALL dr_hook('SFX_OASIS_RECV:CHECK_RECV',0,zhook_handle)
240 !
241 IF (kerr/=oasis_ok.AND.kerr<oasis_recvd) THEN
242  WRITE(kluout,'(A,I4)')'Return OASIS code receiving '//trim(hcomment)//' : ',kerr
243  CALL abor1_sfx('SFX_OASIS_RECV: problem receiving '//trim(hcomment)//' from OASIS')
244 ENDIF
245 !
246 IF (lhook) CALL dr_hook('SFX_OASIS_RECV:CHECK_RECV',1,zhook_handle)
247 !
248 END SUBROUTINE check_recv
249 !
250 !-------------------------------------------------------------------------------
251 #endif
252 !-------------------------------------------------------------------------------
253 !
254 END SUBROUTINE sfx_oasis_recv
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 check_recv(KLUOUT, KERR, HCOMMENT)
subroutine abor1_sfx(YTEXT)
Definition: abor1_sfx.F90:6
subroutine get_luout(HPROGRAM, KLUOUT)
Definition: get_luout.F90:6