SURFEX v8.1
General documentation of Surfex
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, GCP, SG, SB, S, DTS, O, OR, &
7  HPROGRAM,HATMFILE,HATMFILETYPE,HPGDFILE,HPGDFILETYPE,YDCTL)
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 !! P. Marguinaud10/2014, Support for a 2-part PREP
34 !!------------------------------------------------------------------
35 !
36 USE modd_sfx_grid_n, ONLY : grid_t
37 USE modd_canopy_n, ONLY : canopy_t
38 USE modd_seaflux_n, ONLY : seaflux_t
40 USE modd_ocean_n, ONLY : ocean_t
41 USE modd_ocean_rel_n, ONLY : ocean_rel_t
42 !
45 USE modd_surf_atm_n, ONLY : surf_atm_t
47 !
48 USE modi_prep_hor_seaflux_field
49 USE modi_prep_ver_seaflux
50 USE modi_prep_output_grid
51 USE modi_prep_sbl
52 USE modi_prep_seaice
53 USE modi_get_luout
54 !
56 USE modd_read_namelist, ONLY : lnam_read
57 USE modd_prep, ONLY : xzs_ls
58 USE modd_surf_atm, ONLY : lvertshift
59 !
60 USE mode_prep_ctl, ONLY : prep_ctl
61 !
62 USE yomhook ,ONLY : lhook, dr_hook
63 USE parkind1 ,ONLY : jprb
64 !
65 USE modi_clean_prep_output_grid
66 !
67 IMPLICIT NONE
68 !
69 !* 0.1 declarations of arguments
70 !
71 TYPE(data_cover_t), INTENT(INOUT) :: DTCO
72 TYPE(surf_atm_grid_t), INTENT(INOUT) :: UG
73 TYPE(surf_atm_t), INTENT(INOUT) :: U
74 TYPE(grid_conf_proj_t),INTENT(INOUT) :: GCP
75 !
76 TYPE(grid_t), INTENT(INOUT) :: SG
77 TYPE(canopy_t), INTENT(INOUT) :: SB
78 TYPE(seaflux_t), INTENT(INOUT) :: S
79 TYPE(data_seaflux_t), INTENT(INOUT) :: DTS
80 TYPE(ocean_t), INTENT(INOUT) :: O
81 TYPE(ocean_rel_t), INTENT(INOUT) :: OR
82 type(prep_ctl), INTENT(INOUT) :: ydctl
83 !
84  CHARACTER(LEN=6), INTENT(IN) :: HPROGRAM ! program calling surf. schemes
85  CHARACTER(LEN=28), INTENT(IN) :: HATMFILE ! name of the Atmospheric file
86  CHARACTER(LEN=6), INTENT(IN) :: HATMFILETYPE! type of the Atmospheric file
87  CHARACTER(LEN=28), INTENT(IN) :: HPGDFILE ! name of the Atmospheric file
88  CHARACTER(LEN=6), INTENT(IN) :: HPGDFILETYPE! type of the Atmospheric file
89 !
90 !* 0.2 declarations of local variables
91 !
92 INTEGER :: JMTH,INMTH
93 INTEGER :: ILUOUT
94 LOGICAL :: GFOUND ! Return code when searching namelist
95 INTEGER :: ILUNAM ! logical unit of namelist file
96 REAL(KIND=JPRB) :: ZHOOK_HANDLE
97 
98 !-------------------------------------------------------------------------------------
99 !
100 !* 0. Default of configuration
101 !
102 !
103 IF (lhook) CALL dr_hook('PREP_SEAFLUX',0,zhook_handle)
104  CALL get_luout(hprogram,iluout)
105 !
106  CALL prep_output_grid(ug%G, sg, u%NSIZE_FULL, iluout)
107 !
108 !-------------------------------------------------------------------------------------
109 !
110 !* 1. Read namelist
111 !
112 s%LSBL = lsea_sbl
113 !
114 o%LMERCATOR = locean_mercator
115 o%LCURRENT = locean_current
116 !
117 ! Relaxation-forcing parameters
118 or%XTAU_REL = xtime_rel
119 or%XQCORR = xcorflx
120 !
121 or%LREL_CUR = lcur_rel
122 or%LREL_TS = lts_rel
123 or%LFLUX_NULL = lzero_flux
124 or%LFLX_CORR = lcorr_flux
125 or%LDIAPYCNAL = ldiapyc
126 !
127 !-------------------------------------------------------------------------------------
128 !
129 !* 2. Reading and horizontal interpolations
130 !
131 !
132 !* 2.0 Large scale orography
133 !
134  CALL prep_hor_seaflux_field(dtco, ug, u, gcp, dts, o, or, SIZE(sg%XLAT), s, &
135  hprogram,'ZS ',hatmfile,hatmfiletype,hpgdfile,hpgdfiletype,ydctl)
136 !
137 !* 2.1.1 Temperature
138 !
139  CALL prep_hor_seaflux_field(dtco, ug, u, gcp, dts, o, or, SIZE(sg%XLAT), s, &
140  hprogram,'SST ',hatmfile,hatmfiletype,hpgdfile,hpgdfiletype,ydctl)
141 !
142 !* 2.1.2 Salinity
143 !
144 
145  CALL prep_hor_seaflux_field(dtco, ug, u, gcp, dts, o, or, SIZE(sg%XLAT), s, &
146  hprogram,'SSS ',hatmfile,hatmfiletype,hpgdfile,hpgdfiletype,ydctl)
147 !
148 !* 2.1.3 Sea-ice
149 !
150 IF (cseaice_scheme /= 'NONE ') THEN
151  CALL prep_seaice(ug, dtco, dts, o, or, SIZE(sg%XLAT), s, u, gcp, &
152  hprogram,hatmfile,hatmfiletype,hpgdfile,hpgdfiletype,ydctl)
153 ENDIF
154 !
156 
157 IF (ydctl%LPART6) THEN
158 !
159 !* 2.2 Roughness
160 !
161  ALLOCATE(s%XZ0(SIZE(s%XSST)))
162  s%XZ0 = 0.001
163 !
164  ALLOCATE(s%XZ0H(SIZE(s%XSST)))
165  s%XZ0H = s%XZ0
166 !
167 !* 2.3 Ocean Surface Albedo
168 !
169  IF(s%CSEA_ALB=='RS14')THEN
170  ALLOCATE(s%XDIR_ALB(SIZE(s%XSST)))
171  ALLOCATE(s%XSCA_ALB(SIZE(s%XSST)))
172  s%XDIR_ALB = 0.065
173  s%XSCA_ALB = 0.065
174  ENDIF
175 !
176 !-------------------------------------------------------------------------------------
177 !
178 !* 3. Vertical interpolations of all variables
179 !
180  IF(lvertshift)THEN
181  CALL prep_ver_seaflux(s)
182  ENDIF
183 !
184  DEALLOCATE(xzs_ls)
185 !
186 !-------------------------------------------------------------------------------------
187 !
188 !* 4. Preparation of optional interpolation of monthly sst
189 !
190  s%LINTERPOL_SST=.false.
191  IF(trim(s%CINTERPOL_SST)/='NONE')THEN
192 !
193  s%LINTERPOL_SST=.true.
194 !
195 ! Precedent, Current, Next, and Second-next Monthly SST
196  inmth=4
197 !
198  ALLOCATE(s%XSST_MTH(SIZE(s%XSST),inmth))
199  DO jmth=1,inmth
200  s%XSST_MTH(:,jmth)=s%XSST(:)
201  ENDDO
202 !
203  ENDIF
204 !
205 !-------------------------------------------------------------------------------------
206 !
207 !
208 !* 5. Optional preparation of interpolation of monthly Sea Surface salinity
209 !
210  s%LINTERPOL_SSS=.false.
211  IF(trim(s%CINTERPOL_SSS)/='NONE')THEN
212 !
213  s%LINTERPOL_SSS=.true.
214  !
215  ! Precedent, Current, Next, and Second-next Monthly SSS
216  inmth=4
217  !
218  ALLOCATE(s%XSSS_MTH(SIZE(s%XSSS),inmth))
219  DO jmth=1,inmth
220  s%XSSS_MTH(:,jmth)=s%XSSS(:)
221  ENDDO
222  !
223  ENDIF
224 !
225 !-------------------------------------------------------------------------------------
226 !
227 !* 6. Preparation of SBL air variables
228 !
229 !
230  IF (s%LSBL) CALL prep_sbl(sg%NDIM, sb)
231 !
232 ENDIF
233 !-------------------------------------------------------------------------------------
234 !
235 IF (lhook) CALL dr_hook('PREP_SEAFLUX',1,zhook_handle)
236 !
237 !-------------------------------------------------------------------------------------
238 !
239 END SUBROUTINE prep_seaflux
subroutine prep_sbl(KDIM, SB)
Definition: prep_sbl.F90:7
static const char * trim(const char *name, int *n)
Definition: drhook.c:2383
subroutine prep_seaflux(DTCO, UG, U, GCP, SG, SB, S, DTS, O, OR, HPROGRAM, HATMFILE, HATMFILETYPE, HPGDFILE, HPGDFILETYPE, YDCTL)
Definition: prep_seaflux.F90:8
subroutine prep_seaice(UG, DTCO, DTS, O, OR, KLAT, S, U, GCP, HPROGRAM, HATMFILE, HATMFILETYPE, HPGDFILE, HPGDFILETYPE, YDCTL)
Definition: prep_seaice.F90:8
subroutine prep_hor_seaflux_field(DTCO, UG, U, GCP, DTS, O, OR, KLAT, S, HPROGRAM, HSURF, HATMFILE, HATMFILETYPE, HPGDFILE, HPGDFILETYPE, YDCTL)
subroutine clean_prep_output_grid
real, dimension(:), allocatable xzs_ls
Definition: modd_prep.F90:45
character(len=6) cseaice_scheme
integer, parameter jprb
Definition: parkind1.F90:32
subroutine prep_output_grid(UG, G, KSIZE_FULL, KLUOUT)
subroutine get_luout(HPROGRAM, KLUOUT)
Definition: get_luout.F90:7
logical lhook
Definition: yomhook.F90:15
subroutine prep_ver_seaflux(S)
logical lvertshift