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

source: branches/nemo_v3_3_beta/NEMOGCM/NEMO/LIM_SRC_3/iceini.F90 @ 2380

Last change on this file since 2380 was 2287, checked in by smasson, 14 years ago

update licence of all NEMO files...

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