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

source: branches/2015/dev_r5044_CNRS_LIM3CLEAN/NEMOGCM/NEMO/LIM_SRC_3/iceini.F90 @ 5048

Last change on this file since 5048 was 5048, checked in by vancop, 9 years ago

new itd boundaries, namelist changes, mono-category and comments

  • Property svn:keywords set to Id
File size: 11.6 KB
RevLine 
[825]1MODULE iceini
2   !!======================================================================
3   !!                       ***  MODULE iceini   ***
4   !!   Sea-ice model : LIM Sea ice model Initialization
5   !!======================================================================
[2528]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
[2715]8   !!            4.0  ! 2011-02  (G. Madec) dynamical allocation
[2528]9   !!----------------------------------------------------------------------
[825]10#if defined key_lim3
11   !!----------------------------------------------------------------------
[3625]12   !!   'key_lim3'                                     LIM sea-ice model
[825]13   !!----------------------------------------------------------------------
[3625]14   !!   ice_init      : sea-ice model initialization
[825]15   !!----------------------------------------------------------------------
[3625]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   USE lib_fortran    ! Fortran utilities (allows no signed zero when 'key_nosignedzero' defined) 
[825]35
36   IMPLICIT NONE
37   PRIVATE
38
[2715]39   PUBLIC   ice_init   ! called by sbcice_lim.F90
[2528]40
[825]41   !!----------------------------------------------------------------------
[4161]42   !! NEMO/LIM3 4.0 , UCL - NEMO Consortium (2011)
[1156]43   !! $Id$
[2528]44   !! Software governed by the CeCILL licence     (NEMOGCM/NEMO_CeCILL.txt)
[825]45   !!----------------------------------------------------------------------
46CONTAINS
47
48   SUBROUTINE ice_init
49      !!----------------------------------------------------------------------
50      !!                  ***  ROUTINE ice_init  ***
51      !!
[2715]52      !! ** purpose :   Allocate all the dynamic arrays of the LIM-3 modules
[825]53      !!----------------------------------------------------------------------
[2715]54      INTEGER :: ierr
55      !!----------------------------------------------------------------------
56
57      !                                ! Allocate the ice arrays
[3294]58      ierr =        ice_alloc        ()      ! ice variables
59      ierr = ierr + dom_ice_alloc    ()      ! domain
60      ierr = ierr + sbc_ice_alloc    ()      ! surface forcing
61      ierr = ierr + thd_ice_alloc    ()      ! thermodynamics
62      ierr = ierr + lim_itd_me_alloc ()      ! ice thickness distribution - mechanics
[2528]63      !
[2715]64      IF( lk_mpp    )   CALL mpp_sum( ierr )
65      IF( ierr /= 0 )   CALL ctl_stop('STOP', 'ice_init : unable to allocate ice arrays')
66      !
67      !                                ! adequation jpk versus ice/snow layers/categories
[4873]68      IF( jpl > jpk .OR. (nlay_i+1) > jpk .OR. nlay_s > jpk )   &
[4869]69         &      CALL ctl_stop( 'STOP',                     &
[2715]70         &     'ice_init: the 3rd dimension of workspace arrays is too small.',   &
71         &     'use more ocean levels or less ice/snow layers/categories.' )
72
[4298]73                                       ! Open the reference and configuration namelist files and namelist output file
74      CALL ctl_opn( numnam_ice_ref, 'namelist_ice_ref',    'OLD',     'FORMATTED', 'SEQUENTIAL', -1, numout, lwp ) 
75      CALL ctl_opn( numnam_ice_cfg, 'namelist_ice_cfg',    'OLD',     'FORMATTED', 'SEQUENTIAL', -1, numout, lwp )
[4624]76      IF(lwm) CALL ctl_opn( numoni, 'output.namelist.ice', 'UNKNOWN', 'FORMATTED', 'SEQUENTIAL', -1, numout, lwp, 1 )
[2477]77      !
[2715]78      CALL ice_run                     ! set some ice run parameters
[2528]79      !
[2715]80      CALL lim_thd_init                ! set ice thermodynics parameters
[2477]81      !
[2715]82      CALL lim_thd_sal_init            ! set ice salinity parameters
[2477]83      !
[3625]84      rdt_ice   = nn_fsbc * rdttra(1)  ! sea-ice timestep
85      r1_rdtice = 1._wp / rdt_ice      ! sea-ice timestep inverse
[2477]86      !
87      CALL lim_msh                     ! ice mesh initialization
88      !
[2715]89      CALL lim_itd_ini                 ! ice thickness distribution initialization
90      !
[4831]91      CALL lim_itd_me_init             ! ice thickness distribution initialization
[2528]92      !                                ! Initial sea-ice state
[4333]93      IF( .NOT. ln_rstart ) THEN              ! start from rest
[825]94         numit = 0
95         numit = nit000 - 1
[2477]96         CALL lim_istate                        ! start from rest: sea-ice deduced from sst
97         CALL lim_var_agg(1)                    ! aggregate category variables in bulk variables
98         CALL lim_var_glo2eqv                   ! convert global variables in equivalent variables
99      ELSE                                   ! start from a restart file
100         CALL lim_rst_read                      ! read the restart file
[825]101         numit = nit000 - 1
[2477]102         CALL lim_var_agg(1)                    ! aggregate ice variables
103         CALL lim_var_glo2eqv                   ! convert global var in equivalent variables
[825]104      ENDIF
[2477]105      !
[4293]106      hi_max(jpl) = 99._wp  ! Set hi_max(jpl) to a big value to ensure that all ice is thinner than hi_max(jpl)
107      !
[4333]108      CALL lim_sbc_init                 ! ice surface boundary condition   
[4205]109      !
[4333]110      fr_i(:,:) = at_i(:,:)             ! initialisation of sea-ice fraction
111      tn_ice(:,:,:) = t_su(:,:,:)       ! initialisation of surface temp for coupled simu
[2477]112      !
[2528]113      nstart = numit  + nn_fsbc     
114      nitrun = nitend - nit000 + 1 
115      nlast  = numit  + nitrun 
[2477]116      !
117      IF( nstock == 0  )   nstock = nlast + 1
[2528]118      !
[825]119   END SUBROUTINE ice_init
120
[2528]121
[825]122   SUBROUTINE ice_run
123      !!-------------------------------------------------------------------
124      !!                  ***  ROUTINE ice_run ***
125      !!                 
126      !! ** Purpose :   Definition some run parameter for ice model
127      !!
128      !! ** Method  :   Read the namicerun namelist and check the parameter
[2715]129      !!              values called at the first timestep (nit000)
[825]130      !!
131      !! ** input   :   Namelist namicerun
132      !!-------------------------------------------------------------------
[5047]133      NAMELIST/namicerun/ cn_icerst_in, cn_icerst_out, ln_limdyn, amax, ln_nicep, ln_limdiahsb, ln_limdiaout
[4298]134      INTEGER  ::   ios                 ! Local integer output status for namelist read
[825]135      !!-------------------------------------------------------------------
[2528]136      !                   
[4298]137      REWIND( numnam_ice_ref )              ! Namelist namicerun in reference namelist : Parameters for ice
138      READ  ( numnam_ice_ref, namicerun, IOSTAT = ios, ERR = 901)
139901   IF( ios /= 0 ) CALL ctl_nam ( ios , 'namicerun in reference namelist', lwp )
140
141      REWIND( numnam_ice_cfg )              ! Namelist namicerun in configuration namelist : Parameters for ice
142      READ  ( numnam_ice_cfg, namicerun, IOSTAT = ios, ERR = 902 )
143902   IF( ios /= 0 ) CALL ctl_nam ( ios , 'namicerun in configuration namelist', lwp )
[4624]144      IF(lwm) WRITE ( numoni, namicerun )
[2528]145      !
[4333]146      !IF( lk_mpp .AND. ln_nicep ) THEN
147      !   ln_nicep = .FALSE.
148      !   CALL ctl_warn( 'ice_run : specific control print for LIM3 desactivated with MPI' )
149      !ENDIF
[2528]150      !
151      IF(lwp) THEN                        ! control print
[825]152         WRITE(numout,*)
153         WRITE(numout,*) 'ice_run : ice share parameters for dynamics/advection/thermo of sea-ice'
154         WRITE(numout,*) ' ~~~~~~'
155         WRITE(numout,*) '   switch for ice dynamics (1) or not (0)      ln_limdyn   = ', ln_limdyn
[4161]156         WRITE(numout,*) '   maximum ice concentration                               = ', amax
[2528]157         WRITE(numout,*) '   Several ice points in the ice or not in ocean.output    = ', ln_nicep
[4161]158         WRITE(numout,*) '   Diagnose heat/salt budget or not          ln_limdiahsb  = ', ln_limdiahsb
159         WRITE(numout,*) '   Output   heat/salt budget or not          ln_limdiaout  = ', ln_limdiaout
[825]160      ENDIF
[2528]161      !
[825]162   END SUBROUTINE ice_run
163
[2528]164
[825]165   SUBROUTINE lim_itd_ini
[921]166      !!------------------------------------------------------------------
167      !!                ***  ROUTINE lim_itd_ini ***
168      !!
[2528]169      !! ** Purpose :   Initializes the ice thickness distribution
170      !! ** Method  :   ...
[4293]171      !!    Note    : hi_max(jpl) is here set up to a value close to 7 m for
172      !!              limistate (only) and is changed to 99 m in ice_init
[921]173      !!------------------------------------------------------------------
[5048]174      INTEGER  ::   jl                        ! dummy loop index
175      REAL(wp) ::   zc1, zc2, zc3, zx1        ! local scalars
176      REAL(wp) ::   zhmax, znum, zden, zalpha !
[2528]177      !!------------------------------------------------------------------
[825]178
[2528]179      IF(lwp) WRITE(numout,*)
[1112]180      IF(lwp) WRITE(numout,*) 'lim_itd_ini : Initialization of ice thickness distribution '
181      IF(lwp) WRITE(numout,*) '~~~~~~~~~~~~'
[825]182
[921]183      !------------------------------------------------------------------------------!
184      ! 1) Ice thickness distribution parameters initialization   
185      !------------------------------------------------------------------------------!
[1112]186      IF(lwp) THEN 
187         WRITE(numout,*) ' Number of ice categories jpl = ', jpl
188      ENDIF
[825]189
[834]190      !- Thickness categories boundaries
191      !----------------------------------
[5048]192
193      !  Clem - je sais pas encore dans quelle namelist les mettre, ca depend des chgts liés à bdy
194      nn_hibnd  = 2                !  thickness category boundaries: tanh function (1) h^(-alpha) (2)
195      rn_himean = 2.5              !  mean thickness of the domain (used to compute category boundaries, nn_hibnd = 2 only)
196
[2528]197      hi_max(:) = 0._wp
[825]198
[5048]199      SELECT CASE ( nn_hbnd  )       
200                                   !----------------------
201         CASE (1)                  ! tanh function (CICE)
202                                   !----------------------
[825]203
[5048]204         zc1 =  3._wp / REAL( jpl, wp )
205         zc2 = 10._wp * zc1
206         zc3 =  3._wp
[825]207
[5048]208         DO jl = 1, jpl
209            zx1 = REAL( jl-1, wp ) / REAL( jpl, wp )
210            hi_max(jl) = hi_max(jl-1) + zc1 + zc2 * (1._wp + TANH( zc3 * (zx1 - 1._wp ) ) )
211         END DO
212
213                                   !----------------------
214         CASE (2)                  ! h^(-alpha) function
215                                   !----------------------
216
217         zalpha = 0.05             ! exponent of the transform function
218
219         zhmax  = 3.*rn_himean
220
221         DO jl = 1, jpl 
222            znum = jpl * ( zhmax+1 )**zalpha
223            zden = ( jpl - jl ) * ( zhmax+1 )**zalpha + jl
224            hi_max(jl) = ( znum / zden )**(1./zalpha) - 1
225         END DO
226
227      END SELECT
228
229      ! mv- would be nice if we could put the instruction hi_max(jpl) = 99 here
230
[4869]231      IF(lwp) WRITE(numout,*) ' Thickness category boundaries '
[1112]232      IF(lwp) WRITE(numout,*) ' hi_max ', hi_max(0:jpl)
[825]233
[2528]234      !
[862]235      DO jl = 1, jpl
[2528]236         hi_mean(jl) = ( hi_max(jl) + hi_max(jl-1) ) * 0.5_wp
[862]237      END DO
[2528]238      !
239      !
[921]240   END SUBROUTINE lim_itd_ini
[825]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.