SURFEX v8.1
General documentation of Surfex
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, IM, 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 USE modd_flake_n, ONLY : flake_t
49 USE modd_surfex_n, ONLY : isba_model_t
50 USE modd_seaflux_n, ONLY : seaflux_t
51 USE modd_surf_atm_n, ONLY : surf_atm_t
52 USE modd_watflux_n, ONLY : watflux_t
53 !
54 USE modd_surf_par, ONLY : xundef
55 !
56 USE modn_sfx_oasis, ONLY : lwater
57 USE modd_sfx_oasis, ONLY : lcpl_sea, lcpl_seaice, &
58  lcpl_land, lcpl_gw, &
60 !
61 USE modi_get_luout
62 !
63 USE modi_abor1_sfx
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 IMPLICIT NONE
72 !
73 !* 0.1 Declarations of arguments
74 ! -------------------------
75 !
76 !
77 TYPE(flake_t), INTENT(INOUT) :: F
78 TYPE(isba_model_t), INTENT(INOUT) :: IM
79 TYPE(seaflux_t), INTENT(INOUT) :: S
80 TYPE(surf_atm_t), INTENT(INOUT) :: U
81 TYPE(watflux_t), INTENT(INOUT) :: W
82 !
83  CHARACTER(LEN=6), INTENT(IN) :: HPROGRAM
84 INTEGER, INTENT(IN) :: KI ! number of points
85 INTEGER, INTENT(IN) :: KSW ! number of bands
86 !
87 REAL, DIMENSION(KI), INTENT(IN) :: PZENITH
88 REAL, DIMENSION(KSW), INTENT(IN) :: PSW_BANDS ! mean wavelength of each shortwave band (m)
89 !
90 REAL, DIMENSION(KI), INTENT(IN) :: PLAND_WTD ! Land water table depth (m)
91 REAL, DIMENSION(KI), INTENT(IN) :: PLAND_FWTD ! Land grid-cell fraction of water table rise (-)
92 REAL, DIMENSION(KI), INTENT(IN) :: PLAND_FFLOOD ! Land Floodplains fraction (-)
93 REAL, DIMENSION(KI), INTENT(IN) :: PLAND_PIFLOOD ! Land Potential flood infiltration (kg/m2)
94 !
95 REAL, DIMENSION(KI), INTENT(IN) :: PSEA_SST ! Sea surface temperature (K)
96 REAL, DIMENSION(KI), INTENT(IN) :: PSEA_UCU ! Sea u-current stress (Pa)
97 REAL, DIMENSION(KI), INTENT(IN) :: PSEA_VCU ! Sea v-current stress (Pa)
98 !
99 REAL, DIMENSION(KI), INTENT(IN) :: PSEAICE_SIT ! Sea-ice Temperature (K)
100 REAL, DIMENSION(KI), INTENT(IN) :: PSEAICE_CVR ! Sea-ice cover (-)
101 REAL, DIMENSION(KI), INTENT(IN) :: PSEAICE_ALB ! Sea-ice albedo (-)
102 !
103 REAL, DIMENSION(KI), INTENT(OUT) :: PTSRAD ! Total radiative temperature see by the atmosphere
104 REAL, DIMENSION(KI), INTENT(OUT) :: PTSURF ! Total surface temperature see by the atmosphere
105 REAL, DIMENSION(KI), INTENT(OUT) :: PEMIS ! Total emissivity see by the atmosphere
106 REAL, DIMENSION(KI,KSW), INTENT(OUT) :: PDIR_ALB ! Total direct albedo see by the atmosphere
107 REAL, DIMENSION(KI,KSW), INTENT(OUT) :: PSCA_ALB ! Total diffus albedo see by the atmosphere
108 !
109 !
110 !* 0.2 Declarations of local variables
111 ! -------------------------------
112 !
113 !
114 INTEGER :: ILU, ILUOUT
115 REAL(KIND=JPRB) :: ZHOOK_HANDLE
116 !
117 !-------------------------------------------------------------------------------
118 IF (lhook) CALL dr_hook('PUT_SFXCL_N',0,zhook_handle)
119 !
120  CALL get_luout(hprogram,iluout)
121 !-------------------------------------------------------------------------------
122 !
123 ! Global argument
124 !
125 IF(ki/=u%NSIZE_FULL)THEN
126  WRITE(iluout,*) 'size of field from the coupler :', ki
127  WRITE(iluout,*) 'size of field in SURFEX :', u%NSIZE_FULL
128  CALL abor1_sfx('PUT_SFXCPL_N: VECTOR SIZE NOT CORRECT FOR COUPLING')
129 ENDIF
130 !
131 !-------------------------------------------------------------------------------
132 ! Put variable over land tile
133 !-------------------------------------------------------------------------------
134 !
135 IF(lcpl_land)THEN
136  CALL put_sfx_land(im%O, im%S, im%K, im%NK, im%NP, u, iluout, lcpl_gw, lcpl_flood, &
137  pland_wtd(:), pland_fwtd(:),pland_fflood(:),pland_piflood(:))
138 ENDIF
139 !
140 !-------------------------------------------------------------------------------
141 ! Put variable over sea and/or water tile
142 !-------------------------------------------------------------------------------
143 !
144 IF(lcpl_sea)THEN
145 !
146  CALL put_sfx_sea(s, u, w, iluout,lcpl_seaice,lwater,psea_sst(:),psea_ucu(:), &
147  psea_vcu(:),pseaice_sit(:),pseaice_cvr(:),pseaice_alb(:) )
148 !
149 ENDIF
150 !
151 !-------------------------------------------------------------------------------
152 ! Update radiative properties at time t+1 for radiative scheme
153 !-------------------------------------------------------------------------------
154 !
155 IF(lcpl_sea.OR.lcpl_flood)THEN
156  CALL update_esm_surf_atm_n(f, im, s, u, w, hprogram, ki, ksw, pzenith, psw_bands, &
157  ptsrad, pdir_alb, psca_alb, pemis, ptsurf )
158 ENDIF
159 !
160 !-------------------------------------------------------------------------------
161 !
162 IF (lhook) CALL dr_hook('PUT_SFXCL_N',1,zhook_handle)
163 !
164 !
165 END SUBROUTINE put_sfxcpl_n
subroutine update_esm_surf_atm_n(F, IM, S, U, W, HPROGRAM, KI, KSW, PZENITH, PSW_BANDS, PTRAD, PDIR_ALB, PSCA_ALB, PEMIS, PTSURF)
subroutine abor1_sfx(YTEXT)
Definition: abor1_sfx.F90:7
real, parameter xundef
subroutine put_sfx_sea(S, U, W, KLUOUT, OCPL_SEAICE, OWATER, PSEA_SS
Definition: put_sfx_sea.F90:7
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 put_sfxcpl_n(F, IM, 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:13