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 @ 1037

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

trunk: replace freeze(:,:) variable with fr_i(:,:), use the tfreez function defined in eosbn2.F90 and remove the useless ocfzpt.F90 module, see ticket: #177

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