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 – NEMO

source: trunk/NEMO/LIM_SRC/iceini.F90 @ 508

Last change on this file since 508 was 508, checked in by opalod, 18 years ago

nemo_v1_update_071:RB: add iom for restart and reorganization of restart

  • Property svn:eol-style set to native
  • Property svn:keywords set to Author Date Id Revision
File size: 5.5 KB
Line 
1MODULE iceini
2   !!======================================================================
3   !!                       ***  MODULE iceini   ***
4   !!   Sea-ice model : LIM Sea ice model Initialization
5   !!======================================================================
6   !! History :   1.0  !  02-08  (G. Madec)  F90: Free form and modules
7   !!             2.0  !  03-08  (C. Ethe)  add ice_run
8   !!----------------------------------------------------------------------
9#if defined key_ice_lim
10   !!----------------------------------------------------------------------
11   !!   'key_ice_lim' :                                   LIM sea-ice model
12   !!----------------------------------------------------------------------
13   !!----------------------------------------------------------------------
14   !!   ice_init       : sea-ice model initialization
15   !!   ice_run        : Definition some run parameter for ice model
16   !!----------------------------------------------------------------------
17   USE dom_oce
18   USE in_out_manager
19   USE ice_oce         ! ice variables
20   USE flx_oce
21   USE phycst          ! Define parameters for the routines
22   USE ocfzpt
23   USE ice
24   USE limmsh
25   USE limistate
26   USE limrst   
27   USE ini1d           ! initialization of the 1D configuration
28     
29   IMPLICIT NONE
30   PRIVATE
31
32   PUBLIC   ice_init                 ! called by opa.F90
33
34   LOGICAL , PUBLIC               ::   ln_limdyn = .TRUE.   !: flag for ice dynamics (T) or not (F)
35   REAL(wp), PUBLIC               ::   hsndif = 0.e0        !: computation of temp. in snow (0) or not (9999)
36   REAL(wp), PUBLIC               ::   hicdif = 0.e0        !: computation of temp. in ice (0) or not (9999)
37   REAL(wp), PUBLIC, DIMENSION(2) ::   acrit  = (/ 1.e-06 , 1.e-06 /)    !: minimum fraction for leads in
38      !                                                                  !  north and south hemisphere
39   !!----------------------------------------------------------------------
40   !!   LIM 2.0,  UCL-LOCEAN-IPSL (2005)
41   !! $Header$
42   !! This software is governed by the CeCILL licence see modipsl/doc/NEMO_CeCILL.txt
43   !!----------------------------------------------------------------------
44
45CONTAINS
46
47   SUBROUTINE ice_init
48      !!----------------------------------------------------------------------
49      !!                  ***  ROUTINE ice_init  ***
50      !!
51      !! ** purpose :   
52      !!----------------------------------------------------------------------
53      CHARACTER(len=80) :: namelist_icename
54      !!----------------------------------------------------------------------
55      !
56      ! Open the namelist file
57      namelist_icename = 'namelist_ice'
58      CALL ctlopn(numnam_ice,namelist_icename,'OLD', 'FORMATTED', 'SEQUENTIAL',   &
59                     1,numout,.FALSE.,1)     
60      CALL ice_run                    !  read in namelist some run parameters
61                 
62      ! Louvain la Neuve Ice model
63      IF( nacc == 1 ) THEN
64          dtsd2   = nfice * rdtmin * 0.5
65          rdt_ice = nfice * rdtmin
66      ELSE
67          dtsd2   = nfice * rdt * 0.5
68          rdt_ice = nfice * rdt
69      ENDIF
70
71      CALL lim_msh                    ! ice mesh initialization
72     
73      ! Initial sea-ice state
74      IF( .NOT.ln_rstart ) THEN
75         CALL lim_istate              ! start from rest: sea-ice deduced from sst
76      ELSE
77         CALL lim_rst_read            ! start from a restart file
78      ENDIF
79     
80      tn_ice(:,:) = sist(:,:)         ! initialisation of ice temperature   
81      freeze(:,:) = 1.0 - frld(:,:)   ! initialisation of sea/ice cover   
82# if defined key_coupled
83      alb_ice(:,:) = albege(:,:)      ! sea-ice albedo
84# endif
85      !
86   END SUBROUTINE ice_init
87
88
89   SUBROUTINE ice_run
90      !!-------------------------------------------------------------------
91      !!                  ***  ROUTINE ice_run ***
92      !!                 
93      !! ** Purpose :   Definition some run parameter for ice model
94      !!
95      !! ** Method  :   Read the namicerun namelist and check the parameter
96      !!       values called at the first timestep (nit000)
97      !!
98      !! ** input   :   Namelist namicerun
99      !!-------------------------------------------------------------------
100      NAMELIST/namicerun/ ln_limdyn, acrit, hsndif, hicdif
101      !!-------------------------------------------------------------------
102      !                   
103      REWIND ( numnam_ice )                       ! Read Namelist namicerun
104      READ   ( numnam_ice , namicerun )
105
106      IF( lk_cfg_1d  )   ln_limdyn = .FALSE.      ! No ice transport in 1D configuration
107
108      IF(lwp) THEN
109         WRITE(numout,*)
110         WRITE(numout,*) 'ice_run : ice share parameters for dynamics/advection/thermo of sea-ice'
111         WRITE(numout,*) ' ~~~~~~'
112         WRITE(numout,*) '   switch for ice dynamics (1) or not (0)      ln_limdyn   = ', ln_limdyn
113         WRITE(numout,*) '   minimum fraction for leads in the NH (SH)  acrit(1/2)   = ', acrit(:)
114         WRITE(numout,*) '   computation of temp. in snow (=0) or not (=9999) hsndif = ', hsndif
115         WRITE(numout,*) '   computation of temp. in ice  (=0) or not (=9999) hicdif = ', hicdif
116      ENDIF
117      !
118   END SUBROUTINE ice_run
119
120#else
121   !!----------------------------------------------------------------------
122   !!   Default option :        Empty module           NO LIM sea-ice model
123   !!----------------------------------------------------------------------
124CONTAINS
125   SUBROUTINE ice_init        ! Empty routine
126   END SUBROUTINE ice_init
127#endif
128
129   !!======================================================================
130END MODULE iceini
Note: See TracBrowser for help on using the repository browser.