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