New URL for NEMO forge!   http://forge.nemo-ocean.eu

Since March 2022 along with NEMO 4.2 release, the code development moved to a self-hosted GitLab.
This present forge is now archived and remained online for history.
iceini.F90 in trunk/NEMO/LIM_SRC_3 – NEMO

source: trunk/NEMO/LIM_SRC_3/iceini.F90 @ 888

Last change on this file since 888 was 888, checked in by ctlod, 16 years ago

merge dev_001_SBC branche with the trunk to include the New Surface Module package, see ticket: #113

File size: 11.0 KB
Line 
1MODULE iceini
2   !!======================================================================
3   !!                       ***  MODULE iceini   ***
4   !!   Sea-ice model : LIM Sea ice model Initialization
5   !!======================================================================
6#if defined key_lim3
7   !!----------------------------------------------------------------------
8   !!   'key_lim3' :                                   LIM sea-ice model
9   !!----------------------------------------------------------------------
10   !!   ice_init       : sea-ice model initialization
11   !!----------------------------------------------------------------------
12   USE dom_oce
13   USE in_out_manager
14   USE ice_oce         ! ice variables
15   USE sbc_oce         ! Surface boundary condition: ocean fields
16   USE sbc_ice         ! Surface boundary condition: ice fields
17   USE phycst          ! Define parameters for the routines
18   USE ocfzpt
19   USE ice
20   USE limmsh
21   USE limistate
22   USE limrst
23   USE par_ice
24   USE limvar
25
26   IMPLICIT NONE
27   PRIVATE
28
29   !! * Routine accessibility
30   PUBLIC ice_init                 ! called by opa.F90
31   PUBLIC lim_itd_ini
32
33   !! * Share Module variables
34   LOGICAL , PUBLIC  ::     & !!! ** init namelist (namicerun) **
35      ln_limdyn   = .TRUE., & !: flag for ice dynamics (T) or not (F)
36      ln_nicep    = .TRUE.    !: flag for sea-ice points output (T) or not (F)
37   INTEGER , PUBLIC  ::   &  !:
38      nstart ,            &  !: iteration number of the begining of the run
39      nlast  ,            &  !: iteration number of the end of the run
40      nitrun ,            &  !: number of iteration
41      numit                  !: iteration number
42   REAL(wp), PUBLIC  ::   &  !:
43      hsndif = 0.e0    ,  &  !: computation of temp. in snow (0) or not (9999)
44      hicdif = 0.e0    ,  &  !: computation of temp. in ice (0) or not (9999)
45      tpstot           ,  &  !: time of the run in seconds
46      cai    = 1.40e-3 ,  &  !: atmospheric drag over sea ice
47      cao    = 1.00e-3       !: atmospheric drag over ocean
48   REAL(wp), PUBLIC, DIMENSION(2)  ::  &  !:
49      acrit  = (/ 1.e-06 , 1.e-06 /)    !: minimum fraction for leads in
50      !                                   !  north and south hemisphere
51   !!----------------------------------------------------------------------
52   !!   LIM 3.0,  UCL-ASTR-LOCEAN-IPSL (2008)
53   !! $ Id: $
54   !! This software is governed by the CeCILL licence see modipsl/doc/NEMO_CeCILL.txt
55   !!----------------------------------------------------------------------
56
57CONTAINS
58
59   SUBROUTINE ice_init
60      !!----------------------------------------------------------------------
61      !!                  ***  ROUTINE ice_init  ***
62      !!
63      !! ** purpose :   
64      !!
65      !! History :
66      !!   2.0  !  02-08  (G. Madec)  F90: Free form and modules
67      !!   3.0  !  08-03  (M. Vancop) ITD, salinity, EVP-C
68      !!----------------------------------------------------------------------
69
70      ! Open the namelist file
71      CALL ctlopn(numnam_ice,'namelist_ice','OLD', 'FORMATTED', 'SEQUENTIAL', 1,numout,.FALSE.,1)
72
73      CALL ice_run                    !  read in namelist some run parameters
74                 
75      ! Louvain la Neuve Ice model
76      IF( nacc == 1 ) THEN
77          dtsd2   = nn_fsbc * rdtmin * 0.5
78          rdt_ice = nn_fsbc * rdtmin
79      ELSE
80          dtsd2   = nn_fsbc * rdt * 0.5
81          rdt_ice = nn_fsbc * rdt
82      ENDIF
83
84      CALL lim_msh                    ! ice mesh initialization
85     
86      CALL lim_itd_ini                ! initialize the ice thickness
87                                      ! distribution
88      ! Initial sea-ice state
89      IF( .NOT.ln_rstart ) THEN
90         numit = 0
91         numit = nit000 - 1
92         CALL lim_istate              ! start from rest: sea-ice deduced from sst
93         CALL lim_var_agg(1)          ! aggregate category variables in
94                                      ! bulk variables
95         CALL lim_var_glo2eqv         ! convert global variables in equivalent
96                                      ! variables
97      ELSE
98         CALL lim_rst_read            ! start from a restart file
99
100         numit = nit000 - 1
101         CALL lim_var_agg(1)          ! aggregate ice variables
102         CALL lim_var_glo2eqv         ! convert global var in equivalent variables
103      ENDIF
104
105      freeze(:,:) = at_i(:,:)   ! initialisation of sea/ice cover   
106# if defined key_coupled
107      Must be adpated to LIM3 
108      alb_ice(:,:,:) = albege(:,:)      ! sea-ice albedo
109# endif
110     
111      nstart = numit  + nn_fsbc     
112      nitrun = nitend - nit000 + 1 
113      nlast  = numit  + nitrun 
114
115      IF( nstock == 0  )  nstock = nlast + 1
116
117   END SUBROUTINE ice_init
118
119   SUBROUTINE ice_run
120      !!-------------------------------------------------------------------
121      !!                  ***  ROUTINE ice_run ***
122      !!                 
123      !! ** Purpose :   Definition some run parameter for ice model
124      !!
125      !! ** Method  :   Read the namicerun namelist and check the parameter
126      !!       values called at the first timestep (nit000)
127      !!
128      !! ** input   :   Namelist namicerun
129      !!
130      !! history :
131      !!   2.0  !  03-08 (C. Ethe)  Original code
132      !!   3.0  !  08-03 (M. Vancop) LIM3
133      !!-------------------------------------------------------------------
134      NAMELIST/namicerun/ ln_limdyn, acrit, hsndif, hicdif, cai, cao, ln_nicep
135      !!-------------------------------------------------------------------
136
137      !                                           ! Read Namelist namicerun
138      REWIND ( numnam_ice )
139      READ   ( numnam_ice , namicerun )
140      IF(lwp) THEN
141         WRITE(numout,*)
142         WRITE(numout,*) 'ice_run : ice share parameters for dynamics/advection/thermo of sea-ice'
143         WRITE(numout,*) ' ~~~~~~'
144         WRITE(numout,*) '   switch for ice dynamics (1) or not (0)      ln_limdyn   = ', ln_limdyn
145         WRITE(numout,*) '   minimum fraction for leads in the NH (SH)  acrit(1/2)   = ', acrit(:)
146         WRITE(numout,*) '   computation of temp. in snow (=0) or not (=9999) hsndif = ', hsndif
147         WRITE(numout,*) '   computation of temp. in ice  (=0) or not (=9999) hicdif = ', hicdif
148         WRITE(numout,*) '   atmospheric drag over sea ice                           = ', cai
149         WRITE(numout,*) '   atmospheric drag over ocean                             = ', cao
150         WRITE(numout,*) '   Several ice points in the ice or not in ocean.output = ', ln_nicep
151      ENDIF
152     
153   END SUBROUTINE ice_run
154
155   SUBROUTINE lim_itd_ini
156        !!------------------------------------------------------------------
157        !!                ***  ROUTINE lim_itd_ini ***
158        !! ** Purpose :
159        !!            Initializes the ice thickness distribution
160        !! ** Method  :
161        !!            Very simple. Currently there are no ice types in the
162        !!            model...
163        !!
164        !! ** Arguments :
165        !!           kideb , kiut : Starting and ending points on which the
166        !!                         the computation is applied
167        !!
168        !! ** Inputs / Ouputs : (global commons)
169        !!
170        !! ** External :
171        !!
172        !! ** References :
173        !!
174        !! ** History :
175        !!           (12-2005) Martin Vancoppenolle
176        !!
177        !!------------------------------------------------------------------
178        !! * Arguments
179
180       !! * Local variables
181       INTEGER ::   jl,       &   ! ice category dummy loop index
182                    jm            ! ice types    dummy loop index
183
184       REAL(wp)  ::           &  ! constant values
185          zeps      =  1.0e-10,   & !
186          zc1                 ,   & !
187          zc2                 ,   & !
188          zc3                 ,   & !
189          zx1
190
191       WRITE(numout,*) 'lim_itd_ini : Initialization of ice thickness distribution '
192       WRITE(numout,*) '~~~~~~~~~~~~'
193
194!!-- End of declarations
195!!------------------------------------------------------------------------------
196
197!------------------------------------------------------------------------------!
198! 1) Ice thickness distribution parameters initialization   
199!------------------------------------------------------------------------------!
200
201      !- Types boundaries (integer)
202      !----------------------------
203      ice_cat_bounds(1,1) = 1
204      ice_cat_bounds(1,2) = jpl
205
206      !- Number of ice thickness categories in each ice type
207      DO jm = 1, jpm
208         ice_ncat_types(jm) = ice_cat_bounds(jm,2) - ice_cat_bounds(jm,1) + 1 
209      END DO
210
211      !- Make the correspondence between thickness categories and ice types
212      !---------------------------------------------------------------------
213      DO jm = 1, jpm       !over types
214         DO jl = ice_cat_bounds(jm,1), ice_cat_bounds(jm,2) !over thickness categories
215            ice_types(jl) = jm
216         END DO
217      END DO
218
219      WRITE(numout,*) ' Number of ice types jpm =      ', jpm
220      WRITE(numout,*) ' Number of ice categories jpl = ', jpl
221      DO jm = 1, jpm
222         WRITE(numout,*) ' Ice type ', jm
223         WRITE(numout,*) ' Number of thickness categories ', ice_ncat_types(jm)
224         WRITE(numout,*) ' Thickness category boundaries  ', ice_cat_bounds(jm,1:2)
225      END DO
226      WRITE(numout,*) 'Ice type vector', ice_types(1:jpl)
227      WRITE(numout,*)
228
229      !- Thickness categories boundaries
230      !----------------------------------
231      hi_max(:) = 0.0
232      hi_max_typ(:,:) = 0.0
233
234      !- Type 1 - undeformed ice
235      zc1 = 3./REAL(ice_cat_bounds(1,2)-ice_cat_bounds(1,1)+1)
236      zc2 = 10.0*zc1
237      zc3 = 3.0
238
239      DO jl = ice_cat_bounds(1,1), ice_cat_bounds(1,2)
240         zx1 = REAL(jl-1) / REAL(ice_cat_bounds(1,2)-ice_cat_bounds(1,1)+1)
241         hi_max(jl) = hi_max(jl-1) + zc1 + zc2 * (1.0 + TANH ( zc3 * (zx1 - 1.0 ) ) )
242      END DO
243
244      !- Fill in the hi_max_typ vector, useful in other circumstances
245      ! Tricky trick
246      ! hi_max_typ is actually not used in the code and will be removed in a
247      ! next flyspray at this time, the tricky trick will also be removed
248      ! Martin, march 08
249      DO jl = ice_cat_bounds(1,1), ice_cat_bounds(1,2)
250         hi_max_typ(jl,1) = hi_max(jl)
251      END DO
252
253      WRITE(numout,*) ' Thickness category boundaries independently of ice type '
254      WRITE(numout,*) ' hi_max ', hi_max(0:jpl)
255
256      WRITE(numout,*) ' Thickness category boundaries inside ice types '
257      DO jm = 1, jpm
258         WRITE(numout,*) ' Type number ', jm
259         WRITE(numout,*) ' hi_max_typ : ', hi_max_typ(0:ice_ncat_types(jm),jm)
260      END DO
261
262      DO jl = 1, jpl
263         hi_mean(jl) = ( hi_max(jl) + hi_max(jl-1) ) / 2.0
264      END DO
265
266      tn_ice(:,:,:) = t_su(:,:,:)
267
268    END SUBROUTINE lim_itd_ini
269
270#else
271   !!----------------------------------------------------------------------
272   !!   Default option :        Empty module           NO LIM sea-ice model
273   !!----------------------------------------------------------------------
274CONTAINS
275   SUBROUTINE ice_init        ! Empty routine
276   END SUBROUTINE ice_init
277
278   SUBROUTINE lim_itd_ini
279   END SUBROUTINE lim_itd_ini
280#endif
281
282   !!======================================================================
283END MODULE iceini
Note: See TracBrowser for help on using the repository browser.