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 @ 2528

Last change on this file since 2528 was 2528, checked in by rblod, 13 years ago

Update NEMOGCM from branch nemo_v3_3_beta

  • Property svn:keywords set to Id
File size: 9.7 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   !!----------------------------------------------------------------------
9#if defined key_lim3
10   !!----------------------------------------------------------------------
11   !!   'key_lim3' :                                   LIM sea-ice model
12   !!----------------------------------------------------------------------
13   !!   ice_init       : sea-ice model initialization
14   !!----------------------------------------------------------------------
15   USE phycst         ! physical constants
16   USE dom_oce        ! ocean domain
17   USE sbc_oce        ! Surface boundary condition: ocean fields
18   USE sbc_ice        ! Surface boundary condition: ice fields
19   USE ice            ! LIM: sea-ice variables
20   USE limmsh         ! LIM: mesh
21   USE limistate      ! LIM: initial state
22   USE limrst         ! LIM: restart
23   USE limthd         ! LIM: ice thermodynamics
24   USE limthd_sal     ! LIM: ice thermodynamics: salinity
25   USE par_ice        ! LIM: sea-ice parameters
26   USE limvar         ! LIM: variables
27   USE in_out_manager ! I/O manager
28   USE lib_mpp        ! MPP library
29
30   IMPLICIT NONE
31   PRIVATE
32
33   PUBLIC   ice_init   ! called by opa.F90
34
35   !!----------------------------------------------------------------------
36   !! NEMO/LIM3 3.3 , UCL - NEMO Consortium (2010)
37   !! $Id$
38   !! Software governed by the CeCILL licence     (NEMOGCM/NEMO_CeCILL.txt)
39   !!----------------------------------------------------------------------
40CONTAINS
41
42   SUBROUTINE ice_init
43      !!----------------------------------------------------------------------
44      !!                  ***  ROUTINE ice_init  ***
45      !!
46      !! ** purpose :   
47      !!----------------------------------------------------------------------
48      !
49      !                                ! Open the namelist file
50      CALL ctl_opn( numnam_ice, 'namelist_ice', 'OLD', 'FORMATTED', 'SEQUENTIAL', -1, numout, lwp )
51      !
52      CALL ice_run                     ! namelist read some ice run parameters
53      !
54      CALL lim_thd_init                ! namelist read ice thermodynics parameters
55      !
56      CALL lim_thd_sal_init            ! namelist read ice salinity parameters
57      !
58      rdt_ice = nn_fsbc * rdttra(1)    ! sea-ice timestep
59      !
60      CALL lim_msh                     ! ice mesh initialization
61      !
62      CALL lim_itd_ini                 ! initialize the ice thickness distribution
63
64      !                                ! Initial sea-ice state
65      IF( .NOT.ln_rstart ) THEN              ! start from rest
66         numit = 0
67         numit = nit000 - 1
68         CALL lim_istate                        ! start from rest: sea-ice deduced from sst
69         CALL lim_var_agg(1)                    ! aggregate category variables in bulk variables
70         CALL lim_var_glo2eqv                   ! convert global variables in equivalent variables
71      ELSE                                   ! start from a restart file
72         CALL lim_rst_read                      ! read the restart file
73         numit = nit000 - 1
74         CALL lim_var_agg(1)                    ! aggregate ice variables
75         CALL lim_var_glo2eqv                   ! convert global var in equivalent variables
76      ENDIF
77      !
78      fr_i(:,:) = at_i(:,:)           ! initialisation of sea-ice fraction
79      !
80      nstart = numit  + nn_fsbc     
81      nitrun = nitend - nit000 + 1 
82      nlast  = numit  + nitrun 
83      !
84      IF( nstock == 0  )   nstock = nlast + 1
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/ cn_icerst_in, cn_icerst_out, ln_limdyn, acrit, hsndif, hicdif, cai, cao, ln_nicep
101      !!-------------------------------------------------------------------
102      !                   
103      REWIND( numnam_ice )                ! Read Namelist namicerun
104      READ  ( numnam_ice , namicerun )
105      !
106      IF( lk_mpp .AND. ln_nicep ) THEN
107         ln_nicep = .FALSE.
108         CALL ctl_warn( 'ice_run : specific control print for LIM3 desactivated with MPI' )
109      ENDIF       
110      !
111      IF(lwp) THEN                        ! control print
112         WRITE(numout,*)
113         WRITE(numout,*) 'ice_run : ice share parameters for dynamics/advection/thermo of sea-ice'
114         WRITE(numout,*) ' ~~~~~~'
115         WRITE(numout,*) '   switch for ice dynamics (1) or not (0)      ln_limdyn   = ', ln_limdyn
116         WRITE(numout,*) '   minimum fraction for leads in the NH (SH)  acrit(1/2)   = ', acrit(:)
117         WRITE(numout,*) '   computation of temp. in snow (=0) or not (=9999) hsndif = ', hsndif
118         WRITE(numout,*) '   computation of temp. in ice  (=0) or not (=9999) hicdif = ', hicdif
119         WRITE(numout,*) '   atmospheric drag over sea ice                           = ', cai
120         WRITE(numout,*) '   atmospheric drag over ocean                             = ', cao
121         WRITE(numout,*) '   Several ice points in the ice or not in ocean.output    = ', ln_nicep
122      ENDIF
123      !
124   END SUBROUTINE ice_run
125
126
127   SUBROUTINE lim_itd_ini
128      !!------------------------------------------------------------------
129      !!                ***  ROUTINE lim_itd_ini ***
130      !!
131      !! ** Purpose :   Initializes the ice thickness distribution
132      !! ** Method  :   ...
133      !!------------------------------------------------------------------
134      INTEGER  ::   jl, jm               ! dummy loop index
135      REAL(wp) ::   zc1, zc2, zc3, zx1   ! local scalars
136      !!------------------------------------------------------------------
137
138      IF(lwp) WRITE(numout,*)
139      IF(lwp) WRITE(numout,*) 'lim_itd_ini : Initialization of ice thickness distribution '
140      IF(lwp) WRITE(numout,*) '~~~~~~~~~~~~'
141
142      !------------------------------------------------------------------------------!
143      ! 1) Ice thickness distribution parameters initialization   
144      !------------------------------------------------------------------------------!
145
146      !- Types boundaries (integer)
147      !----------------------------
148      ice_cat_bounds(1,1) = 1
149      ice_cat_bounds(1,2) = jpl
150
151      !- Number of ice thickness categories in each ice type
152      DO jm = 1, jpm
153         ice_ncat_types(jm) = ice_cat_bounds(jm,2) - ice_cat_bounds(jm,1) + 1 
154      END DO
155
156      !- Make the correspondence between thickness categories and ice types
157      !---------------------------------------------------------------------
158      DO jm = 1, jpm       !over types
159         DO jl = ice_cat_bounds(jm,1), ice_cat_bounds(jm,2) !over thickness categories
160            ice_types(jl) = jm
161         END DO
162      END DO
163
164      IF(lwp) THEN 
165         WRITE(numout,*) ' Number of ice types jpm =      ', jpm
166         WRITE(numout,*) ' Number of ice categories jpl = ', jpl
167         DO jm = 1, jpm
168            WRITE(numout,*) ' Ice type ', jm
169            WRITE(numout,*) ' Number of thickness categories ', ice_ncat_types(jm)
170            WRITE(numout,*) ' Thickness category boundaries  ', ice_cat_bounds(jm,1:2)
171         END DO
172         WRITE(numout,*) 'Ice type vector', ice_types(1:jpl)
173         WRITE(numout,*)
174      ENDIF
175
176      !- Thickness categories boundaries
177      !----------------------------------
178      hi_max(:) = 0._wp
179      hi_max_typ(:,:) = 0._wp
180
181      !- Type 1 - undeformed ice
182      zc1 =  3._wp / REAL( ice_cat_bounds(1,2) - ice_cat_bounds(1,1) + 1 , wp )
183      zc2 = 10._wp * zc1
184      zc3 =  3._wp
185
186      DO jl = ice_cat_bounds(1,1), ice_cat_bounds(1,2)
187         zx1 = REAL( jl-1 , wp ) / REAL( ice_cat_bounds(1,2) - ice_cat_bounds(1,1) + 1 , wp )
188         hi_max(jl) = hi_max(jl-1) + zc1 + zc2 * (1._wp + TANH( zc3 * (zx1 - 1._wp ) ) )
189      END DO
190
191      !- Fill in the hi_max_typ vector, useful in other circumstances
192      ! Tricky trick: hi_max_typ is actually not used in the code and will be removed in a
193      ! next flyspray at this time, the tricky trick will also be removed (Martin, march 08)
194      DO jl = ice_cat_bounds(1,1), ice_cat_bounds(1,2)
195         hi_max_typ(jl,1) = hi_max(jl)
196      END DO
197
198      IF(lwp) WRITE(numout,*) ' Thickness category boundaries independently of ice type '
199      IF(lwp) WRITE(numout,*) ' hi_max ', hi_max(0:jpl)
200
201      IF(lwp) WRITE(numout,*) ' Thickness category boundaries inside ice types '
202      IF(lwp) THEN
203         DO jm = 1, jpm
204            WRITE(numout,*) ' Type number ', jm
205            WRITE(numout,*) ' hi_max_typ : ', hi_max_typ(0:ice_ncat_types(jm),jm)
206         END DO
207      ENDIF
208      !
209      DO jl = 1, jpl
210         hi_mean(jl) = ( hi_max(jl) + hi_max(jl-1) ) * 0.5_wp
211      END DO
212      !
213      tn_ice(:,:,:) = t_su(:,:,:)
214      !
215   END SUBROUTINE lim_itd_ini
216
217#else
218   !!----------------------------------------------------------------------
219   !!   Default option :        Empty module           NO LIM sea-ice model
220   !!----------------------------------------------------------------------
221CONTAINS
222   SUBROUTINE ice_init        ! Empty routine
223   END SUBROUTINE ice_init
224#endif
225
226   !!======================================================================
227END MODULE iceini
Note: See TracBrowser for help on using the repository browser.