SURFEX  V8_0
Surfex V8_0 release
 All Classes Files Functions Variables
prep_seaflux.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 prep_seaflux (DTCO, UG, U, SM, &
7  hprogram,hatmfile,hatmfiletype,hpgdfile,hpgdfiletype)
8 ! #################################################################################
9 !
10 !!**** *PREP_SEAFLUX* - prepares variables for SEAFLUX scheme
11 !!
12 !! PURPOSE
13 !! -------
14 !
15 !!** METHOD
16 !! ------
17 !!
18 !! REFERENCE
19 !! ---------
20 !!
21 !!
22 !! AUTHOR
23 !! ------
24 !! S. Malardel
25 !!
26 !! MODIFICATIONS
27 !! -------------
28 !! Original 01/2004
29 !! S. Riette 06/2009 PREP_SEAFLUX_SBL has no more argument
30 !! Modified 07/2012, P. Le Moigne : CMO1D phasing
31 !! Modified 01/2014, S. Senesi : introduce sea-ice model
32 !! Modified 01/2015, R. Séférian : introduce ocean surface albedo
33 !!------------------------------------------------------------------
34 !
35 !
37 !
38 !
41 USE modd_surf_atm_n, ONLY : surf_atm_t
42 !
43 USE modi_prep_hor_seaflux_field
44 USE modi_prep_ver_seaflux
45 USE modi_prep_output_grid
46 USE modi_prep_seaflux_sbl
47 USE modi_prep_seaice
48 USE modi_get_luout
49 !
51 USE modd_read_namelist, ONLY : lnam_read
52 USE modd_prep, ONLY : xzs_ls
53 USE modd_surf_atm, ONLY : lvertshift
54 !
55 !
56 USE yomhook ,ONLY : lhook, dr_hook
57 USE parkind1 ,ONLY : jprb
58 !
59 USE modi_clean_prep_output_grid
60 !
61 IMPLICIT NONE
62 !
63 !* 0.1 declarations of arguments
64 !
65 !
66 !
67 !
68 TYPE(data_cover_t), INTENT(INOUT) :: dtco
69 TYPE(surf_atm_grid_t), INTENT(INOUT) :: ug
70 TYPE(surf_atm_t), INTENT(INOUT) :: u
71 TYPE(seaflux_model_t), INTENT(INOUT) :: sm
72 !
73  CHARACTER(LEN=6), INTENT(IN) :: hprogram ! program calling surf. schemes
74  CHARACTER(LEN=28), INTENT(IN) :: hatmfile ! name of the Atmospheric file
75  CHARACTER(LEN=6), INTENT(IN) :: hatmfiletype! type of the Atmospheric file
76  CHARACTER(LEN=28), INTENT(IN) :: hpgdfile ! name of the Atmospheric file
77  CHARACTER(LEN=6), INTENT(IN) :: hpgdfiletype! type of the Atmospheric file
78 !
79 !* 0.2 declarations of local variables
80 !
81 INTEGER :: jmth,inmth
82 INTEGER :: iluout
83 LOGICAL :: gfound ! Return code when searching namelist
84 INTEGER :: ilunam ! logical unit of namelist file
85 REAL(KIND=JPRB) :: zhook_handle
86 
87 !-------------------------------------------------------------------------------------
88 !
89 !* 0. Default of configuration
90 !
91 !
92 IF (lhook) CALL dr_hook('PREP_SEAFLUX',0,zhook_handle)
93  CALL get_luout(hprogram,iluout)
94 !
95  CALL prep_output_grid(ug, u, &
96  iluout,sm%SG%CGRID,sm%SG%XGRID_PAR,sm%SG%XLAT,sm%SG%XLON)
97 !
98 !-------------------------------------------------------------------------------------
99 !
100 !* 1. Read namelist
101 !
102 sm%S%LSBL = lsea_sbl
103 sm%O%LMERCATOR = locean_mercator
104 sm%O%LCURRENT = locean_current
105 ! Relaxation-forcing parameters
106 sm%OR%XTAU_REL = xtime_rel
107 sm%OR%XQCORR = xcorflx
108 !
109 sm%OR%LREL_CUR = lcur_rel
110 sm%OR%LREL_TS = lts_rel
111 sm%OR%LFLUX_NULL = lzero_flux
112 sm%OR%LFLX_CORR = lcorr_flux
113 sm%OR%LDIAPYCNAL = ldiapyc
114 !
115 !-------------------------------------------------------------------------------------
116 !
117 !* 2. Reading and horizontal interpolations
118 !
119 !
120 !* 2.0 Large scale orography
121 !
122  CALL prep_hor_seaflux_field(dtco, ug, u, &
123  sm%DTS, sm%O, sm%OR, sm%SG, sm%S, &
124  hprogram,'ZS ',hatmfile,hatmfiletype,hpgdfile,hpgdfiletype)
125 !
126 !* 2.1.1 Temperature
127 !
128  CALL prep_hor_seaflux_field(dtco, ug, u, &
129  sm%DTS, sm%O, sm%OR, sm%SG, sm%S, &
130  hprogram,'SST ',hatmfile,hatmfiletype,hpgdfile,hpgdfiletype)
131 !
132 !* 2.1.2 Salinity
133 !
134 
135  CALL prep_hor_seaflux_field(dtco, ug, u, &
136  sm%DTS, sm%O, sm%OR, sm%SG, sm%S, &
137  hprogram,'SSS ',hatmfile,hatmfiletype,hpgdfile,hpgdfiletype)
138 !
139 !* 2.1.3 Sea-ice
140 !
141 IF (cseaice_scheme /= 'NONE ') THEN
142  CALL prep_seaice(ug, &
143  dtco, sm%DTS, sm%O, sm%OR, sm%SG, sm%S, u, &
144  hprogram,hatmfile,hatmfiletype,hpgdfile,hpgdfiletype)
145 ENDIF
146 !
147 !
148 !* 2.2 Roughness
149 !
150 ALLOCATE(sm%S%XZ0(SIZE(sm%S%XSST)))
151 sm%S%XZ0 = 0.001
152 !
153 ALLOCATE(sm%S%XZ0H(SIZE(sm%S%XSST)))
154 sm%S%XZ0H = sm%S%XZ0
155 !
156 !* 2.3 Ocean Surface Albedo
157 !
158 IF(sm%S%CSEA_ALB=='RS14')THEN
159  ALLOCATE(sm%S%XDIR_ALB(SIZE(sm%S%XSST)))
160  ALLOCATE(sm%S%XSCA_ALB(SIZE(sm%S%XSST)))
161  sm%S%XDIR_ALB = 0.065
162  sm%S%XSCA_ALB = 0.065
163 ENDIF
164 !
165 !-------------------------------------------------------------------------------------
167 !-------------------------------------------------------------------------------------
168 !
169 !* 3. Vertical interpolations of all variables
170 !
171 IF(lvertshift)THEN
172  CALL prep_ver_seaflux(sm%S)
173 ENDIF
174 !
175 DEALLOCATE(xzs_ls)
176 !
177 !-------------------------------------------------------------------------------------
178 !
179 !* 4. Preparation of optional interpolation of monthly sst
180 !
181 sm%S%LINTERPOL_SST=.false.
182 IF(trim(sm%S%CINTERPOL_SST)/='NONE')THEN
183 !
184  sm%S%LINTERPOL_SST=.true.
185 !
186 ! Precedent, Current, Next, and Second-next Monthly SST
187  inmth=4
188 !
189  ALLOCATE(sm%S%XSST_MTH(SIZE(sm%S%XSST),inmth))
190  DO jmth=1,inmth
191  sm%S%XSST_MTH(:,jmth)=sm%S%XSST(:)
192  ENDDO
193 !
194 ENDIF
195 !
196 !-------------------------------------------------------------------------------------
197 !
198 !
199 !* 5. Optional preparation of interpolation of monthly Sea Surface salinity
200 !
201 sm%S%LINTERPOL_SSS=.false.
202 IF(trim(sm%S%CINTERPOL_SSS)/='NONE')THEN
203 !
204  sm%S%LINTERPOL_SSS=.true.
205  !
206  ! Precedent, Current, Next, and Second-next Monthly SSS
207  inmth=4
208  !
209  ALLOCATE(sm%S%XSSS_MTH(SIZE(sm%S%XSSS),inmth))
210  DO jmth=1,inmth
211  sm%S%XSSS_MTH(:,jmth)=sm%S%XSSS(:)
212  ENDDO
213  !
214 ENDIF
215 !
216 !-------------------------------------------------------------------------------------
217 !
218 !* 6. Preparation of SBL air variables
219 !
220 !
221 IF (sm%S%LSBL) CALL prep_seaflux_sbl(sm%SG, sm%SSB)
222 !
223 !-------------------------------------------------------------------------------------
224 !
225 IF (lhook) CALL dr_hook('PREP_SEAFLUX',1,zhook_handle)
226 !
227 !-------------------------------------------------------------------------------------
228 !
229 END SUBROUTINE prep_seaflux
subroutine clean_prep_output_grid
subroutine prep_seaflux(DTCO, UG, U, SM, HPROGRAM, HATMFILE, HATMFILETYPE, HPGDFILE, HPGDFILETYPE)
Definition: prep_seaflux.F90:6
subroutine prep_hor_seaflux_field(DTCO, UG, U, DTS, O, OR, SG, S, HPROGRAM, HSURF, HATMFILE, HATMFILETYPE, HPGDFILE, HPGDFILETYPE)
subroutine prep_seaice(UG, DTCO, DTS, O, OR, SG, S, U, HPROGRAM, HATMFILE, HATMFILETYPE, HPGDFILE, HPGDFILETYPE)
Definition: prep_seaice.F90:6
subroutine get_luout(HPROGRAM, KLUOUT)
Definition: get_luout.F90:6
subroutine prep_seaflux_sbl(SG, SSB)
subroutine prep_ver_seaflux(S)
subroutine prep_output_grid(UG, U, KLUOUT, HGRID, PGRID_PAR, PLAT, PLON)