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 tags/start/NEMO/LIM_SRC – NEMO

source: tags/start/NEMO/LIM_SRC/iceini.F90 @ 3489

Last change on this file since 3489 was 3, checked in by opalod, 20 years ago

Initial revision

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