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/2013/dev_r3406_CNRS_LIM3/NEMOGCM/NEMO/LIM_SRC_3 – NEMO

source: branches/2013/dev_r3406_CNRS_LIM3/NEMOGCM/NEMO/LIM_SRC_3/iceini.F90 @ 6917

Last change on this file since 6917 was 3977, checked in by flavoni, 11 years ago

add print of fwb correction value, and hminrhg for LIM2, in CNRS LIM3 branch

  • Property svn:keywords set to Id
File size: 11.0 KB
Line 
1MODULE iceini
2   !!======================================================================
3   !!                       ***  MODULE iceini   ***
4   !!   Sea-ice model : LIM Sea ice model Initialization
5   !!======================================================================
6   !! History :  3.0  ! 2008-03  (M. Vancoppenolle) LIM-3 original code
7   !!            3.3  ! 2010-12  (G. Madec) add call to lim_thd_init and lim_thd_sal_init
8   !!            4.0  ! 2011-02  (G. Madec) dynamical allocation
9   !!----------------------------------------------------------------------
10#if defined key_lim3
11   !!----------------------------------------------------------------------
12   !!   'key_lim3' :                                   LIM sea-ice model
13   !!----------------------------------------------------------------------
14   !!   ice_init       : sea-ice model initialization
15   !!----------------------------------------------------------------------
16   USE phycst           ! physical constants
17   USE dom_oce          ! ocean domain
18   USE sbc_oce          ! Surface boundary condition: ocean fields
19   USE sbc_ice          ! Surface boundary condition: ice   fields
20   USE ice              ! LIM variables
21   USE par_ice          ! LIM parameters
22   USE dom_ice          ! LIM domain
23   USE thd_ice          ! LIM thermodynamical variables
24   USE limitd_me        ! LIM ice thickness distribution
25   USE limmsh           ! LIM mesh
26   USE limistate        ! LIM initial state
27   USE limrst           ! LIM restart
28   USE limthd           ! LIM ice thermodynamics
29   USE limthd_sal       ! LIM ice thermodynamics: salinity
30   USE limvar           ! LIM variables
31   USE limsbc           ! LIM surface boundary condition
32   USE in_out_manager   ! I/O manager
33   USE lib_mpp          ! MPP library
34
35   IMPLICIT NONE
36   PRIVATE
37
38   PUBLIC   ice_init   ! called by sbcice_lim.F90
39
40   !!----------------------------------------------------------------------
41   !! NEMO/LIM3 4.0 , UCL - NEMO Consortium (2011)
42   !! $Id$
43   !! Software governed by the CeCILL licence     (NEMOGCM/NEMO_CeCILL.txt)
44   !!----------------------------------------------------------------------
45CONTAINS
46
47   SUBROUTINE ice_init
48      !!----------------------------------------------------------------------
49      !!                  ***  ROUTINE ice_init  ***
50      !!
51      !! ** purpose :   Allocate all the dynamic arrays of the LIM-3 modules
52      !!----------------------------------------------------------------------
53      INTEGER :: ierr
54      !!----------------------------------------------------------------------
55
56      !                                ! Allocate the ice arrays
57      ierr =        ice_alloc        ()      ! ice variables
58      ierr = ierr + dom_ice_alloc    ()      ! domain
59      ierr = ierr + sbc_ice_alloc    ()      ! surface forcing
60      ierr = ierr + thd_ice_alloc    ()      ! thermodynamics
61      ierr = ierr + lim_itd_me_alloc ()      ! ice thickness distribution - mechanics
62      !
63      IF( lk_mpp    )   CALL mpp_sum( ierr )
64      IF( ierr /= 0 )   CALL ctl_stop('STOP', 'ice_init : unable to allocate ice arrays')
65      !
66      !                                ! adequation jpk versus ice/snow layers/categories
67      IF( jpl   > jpk  .OR.  jpm    > jpk .OR.                                    &
68          jkmax > jpk  .OR.  nlay_s > jpk      )   CALL ctl_stop( 'STOP',         &
69         &     'ice_init: the 3rd dimension of workspace arrays is too small.',   &
70         &     'use more ocean levels or less ice/snow layers/categories.' )
71
72      !                                ! Open the namelist file
73      CALL ctl_opn( numnam_ice, 'namelist_ice', 'OLD', 'FORMATTED', 'SEQUENTIAL', -1, numout, lwp )
74      !
75      CALL ice_run                     ! set some ice run parameters
76      !
77      CALL lim_thd_init                ! set ice thermodynics parameters
78      !
79      CALL lim_thd_sal_init            ! set ice salinity parameters
80      !
81      rdt_ice = nn_fsbc * rdttra(1)    ! sea-ice timestep
82      !
83      CALL lim_msh                     ! ice mesh initialization
84      !
85      CALL lim_itd_ini                 ! ice thickness distribution initialization
86      !
87
88      !                                ! Initial sea-ice state
89      IF( .NOT.ln_rstart ) THEN              ! start from rest
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 bulk variables
94         CALL lim_var_glo2eqv                   ! convert global variables in equivalent variables
95      ELSE                                   ! start from a restart file
96         CALL lim_rst_read                      ! read the restart file
97         numit = nit000 - 1
98         CALL lim_var_agg(1)                    ! aggregate ice variables
99         CALL lim_var_glo2eqv                   ! convert global var in equivalent variables
100      ENDIF
101      !
102      CALL lim_sbc_init                ! ice surface boundary condition   
103      !
104      fr_i(:,:) = at_i(:,:)           ! initialisation of sea-ice fraction
105      !
106      nstart = numit  + nn_fsbc     
107      nitrun = nitend - nit000 + 1 
108      nlast  = numit  + nitrun 
109      !
110      IF( nstock == 0  )   nstock = nlast + 1
111      !
112   END SUBROUTINE ice_init
113
114
115   SUBROUTINE ice_run
116      !!-------------------------------------------------------------------
117      !!                  ***  ROUTINE ice_run ***
118      !!                 
119      !! ** Purpose :   Definition some run parameter for ice model
120      !!
121      !! ** Method  :   Read the namicerun namelist and check the parameter
122      !!              values called at the first timestep (nit000)
123      !!
124      !! ** input   :   Namelist namicerun
125      !!-------------------------------------------------------------------
126      NAMELIST/namicerun/ cn_icerst_in, cn_icerst_out, ln_limdyn, amax, cai, cao, ln_nicep, ln_limdiahsb
127      !!-------------------------------------------------------------------
128      !                   
129      REWIND( numnam_ice )                ! Read Namelist namicerun
130      READ  ( numnam_ice , namicerun )
131      !
132      IF( lk_mpp .AND. ln_nicep ) THEN
133         ln_nicep = .FALSE.
134         CALL ctl_warn( 'ice_run : specific control print for LIM3 desactivated with MPI' )
135      ENDIF       
136      !
137      IF(lwp) THEN                        ! control print
138         WRITE(numout,*)
139         WRITE(numout,*) 'ice_run : ice share parameters for dynamics/advection/thermo of sea-ice'
140         WRITE(numout,*) ' ~~~~~~'
141         WRITE(numout,*) '   switch for ice dynamics (1) or not (0)      ln_limdyn   = ', ln_limdyn
142         WRITE(numout,*) '   maximum ice concentration                               = ', amax
143         WRITE(numout,*) '   atmospheric drag over sea ice                           = ', cai
144         WRITE(numout,*) '   atmospheric drag over ocean                             = ', cao
145         WRITE(numout,*) '   Several ice points in the ice or not in ocean.output    = ', ln_nicep
146         WRITE(numout,*) '   Diagnose heat/salt budget or not          ln_limdiahsb  = ', ln_limdiahsb
147      ENDIF
148      !
149   END SUBROUTINE ice_run
150
151
152   SUBROUTINE lim_itd_ini
153      !!------------------------------------------------------------------
154      !!                ***  ROUTINE lim_itd_ini ***
155      !!
156      !! ** Purpose :   Initializes the ice thickness distribution
157      !! ** Method  :   ...
158      !!------------------------------------------------------------------
159      INTEGER  ::   jl, jm               ! dummy loop index
160      REAL(wp) ::   zc1, zc2, zc3, zx1   ! local scalars
161      !!------------------------------------------------------------------
162
163      IF(lwp) WRITE(numout,*)
164      IF(lwp) WRITE(numout,*) 'lim_itd_ini : Initialization of ice thickness distribution '
165      IF(lwp) WRITE(numout,*) '~~~~~~~~~~~~'
166
167      !------------------------------------------------------------------------------!
168      ! 1) Ice thickness distribution parameters initialization   
169      !------------------------------------------------------------------------------!
170
171      !- Types boundaries (integer)
172      !----------------------------
173      ice_cat_bounds(1,1) = 1
174      ice_cat_bounds(1,2) = jpl
175
176      !- Number of ice thickness categories in each ice type
177      DO jm = 1, jpm
178         ice_ncat_types(jm) = ice_cat_bounds(jm,2) - ice_cat_bounds(jm,1) + 1 
179      END DO
180
181      !- Make the correspondence between thickness categories and ice types
182      !---------------------------------------------------------------------
183      DO jm = 1, jpm       !over types
184         DO jl = ice_cat_bounds(jm,1), ice_cat_bounds(jm,2) !over thickness categories
185            ice_types(jl) = jm
186         END DO
187      END DO
188
189      IF(lwp) THEN 
190         WRITE(numout,*) ' Number of ice types jpm =      ', jpm
191         WRITE(numout,*) ' Number of ice categories jpl = ', jpl
192         DO jm = 1, jpm
193            WRITE(numout,*) ' Ice type ', jm
194            WRITE(numout,*) ' Number of thickness categories ', ice_ncat_types(jm)
195            WRITE(numout,*) ' Thickness category boundaries  ', ice_cat_bounds(jm,1:2)
196         END DO
197         WRITE(numout,*) 'Ice type vector', ice_types(1:jpl)
198         WRITE(numout,*)
199      ENDIF
200
201      !- Thickness categories boundaries
202      !----------------------------------
203      hi_max(:) = 0._wp
204      hi_max_typ(:,:) = 0._wp
205
206      !- Type 1 - undeformed ice
207      zc1 =  3._wp / REAL( ice_cat_bounds(1,2) - ice_cat_bounds(1,1) + 1 , wp )
208      zc2 = 10._wp * zc1
209      zc3 =  3._wp
210
211      DO jl = ice_cat_bounds(1,1), ice_cat_bounds(1,2)
212         zx1 = REAL( jl-1 , wp ) / REAL( ice_cat_bounds(1,2) - ice_cat_bounds(1,1) + 1 , wp )
213         hi_max(jl) = hi_max(jl-1) + zc1 + zc2 * (1._wp + TANH( zc3 * (zx1 - 1._wp ) ) )
214      END DO
215
216      !- Fill in the hi_max_typ vector, useful in other circumstances
217      ! Tricky trick: hi_max_typ is actually not used in the code and will be removed in a
218      ! next flyspray at this time, the tricky trick will also be removed (Martin, march 08)
219      DO jl = ice_cat_bounds(1,1), ice_cat_bounds(1,2)
220         hi_max_typ(jl,1) = hi_max(jl)
221      END DO
222
223      IF(lwp) WRITE(numout,*) ' Thickness category boundaries independently of ice type '
224      IF(lwp) WRITE(numout,*) ' hi_max ', hi_max(0:jpl)
225
226      IF(lwp) WRITE(numout,*) ' Thickness category boundaries inside ice types '
227      IF(lwp) THEN
228         DO jm = 1, jpm
229            WRITE(numout,*) ' Type number ', jm
230            WRITE(numout,*) ' hi_max_typ : ', hi_max_typ(0:ice_ncat_types(jm),jm)
231         END DO
232      ENDIF
233      !
234      DO jl = 1, jpl
235         hi_mean(jl) = ( hi_max(jl) + hi_max(jl-1) ) * 0.5_wp
236      END DO
237      !
238      tn_ice(:,:,:) = t_su(:,:,:)
239      !
240   END SUBROUTINE lim_itd_ini
241
242#else
243   !!----------------------------------------------------------------------
244   !!   Default option :        Empty module           NO LIM sea-ice model
245   !!----------------------------------------------------------------------
246CONTAINS
247   SUBROUTINE ice_init        ! Empty routine
248   END SUBROUTINE ice_init
249#endif
250
251   !!======================================================================
252END MODULE iceini
Note: See TracBrowser for help on using the repository browser.