SURFEX v8.1
General documentation of Surfex
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 modi_get_luout
50 !
51 USE yomhook ,ONLY : lhook, dr_hook
52 USE parkind1 ,ONLY : jprb
53 !
54 #ifdef CPLOASIS
55 USE mod_oasis
56 #endif
57 !
58 IMPLICIT NONE
59 !
60 !* 0.1 Declarations of arguments
61 ! -------------------------
62 !
63  CHARACTER(LEN=*), INTENT(IN) :: HPROGRAM ! program calling surf. schemes
64 INTEGER, INTENT(IN) :: KI ! number of points on this proc
65 INTEGER, INTENT(IN) :: KSW ! number of short-wave spectral bands
66 REAL, INTENT(IN) :: PTIMEC ! Cumulated run time step (s)
67 !
68 LOGICAL, INTENT(IN) :: ORECV_LAND
69 LOGICAL, INTENT(IN) :: ORECV_SEA
70 !
71 REAL, DIMENSION(KI), INTENT(OUT) :: PLAND_WTD ! Land water table depth (m)
72 REAL, DIMENSION(KI), INTENT(OUT) :: PLAND_FWTD ! Land grid-cell fraction of water table rise (-)
73 REAL, DIMENSION(KI), INTENT(OUT) :: PLAND_FFLOOD ! Land Floodplains fraction (-)
74 REAL, DIMENSION(KI), INTENT(OUT) :: PLAND_PIFLOOD ! Land Potential flood infiltration (kg/m2/s)
75 !
76 REAL, DIMENSION(KI), INTENT(OUT) :: PSEA_SST ! Sea surface temperature (K)
77 REAL, DIMENSION(KI), INTENT(OUT) :: PSEA_UCU ! Sea u-current stress (Pa)
78 REAL, DIMENSION(KI), INTENT(OUT) :: PSEA_VCU ! Sea v-current stress (Pa)
79 !
80 REAL, DIMENSION(KI), INTENT(OUT) :: PSEAICE_SIT ! Sea-ice Temperature (K)
81 REAL, DIMENSION(KI), INTENT(OUT) :: PSEAICE_CVR ! Sea-ice cover (-)
82 REAL, DIMENSION(KI), INTENT(OUT) :: PSEAICE_ALB ! Sea-ice albedo (-)
83 !
84 !
85 !* 0.2 Declarations of local variables
86 ! -------------------------------
87 !
88 REAL, DIMENSION(KI,1) :: ZREAD
89 !
90 INTEGER :: IDATE ! current coupling time step (s)
91 INTEGER :: IERR ! Error info
92 INTEGER :: ILUOUT
93  CHARACTER(LEN=50) :: YCOMMENT
94 !
95 REAL(KIND=JPRB) :: ZHOOK_HANDLE
96 !
97 !-------------------------------------------------------------------------------
98 #ifdef CPLOASIS
99 !-------------------------------------------------------------------------------
100 !
101 IF (lhook) CALL dr_hook('SFX_OASIS_RECV',0,zhook_handle)
102 !
103 !* 1. Initialize :
104 ! ------------
105 !
106  CALL get_luout(hprogram,iluout)
107 !
108 idate = int(ptimec)
109 !
110 !-------------------------------------------------------------------------------
111 !
112 !* 2. Get Land surface variable :
113 ! ------------------------------------
114 !
115 IF(orecv_land)THEN
116 !
117 ! * Init river input fields
118 !
119  zread(:,:) = xundef
120 !
121  pland_wtd(:) = xundef
122  pland_fwtd(:) = xundef
123  pland_fflood(:) = xundef
124  pland_piflood(:) = xundef
125 !
126 ! * Receive river input fields
127 !
128  IF(lcpl_gw)THEN
129 !
130  ycomment='water table depth'
131  CALL oasis_get(nwtd_id,idate,zread(:,:),ierr)
132  CALL check_recv(iluout,ierr,ycomment)
133  pland_wtd(:)=zread(:,1)
134 !
135  ycomment='fraction of water table rise'
136  CALL oasis_get(nfwtd_id,idate,zread(:,:),ierr)
137  CALL check_recv(iluout,ierr,ycomment)
138  pland_fwtd(:)=zread(:,1)
139 !
140  ENDIF
141 !
142  IF(lcpl_flood)THEN
143 !
144  ycomment='Flood fraction'
145  CALL oasis_get(nfflood_id,idate,zread(:,:),ierr)
146  CALL check_recv(iluout,ierr,ycomment)
147  pland_fflood(:)=zread(:,1)
148 !
149  ycomment='Potential flood infiltration'
150  CALL oasis_get(npiflood_id,idate,zread(:,:),ierr)
151  CALL check_recv(iluout,ierr,ycomment)
152  pland_piflood(:)=zread(:,1)
153 !
154  WHERE(pland_piflood(:)==0.0)pland_fflood(:)=0.0
155 !
156  ENDIF
157 !
158 ENDIF
159 !
160 !-------------------------------------------------------------------------------
161 !
162 !* 3. Get Sea variables :
163 ! -----------------------------
164 !
165 !
166 IF(orecv_sea)THEN
167 !
168 ! * Init ocean input fields
169 !
170  zread(:,:) = xundef
171 !
172  psea_sst(:) = xundef
173  psea_ucu(:) = xundef
174  psea_vcu(:) = xundef
175 !
176  pseaice_sit(:) = xundef
177  pseaice_cvr(:) = xundef
178  pseaice_alb(:) = xundef
179 !
180 ! * Receive ocean input fields
181 !
182  ycomment='Sea surface temperature'
183  CALL oasis_get(nsea_sst_id,idate,zread(:,:),ierr)
184  CALL check_recv(iluout,ierr,ycomment)
185  psea_sst(:)=zread(:,1)
186 !
187  ycomment='Sea u-current stress'
188  CALL oasis_get(nsea_ucu_id,idate,zread(:,:),ierr)
189  CALL check_recv(iluout,ierr,ycomment)
190  psea_ucu(:)=zread(:,1)
191 !
192  ycomment='Sea v-current stress'
193  CALL oasis_get(nsea_vcu_id,idate,zread(:,:),ierr)
194  CALL check_recv(iluout,ierr,ycomment)
195  psea_vcu(:)=zread(:,1)
196 !
197  IF(lcpl_seaice)THEN
198 !
199  ycomment='Sea-ice Temperature'
200  CALL oasis_get(nseaice_sit_id,idate,zread(:,:),ierr)
201  CALL check_recv(iluout,ierr,ycomment)
202  pseaice_sit(:)=zread(:,1)
203 !
204  ycomment='Sea-ice cover'
205  CALL oasis_get(nseaice_cvr_id,idate,zread(:,:),ierr)
206  CALL check_recv(iluout,ierr,ycomment)
207  pseaice_cvr(:)=zread(:,1)
208 !
209  ycomment='Sea-ice albedo'
210  CALL oasis_get(nseaice_alb_id,idate,zread(:,:),ierr)
211  CALL check_recv(iluout,ierr,ycomment)
212  pseaice_alb(:)=zread(:,1)
213 !
214  ENDIF
215 !
216 ENDIF
217 !-------------------------------------------------------------------------------
218 !
219 IF (lhook) CALL dr_hook('SFX_OASIS_RECV',1,zhook_handle)
220 !
221 !-------------------------------------------------------------------------------
222 CONTAINS
223 !-------------------------------------------------------------------------------
224 !
225 SUBROUTINE check_recv(KLUOUT,KERR,HCOMMENT)
226 !
227 USE modi_abor1_sfx
228 !
229 IMPLICIT NONE
230 !
231 INTEGER, INTENT(IN) :: KLUOUT
232 INTEGER, INTENT(IN) :: KERR
233  CHARACTER(LEN=*), INTENT(IN) :: HCOMMENT
234 !
235 REAL(KIND=JPRB) :: ZHOOK_HANDLE
236 !
237 IF (lhook) CALL dr_hook('SFX_OASIS_RECV:CHECK_RECV',0,zhook_handle)
238 !
239 IF (kerr/=oasis_ok.AND.kerr<oasis_recvd) THEN
240  WRITE(kluout,'(A,I4)')'Return OASIS code receiving '//trim(hcomment)//' : ',kerr
241  CALL abor1_sfx('SFX_OASIS_RECV: problem receiving '//trim(hcomment)//' from OASIS')
242 ENDIF
243 !
244 IF (lhook) CALL dr_hook('SFX_OASIS_RECV:CHECK_RECV',1,zhook_handle)
245 !
246 END SUBROUTINE check_recv
247 !
248 !-------------------------------------------------------------------------------
249 #endif
250 !-------------------------------------------------------------------------------
251 !
252 END SUBROUTINE sfx_oasis_recv
static const char * trim(const char *name, int *n)
Definition: drhook.c:2383
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:7
real, parameter xundef
integer, parameter jprb
Definition: parkind1.F90:32
subroutine get_luout(HPROGRAM, KLUOUT)
Definition: get_luout.F90:7
logical lhook
Definition: yomhook.F90:15