SURFEX  V8_0
Surfex V8_0 release
 All Classes Files Functions Variables
put_sfxcpln.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 put_sfxcpl_n (F, I, S, U, W, &
7  hprogram,ki,ksw,psw_bands,pzenith, &
8  pland_wtd,pland_fwtd,pland_fflood, &
9  pland_piflood,psea_sst,psea_ucu, &
10  psea_vcu,pseaice_sit,pseaice_cvr, &
11  pseaice_alb,ptsrad, &
12  pdir_alb,psca_alb,pemis,ptsurf )
13 ! #################################################################################################
14 !
15 !!**** *PUT_SFXCPL_n* - routine to modify some variables in surfex from information coming
16 ! from an ocean and/or a river routing model (but already on Surfex grid)
17 !
18 !
19 !! PURPOSE
20 !! -------
21 !!
22 !!** METHOD
23 !! ------
24 !!
25 !! EXTERNAL
26 !! --------
27 !!
28 !!
29 !! IMPLICIT ARGUMENTS
30 !! ------------------
31 !!
32 !! REFERENCE
33 !! ---------
34 !!
35 !!
36 !! AUTHOR
37 !! ------
38 !! B. Decharme *Meteo France*
39 !!
40 !! MODIFICATIONS
41 !! -------------
42 !! Original 08/2009
43 !-------------------------------------------------------------------------------
44 !
45 !* 0. DECLARATIONS
46 ! ------------
47 !
48 !
49 !
50 !
51 !
52 !
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 modn_sfx_oasis, ONLY : lwater
63 USE modd_sfx_oasis, ONLY : lcpl_sea, lcpl_seaice, &
64  lcpl_land, lcpl_gw, &
65  lcpl_flood
66 !
67 USE modi_get_luout
68 !
69 USE modi_abor1_sfx
70 USE modi_put_sfx_land
71 USE modi_put_sfx_sea
72 USE modi_update_esm_surf_atm_n
73 !
74 USE yomhook ,ONLY : lhook, dr_hook
75 USE parkind1 ,ONLY : jprb
76 !
77 IMPLICIT NONE
78 !
79 !* 0.1 Declarations of arguments
80 ! -------------------------
81 !
82 !
83 TYPE(flake_t), INTENT(INOUT) :: f
84 TYPE(isba_t), INTENT(INOUT) :: i
85 TYPE(seaflux_t), INTENT(INOUT) :: s
86 TYPE(surf_atm_t), INTENT(INOUT) :: u
87 TYPE(watflux_t), INTENT(INOUT) :: w
88 !
89  CHARACTER(LEN=6), INTENT(IN) :: hprogram
90 INTEGER, INTENT(IN) :: ki ! number of points
91 INTEGER, INTENT(IN) :: ksw ! number of bands
92 !
93 REAL, DIMENSION(KI), INTENT(IN) :: pzenith
94 REAL, DIMENSION(KSW), INTENT(IN) :: psw_bands ! mean wavelength of each shortwave band (m)
95 !
96 REAL, DIMENSION(KI), INTENT(IN) :: pland_wtd ! Land water table depth (m)
97 REAL, DIMENSION(KI), INTENT(IN) :: pland_fwtd ! Land grid-cell fraction of water table rise (-)
98 REAL, DIMENSION(KI), INTENT(IN) :: pland_fflood ! Land Floodplains fraction (-)
99 REAL, DIMENSION(KI), INTENT(IN) :: pland_piflood ! Land Potential flood infiltration (kg/m2)
100 !
101 REAL, DIMENSION(KI), INTENT(IN) :: psea_sst ! Sea surface temperature (K)
102 REAL, DIMENSION(KI), INTENT(IN) :: psea_ucu ! Sea u-current stress (Pa)
103 REAL, DIMENSION(KI), INTENT(IN) :: psea_vcu ! Sea v-current stress (Pa)
104 !
105 REAL, DIMENSION(KI), INTENT(IN) :: pseaice_sit ! Sea-ice Temperature (K)
106 REAL, DIMENSION(KI), INTENT(IN) :: pseaice_cvr ! Sea-ice cover (-)
107 REAL, DIMENSION(KI), INTENT(IN) :: pseaice_alb ! Sea-ice albedo (-)
108 !
109 REAL, DIMENSION(KI), INTENT(OUT) :: ptsrad ! Total radiative temperature see by the atmosphere
110 REAL, DIMENSION(KI), INTENT(OUT) :: ptsurf ! Total surface temperature see by the atmosphere
111 REAL, DIMENSION(KI), INTENT(OUT) :: pemis ! Total emissivity see by the atmosphere
112 REAL, DIMENSION(KI,KSW), INTENT(OUT) :: pdir_alb ! Total direct albedo see by the atmosphere
113 REAL, DIMENSION(KI,KSW), INTENT(OUT) :: psca_alb ! Total diffus albedo see by the atmosphere
114 !
115 !
116 !* 0.2 Declarations of local variables
117 ! -------------------------------
118 !
119 !
120 INTEGER :: ilu, iluout
121 REAL(KIND=JPRB) :: zhook_handle
122 !
123 !-------------------------------------------------------------------------------
124 IF (lhook) CALL dr_hook('PUT_SFXCL_N',0,zhook_handle)
125 !
126  CALL get_luout(hprogram,iluout)
127 !-------------------------------------------------------------------------------
128 !
129 ! Global argument
130 !
131 IF(ki/=u%NSIZE_FULL)THEN
132  WRITE(iluout,*) 'size of field from the coupler :', ki
133  WRITE(iluout,*) 'size of field in SURFEX :', u%NSIZE_FULL
134  CALL abor1_sfx('PUT_SFXCPL_N: VECTOR SIZE NOT CORRECT FOR COUPLING')
135 ENDIF
136 !
137 !-------------------------------------------------------------------------------
138 ! Put variable over land tile
139 !-------------------------------------------------------------------------------
140 !
141 IF(lcpl_land)THEN
142  CALL put_sfx_land(i, u, &
143  iluout,lcpl_gw,lcpl_flood,pland_wtd(:), &
144  pland_fwtd(:),pland_fflood(:),pland_piflood(:))
145 ENDIF
146 !
147 !-------------------------------------------------------------------------------
148 ! Put variable over sea and/or water tile
149 !-------------------------------------------------------------------------------
150 !
151 IF(lcpl_sea)THEN
152 !
153  CALL put_sfx_sea(s, u, w, &
154  iluout,lcpl_seaice,lwater,psea_sst(:),psea_ucu(:), &
155  psea_vcu(:),pseaice_sit(:),pseaice_cvr(:),pseaice_alb(:) )
156 !
157 ENDIF
158 !
159 !-------------------------------------------------------------------------------
160 ! Update radiative properties at time t+1 for radiative scheme
161 !-------------------------------------------------------------------------------
162 !
163 IF(lcpl_sea.OR.lcpl_flood)THEN
164  CALL update_esm_surf_atm_n(f, i, s, u, w, &
165  hprogram, ki, ksw, pzenith, psw_bands, &
166  ptsrad, pdir_alb, psca_alb, pemis, ptsurf )
167 ENDIF
168 !
169 !-------------------------------------------------------------------------------
170 !
171 IF (lhook) CALL dr_hook('PUT_SFXCL_N',1,zhook_handle)
172 !
173 !
174 END SUBROUTINE put_sfxcpl_n
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 put_sfxcpl_n(F, I, S, U, W, HPROGRAM, KI, KSW, PSW_BANDS, PZENITH, PLAND_WTD, PLAND_FWTD, PLAND_FFLOOD, PLAND_PIFLOOD, PSEA_SST, PSEA_UCU, PSEA_VCU, PSEAICE_SIT, PSEAICE_CVR, PSEAICE_ALB, PTSRAD, PDIR_ALB, PSCA_ALB, PEMIS, PTSURF)
Definition: put_sfxcpln.F90:6
subroutine abor1_sfx(YTEXT)
Definition: abor1_sfx.F90:6
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 get_luout(HPROGRAM, KLUOUT)
Definition: get_luout.F90:6