SURFEX v8.1
General documentation of Surfex
prep_seaice.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_seaice (UG, DTCO, DTS, O, OR, KLAT, S, U, GCP, &
7  HPROGRAM,HATMFILE,HATMFILETYPE,HPGDFILE,HPGDFILETYPE,YDCTL)
8 ! #################################################################################
9 !
10 !!**** *PREP_SEAICE* - prepares variables for SEAICE scheme (for now : Gelato only)
11 !!
12 !! PURPOSE
13 !! -------
14 !
15 !!** METHOD
16 !! ------
17 !!
18 !! REFERENCE
19 !! ---------
20 !!
21 !!
22 !! AUTHOR
23 !! ------
24 !! S. Sénési
25 !!
26 !! MODIFICATIONS
27 !! -------------
28 !! Original 01/2014
29 !!------------------------------------------------------------------
30 !
32 !
35 USE modd_ocean_n, ONLY : ocean_t
36 USE modd_ocean_rel_n, ONLY : ocean_rel_t
37 USE modd_seaflux_n, ONLY : seaflux_t
38 USE modd_surf_atm_n, ONLY : surf_atm_t
40 !
41 USE modd_surf_par, ONLY : xundef
42 USE modi_get_luout
43 USE modi_get_type_dim_n
44 USE modi_gltools_readnam
45 !
46 USE modd_types_glt, ONLY : t_glt
47 !
48 USE mode_prep_ctl, ONLY : prep_ctl
49 !
50 USE modn_prep_seaflux, ONLY : cprep_seaice_scheme => cseaice_scheme
51 USE modi_prep_hor_seaflux_field
52 !
53 USE modd_glt_param, ONLY : nl, nt, nx, ny, nxglo, nyglo
54 USE modi_gltools_alloc
55 !
56 USE yomhook ,ONLY : lhook, dr_hook
57 USE parkind1 ,ONLY : jprb
58 !
59 IMPLICIT NONE
60 !
61 !* 0.1 declarations of arguments
62 !
63 !
64 !
65 TYPE(surf_atm_grid_t), INTENT(INOUT) :: UG
66 !
67 TYPE(data_cover_t), INTENT(INOUT) :: DTCO
68 TYPE(data_seaflux_t), INTENT(INOUT) :: DTS
69 TYPE(ocean_t), INTENT(INOUT) :: O
70 TYPE(ocean_rel_t), INTENT(INOUT) :: OR
71 INTEGER, INTENT(IN) :: KLAT
72 TYPE(seaflux_t), INTENT(INOUT) :: S
73 TYPE(surf_atm_t), INTENT(INOUT) :: U
74 TYPE(grid_conf_proj_t),INTENT(INOUT) :: GCP
75 !
76 type(prep_ctl), INTENT(INOUT) :: ydctl
77 !
78  CHARACTER(LEN=6), INTENT(IN) :: HPROGRAM ! program calling surf. schemes
79  CHARACTER(LEN=28), INTENT(IN) :: HATMFILE ! name of the Atmospheric file
80  CHARACTER(LEN=6), INTENT(IN) :: HATMFILETYPE! type of the Atmospheric file
81  CHARACTER(LEN=28), INTENT(IN) :: HPGDFILE ! name of the Atmospheric file
82  CHARACTER(LEN=6), INTENT(IN) :: HPGDFILETYPE! type of the Atmospheric file
83 !
84 !* 0.2 declarations of local variables
85 !
86 INTEGER :: IK,IL ! loop counter on ice categories and layers
87 INTEGER :: JMTH,INMTH
88 INTEGER :: ILUOUT
89 LOGICAL :: GFOUND ! Return code when searching namelist
90 INTEGER :: ILUNAM ! logical unit of namelist file
91 REAL(KIND=JPRB) :: ZHOOK_HANDLE
92 !
93 !-------------------------------------------------------------------------------------
94 !
95 IF (lhook) CALL dr_hook('PREP_SEAICE',0,zhook_handle)
96 !
97 !* 0. Default of configuration
98 !
99 !
100  CALL get_luout(hprogram,iluout)
101 !
102 !-------------------------------------------------------------------------------------
103 !
104 !* 1. Interpret namelist
105 !
106 s%CSEAICE_SCHEME=cprep_seaice_scheme
107 IF ( s%CSEAICE_SCHEME == 'GELATO' ) THEN
108  CALL gltools_readnam(.false.,iluout)
109 ENDIF
110 !
111 s%LHANDLE_SIC = .false.
112 IF(trim(s%CSEAICE_SCHEME)/='NONE' .OR. trim(s%CINTERPOL_SIC)/='NONE' )THEN
113  s%LHANDLE_SIC=.true.
114 ENDIF
115 !
116 !-------------------------------------------------------------------------------------
117 !
118 !* 2. Reading and horizontal interpolations of Seaice cover
119 !
120 IF (s%LHANDLE_SIC) THEN
121  CALL prep_hor_seaflux_field(dtco, ug, u, gcp, dts, o, or, klat, s, &
122  hprogram,'SIC ',hatmfile,hatmfiletype,hpgdfile,hpgdfiletype,ydctl)
123 ENDIF
124 !
125 !-------------------------------------------------------------------------------------
126 !
127 !* 3. Optional preparation of interpolation of monthly sea ice cover and sea
128 ! ice thickness
129 !
130 s%LINTERPOL_SIC=.false.
131 IF(trim(s%CINTERPOL_SIC)/='NONE')THEN
132  s%LINTERPOL_SIC=.true.
133 ENDIF
134 !
135 IF(trim(s%CINTERPOL_SIT)/='NONE')THEN
136  s%LINTERPOL_SIT=.true.
137 ENDIF
138 !
139 IF(s%LINTERPOL_SIC)THEN
140  !
141  ! Precedent, Current, Next, and Second-next Monthly SIC
142  inmth=4
143  !
144  ALLOCATE(s%XSIC_MTH(SIZE(s%XSIC),inmth))
145  DO jmth=1,inmth
146  s%XSIC_MTH(:,jmth)=s%XSIC(:)
147  ENDDO
148 !
149 ENDIF
150 !
151 IF(s%LINTERPOL_SIT)THEN
152  !
153  !Precedent, Current, Next, and Second-next Monthly SIT
154  inmth=4
155  !
156  ALLOCATE(s%XSIT_MTH(SIZE(s%XSIC),inmth))
157  DO jmth=1,inmth
158  s%XSIT_MTH(:,jmth)=xundef
159  ENDDO
160 !
161 ENDIF
162 !-------------------------------------------------------------------------------------
163 !
164 !* Creating default initial state for Gelato
165 !
166 !
167  CALL get_type_dim_n(dtco, u, 'SEA ',nx)
168 ny=1
169 nyglo=1
170 nxglo=nx
171  CALL gltools_alloc(s%TGLT)
172 !
173 !* G1 Prognostic fields with only space dimension(s) :
174 !
175 s%TGLT%ust(:,1)=0.
176 !
177 !* G2 Prognostic fields with space and ice-category dimension(s) :
178 !
179 ! sea ice age
180 s%TGLT%sit(:,:,1)%age=0.
181 ! melt pond volume
182 s%TGLT%sit(:,:,1)%vmp=0.
183 ! sea ice surface albedo
184 s%TGLT%sit(:,:,1)%asn=0.
185 ! sea ice fraction
186 s%TGLT%sit(:,:,1)%fsi=0.
187 ! sea ice thickness
188 s%TGLT%sit(:,:,1)%hsi=1.*s%TGLT%sit(:,:,1)%fsi
189 ! sea ice salinity
190 s%TGLT%sit(:,:,1)%ssi=0.
191 ! sea ice surface temperature
192 s%TGLT%sit(:,:,1)%tsf=260.
193 ! snow thickness
194 s%TGLT%sit(:,:,1)%hsn=0.
195 ! snow density
196 s%TGLT%sit(:,:,1)%rsn=100.
197 !
198 !* G3 Prognostic fields with space, ice-category and layer dimensions :
199 !
200 ! sea ice vertical gltools_enthalpy profile for all types and levels
201 s%TGLT%sil(:,:,:,1)%ent=-1000.
202 !
203 IF (lhook) CALL dr_hook('PREP_SEAICE',1,zhook_handle)
204 !
205 !-------------------------------------------------------------------------------------
206 !
207 END SUBROUTINE prep_seaice
subroutine get_type_dim_n(DTCO, U, HTYPE, KDIM)
static const char * trim(const char *name, int *n)
Definition: drhook.c:2383
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)
character(len=6) cseaice_scheme
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