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

source: trunk/NEMOGCM/NEMO/LIM_SRC_3/iceini.F90 @ 3319

Last change on this file since 3319 was 3294, checked in by rblod, 12 years ago

Merge of 3.4beta into the trunk

  • Property svn:keywords set to Id
File size: 11.1 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   !!----------------------------------------------------------------------
12   !!   'key_lim3' :                                   LIM sea-ice model
13   !!----------------------------------------------------------------------
14   !!   ice_init       : sea-ice model initialization
15   !!----------------------------------------------------------------------
[2715]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
[825]34
35   IMPLICIT NONE
36   PRIVATE
37
[2715]38   PUBLIC   ice_init   ! called by sbcice_lim.F90
[2528]39
[825]40   !!----------------------------------------------------------------------
[2715]41   !! NEMO/LIM3 4.0 , UCL - NEMO Consortium (2011)
[1156]42   !! $Id$
[2528]43   !! Software governed by the CeCILL licence     (NEMOGCM/NEMO_CeCILL.txt)
[825]44   !!----------------------------------------------------------------------
45CONTAINS
46
47   SUBROUTINE ice_init
48      !!----------------------------------------------------------------------
49      !!                  ***  ROUTINE ice_init  ***
50      !!
[2715]51      !! ** purpose :   Allocate all the dynamic arrays of the LIM-3 modules
[825]52      !!----------------------------------------------------------------------
[2715]53      INTEGER :: ierr
54      !!----------------------------------------------------------------------
55
56      !                                ! Allocate the ice arrays
[3294]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
[2528]62      !
[2715]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
[2528]72      !                                ! Open the namelist file
[1581]73      CALL ctl_opn( numnam_ice, 'namelist_ice', 'OLD', 'FORMATTED', 'SEQUENTIAL', -1, numout, lwp )
[2477]74      !
[2715]75      CALL ice_run                     ! set some ice run parameters
[2528]76      !
[2715]77      CALL lim_thd_init                ! set ice thermodynics parameters
[2477]78      !
[2715]79      CALL lim_thd_sal_init            ! set ice salinity parameters
[2477]80      !
81      rdt_ice = nn_fsbc * rdttra(1)    ! sea-ice timestep
82      !
83      CALL lim_msh                     ! ice mesh initialization
84      !
[2715]85      CALL lim_itd_ini                 ! ice thickness distribution initialization
86      !
87      CALL lim_sbc_init                ! ice surface boundary condition   
[921]88
[2715]89
[2528]90      !                                ! Initial sea-ice state
[2477]91      IF( .NOT.ln_rstart ) THEN              ! start from rest
[825]92         numit = 0
93         numit = nit000 - 1
[2477]94         CALL lim_istate                        ! start from rest: sea-ice deduced from sst
95         CALL lim_var_agg(1)                    ! aggregate category variables in bulk variables
96         CALL lim_var_glo2eqv                   ! convert global variables in equivalent variables
97      ELSE                                   ! start from a restart file
98         CALL lim_rst_read                      ! read the restart file
[825]99         numit = nit000 - 1
[2477]100         CALL lim_var_agg(1)                    ! aggregate ice variables
101         CALL lim_var_glo2eqv                   ! convert global var in equivalent variables
[825]102      ENDIF
[2477]103      !
[1037]104      fr_i(:,:) = at_i(:,:)           ! initialisation of sea-ice fraction
[2477]105      !
[2528]106      nstart = numit  + nn_fsbc     
107      nitrun = nitend - nit000 + 1 
108      nlast  = numit  + nitrun 
[2477]109      !
110      IF( nstock == 0  )   nstock = nlast + 1
[2528]111      !
[825]112   END SUBROUTINE ice_init
113
[2528]114
[825]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
[2715]122      !!              values called at the first timestep (nit000)
[825]123      !!
124      !! ** input   :   Namelist namicerun
125      !!-------------------------------------------------------------------
[1229]126      NAMELIST/namicerun/ cn_icerst_in, cn_icerst_out, ln_limdyn, acrit, hsndif, hicdif, cai, cao, ln_nicep
[825]127      !!-------------------------------------------------------------------
[2528]128      !                   
129      REWIND( numnam_ice )                ! Read Namelist namicerun
130      READ  ( numnam_ice , namicerun )
131      !
[1055]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       
[2528]136      !
137      IF(lwp) THEN                        ! control print
[825]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,*) '   minimum fraction for leads in the NH (SH)  acrit(1/2)   = ', acrit(:)
143         WRITE(numout,*) '   computation of temp. in snow (=0) or not (=9999) hsndif = ', hsndif
144         WRITE(numout,*) '   computation of temp. in ice  (=0) or not (=9999) hicdif = ', hicdif
[830]145         WRITE(numout,*) '   atmospheric drag over sea ice                           = ', cai
146         WRITE(numout,*) '   atmospheric drag over ocean                             = ', cao
[2528]147         WRITE(numout,*) '   Several ice points in the ice or not in ocean.output    = ', ln_nicep
[825]148      ENDIF
[2528]149      !
[825]150   END SUBROUTINE ice_run
151
[2528]152
[825]153   SUBROUTINE lim_itd_ini
[921]154      !!------------------------------------------------------------------
155      !!                ***  ROUTINE lim_itd_ini ***
156      !!
[2528]157      !! ** Purpose :   Initializes the ice thickness distribution
158      !! ** Method  :   ...
[921]159      !!------------------------------------------------------------------
[2528]160      INTEGER  ::   jl, jm               ! dummy loop index
161      REAL(wp) ::   zc1, zc2, zc3, zx1   ! local scalars
162      !!------------------------------------------------------------------
[825]163
[2528]164      IF(lwp) WRITE(numout,*)
[1112]165      IF(lwp) WRITE(numout,*) 'lim_itd_ini : Initialization of ice thickness distribution '
166      IF(lwp) WRITE(numout,*) '~~~~~~~~~~~~'
[825]167
[921]168      !------------------------------------------------------------------------------!
169      ! 1) Ice thickness distribution parameters initialization   
170      !------------------------------------------------------------------------------!
[825]171
[834]172      !- Types boundaries (integer)
173      !----------------------------
[825]174      ice_cat_bounds(1,1) = 1
175      ice_cat_bounds(1,2) = jpl
176
177      !- Number of ice thickness categories in each ice type
178      DO jm = 1, jpm
179         ice_ncat_types(jm) = ice_cat_bounds(jm,2) - ice_cat_bounds(jm,1) + 1 
180      END DO
181
182      !- Make the correspondence between thickness categories and ice types
183      !---------------------------------------------------------------------
184      DO jm = 1, jpm       !over types
185         DO jl = ice_cat_bounds(jm,1), ice_cat_bounds(jm,2) !over thickness categories
186            ice_types(jl) = jm
187         END DO
188      END DO
189
[1112]190      IF(lwp) THEN 
191         WRITE(numout,*) ' Number of ice types jpm =      ', jpm
192         WRITE(numout,*) ' Number of ice categories jpl = ', jpl
193         DO jm = 1, jpm
194            WRITE(numout,*) ' Ice type ', jm
195            WRITE(numout,*) ' Number of thickness categories ', ice_ncat_types(jm)
196            WRITE(numout,*) ' Thickness category boundaries  ', ice_cat_bounds(jm,1:2)
197         END DO
198         WRITE(numout,*) 'Ice type vector', ice_types(1:jpl)
199         WRITE(numout,*)
200      ENDIF
[825]201
[834]202      !- Thickness categories boundaries
203      !----------------------------------
[2528]204      hi_max(:) = 0._wp
205      hi_max_typ(:,:) = 0._wp
[825]206
207      !- Type 1 - undeformed ice
[2528]208      zc1 =  3._wp / REAL( ice_cat_bounds(1,2) - ice_cat_bounds(1,1) + 1 , wp )
209      zc2 = 10._wp * zc1
210      zc3 =  3._wp
[825]211
[834]212      DO jl = ice_cat_bounds(1,1), ice_cat_bounds(1,2)
[2528]213         zx1 = REAL( jl-1 , wp ) / REAL( ice_cat_bounds(1,2) - ice_cat_bounds(1,1) + 1 , wp )
214         hi_max(jl) = hi_max(jl-1) + zc1 + zc2 * (1._wp + TANH( zc3 * (zx1 - 1._wp ) ) )
[834]215      END DO
[825]216
[862]217      !- Fill in the hi_max_typ vector, useful in other circumstances
[2528]218      ! Tricky trick: hi_max_typ is actually not used in the code and will be removed in a
219      ! next flyspray at this time, the tricky trick will also be removed (Martin, march 08)
[834]220      DO jl = ice_cat_bounds(1,1), ice_cat_bounds(1,2)
221         hi_max_typ(jl,1) = hi_max(jl)
222      END DO
[825]223
[1112]224      IF(lwp) WRITE(numout,*) ' Thickness category boundaries independently of ice type '
225      IF(lwp) WRITE(numout,*) ' hi_max ', hi_max(0:jpl)
[825]226
[1112]227      IF(lwp) WRITE(numout,*) ' Thickness category boundaries inside ice types '
228      IF(lwp) THEN
229         DO jm = 1, jpm
230            WRITE(numout,*) ' Type number ', jm
231            WRITE(numout,*) ' hi_max_typ : ', hi_max_typ(0:ice_ncat_types(jm),jm)
232         END DO
233      ENDIF
[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      !
[834]239      tn_ice(:,:,:) = t_su(:,:,:)
[2528]240      !
[921]241   END SUBROUTINE lim_itd_ini
[825]242
243#else
244   !!----------------------------------------------------------------------
245   !!   Default option :        Empty module           NO LIM sea-ice model
246   !!----------------------------------------------------------------------
247CONTAINS
248   SUBROUTINE ice_init        ! Empty routine
249   END SUBROUTINE ice_init
250#endif
251
252   !!======================================================================
253END MODULE iceini
Note: See TracBrowser for help on using the repository browser.