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 tags/nemo_v3_2_2/NEMO/LIM_SRC_3 – NEMO

source: tags/nemo_v3_2_2/NEMO/LIM_SRC_3/iceini.F90 @ 3518

Last change on this file since 3518 was 2477, checked in by cetlod, 14 years ago

v3.2:remove hardcoded value of num_sal in limrst.F90, see ticket #633

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