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 branches/dev_003_CPL/NEMO/LIM_SRC_3 – NEMO

source: branches/dev_003_CPL/NEMO/LIM_SRC_3/iceini.F90 @ 991

Last change on this file since 991 was 991, checked in by smasson, 16 years ago

dev_003_CPL: preliminary draft (not working), see ticket #155

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