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.
limistate_2.F90 in branches/dev_003_CPL/NEMO/LIM_SRC_2 – NEMO

source: branches/dev_003_CPL/NEMO/LIM_SRC_2/limistate_2.F90 @ 991

Last change on this file since 991 was 991, checked in by smasson, 16 years ago

dev_003_CPL: preliminary draft (not working), see ticket #155

  • Property svn:eol-style set to native
  • Property svn:keywords set to Author Date Id Revision
File size: 9.8 KB
Line 
1MODULE limistate_2
2   !!======================================================================
3   !!                     ***  MODULE  limistate_2  ***
4   !!              Initialisation of diagnostics ice variables
5   !!======================================================================
6   !! History :   1.0  !  01-04  (C. Ethe, G. Madec)  Original code
7   !!             2.0  !  03-08  (G. Madec)  add lim_istate_init
8   !!                  !  04-04  (S. Theetten) initialization from a file
9   !!                  !  06-07  (S. Masson)  IOM to read the restart
10   !!                  !  07-10  (G. Madec)  surface module
11   !!--------------------------------------------------------------------
12#if defined key_lim2
13   !!----------------------------------------------------------------------
14   !!   'key_lim2' :                                  LIM 2.0 sea-ice model
15   !!----------------------------------------------------------------------
16   !!----------------------------------------------------------------------
17   !!   lim_istate_2      :  Initialisation of diagnostics ice variables
18   !!   lim_istate_init_2 :  initialization of ice state and namelist read
19   !!----------------------------------------------------------------------
20   USE phycst
21   USE ocfzpt
22   USE par_ice_2       ! ice parameters
23   USE ice_oce         ! ice variables
24   USE dom_ice_2
25   USE lbclnk
26   USE oce
27   USE ice_2
28   USE iom
29   USE in_out_manager
30
31   IMPLICIT NONE
32   PRIVATE
33
34   PUBLIC lim_istate_2      ! routine called by lim_init_2.F90
35
36   REAL(wp) ::           &  !!! ** init namelist (namiceini) **
37      ttest  = 2.0  ,    &  ! threshold water temperature for initial sea ice
38      hninn  = 0.5  ,    &  ! initial snow thickness in the north
39      hginn  = 3.0  ,    &  ! initial ice thickness in the north
40      alinn  = 0.05 ,    &  ! initial leads area in the north
41      hnins  = 0.1  ,    &  ! initial snow thickness in the south
42      hgins  = 1.0  ,    &  ! initial ice thickness in the south
43      alins  = 0.1          ! initial leads area in the south
44
45   REAL(wp)  ::          &  ! constant values
46      zzero   = 0.e0  ,  &
47      zone    = 1.e0
48   !!----------------------------------------------------------------------
49   !!   LIM 2.0,  UCL-LOCEAN-IPSL (2006)
50   !! $ Id: $
51   !! Software governed by the CeCILL licence (modipsl/doc/NEMO_CeCILL.txt)
52   !!----------------------------------------------------------------------
53
54CONTAINS
55
56   SUBROUTINE lim_istate_2
57      !!-------------------------------------------------------------------
58      !!                    ***  ROUTINE lim_istate_2  ***
59      !!
60      !! ** Purpose :   defined the sea-ice initial state
61      !!
62      !! ** Method  :   restart from a state defined in a binary file
63      !!                or from arbitrary sea-ice conditions
64      !!--------------------------------------------------------------------
65      INTEGER  ::   ji, jj, jk                ! dummy loop indices
66      REAL(wp) ::   zidto, zs0, ztf, zbin     ! temporary scalar
67      REAL(wp), DIMENSION(jpi,jpj) ::   ztn   ! workspace
68      !--------------------------------------------------------------------
69 
70      CALL lim_istate_init_2     !  reading the initials parameters of the ice
71
72      IF( .NOT. ln_limini ) THEN 
73         
74         ! Initialisation at tn or -2 if ice
75         DO jj = 1, jpj
76            DO ji = 1, jpi
77               zbin = MAX( 0., SIGN( 1., fzptn(ji,jj) - tn(ji,jj,1) ) )
78               ztn(ji,jj) = ( (1.-zbin) * tn(ji,jj,1) - 2. * zbin + rt0 ) * tmask(ji,jj,1)
79            END DO
80         END DO
81                 
82         !  tfu: Melting point of sea water [Kelvin]
83         zs0 = 34.e0
84         ztf = rt0 + ( - 0.0575 + 1.710523e-3 * SQRT( zs0 ) - 2.154996e-4 * zs0 ) * zs0
85         tfu(:,:) = ztf
86         
87         DO jj = 1, jpj
88            DO ji = 1, jpi
89               !--- Criterion for presence (zidto=1) or absence (zidto=0) of ice
90               zidto  = tms(ji,jj) * ( 1.0 - MAX(zzero, SIGN( zone, ztn(ji,jj) - tfu(ji,jj) - ttest) ) )
91               
92               IF( fcor(ji,jj) >= 0.e0 ) THEN     !--  Northern hemisphere.
93                  hicif(ji,jj)   = zidto * hginn
94                  frld(ji,jj)    = zidto * alinn + ( 1.0 - zidto ) * 1.0
95                  hsnif(ji,jj)   = zidto * hninn
96               ELSE                               !---  Southern hemisphere.
97                  hicif(ji,jj)   = zidto * hgins
98                  frld(ji,jj)    = zidto * alins + ( 1.0 - zidto ) * 1.0
99                  hsnif(ji,jj)   = zidto * hnins
100               ENDIF
101            END DO
102         END DO
103         
104         sist  (:,:)   = tfu(:,:)
105         tbif  (:,:,1) = tfu(:,:)
106         tbif  (:,:,2) = tfu(:,:)
107         tbif  (:,:,3) = tfu(:,:)
108
109      ENDIF
110     
111      fsbbq (:,:)   = 0.e0
112      qstoif(:,:)   = 0.e0
113      ui_ice(:,:)   = 0.e0
114      vi_ice(:,:)   = 0.e0
115
116      !---  Moments for advection.             
117
118      sxice (:,:)  = 0.e0   ;   sxsn (:,:)  = 0.e0   ;   sxa  (:,:)  = 0.e0
119      syice (:,:)  = 0.e0   ;   sysn (:,:)  = 0.e0   ;   sya  (:,:)  = 0.e0
120      sxxice(:,:)  = 0.e0   ;   sxxsn(:,:)  = 0.e0   ;   sxxa (:,:)  = 0.e0
121      syyice(:,:)  = 0.e0   ;   syysn(:,:)  = 0.e0   ;   syya (:,:)  = 0.e0
122      sxyice(:,:)  = 0.e0   ;   sxysn(:,:)  = 0.e0   ;   sxya (:,:)  = 0.e0
123
124      sxc0  (:,:)  = 0.e0   ;   sxc1 (:,:)  = 0.e0   ;   sxc2 (:,:)  = 0.e0
125      syc0  (:,:)  = 0.e0   ;   syc1 (:,:)  = 0.e0   ;   syc2 (:,:)  = 0.e0
126      sxxc0 (:,:)  = 0.e0   ;   sxxc1(:,:)  = 0.e0   ;   sxxc2(:,:)  = 0.e0
127      syyc0 (:,:)  = 0.e0   ;   syyc1(:,:)  = 0.e0   ;   syyc2(:,:)  = 0.e0
128      sxyc0 (:,:)  = 0.e0   ;   sxyc1(:,:)  = 0.e0   ;   sxyc2(:,:)  = 0.e0
129
130      sxst  (:,:)  = 0.e0
131      syst  (:,:)  = 0.e0
132      sxxst (:,:)  = 0.e0
133      syyst (:,:)  = 0.e0
134      sxyst (:,:)  = 0.e0
135
136      !-- lateral boundary conditions
137      CALL lbc_lnk( hicif, 'T', 1. )
138      CALL lbc_lnk( frld , 'T', 1. )
139
140      ! C A U T I O N  frld = 1 over land and lbc_lnk put zero along
141      ! *************  closed boundaries herefore we force to one over land
142      frld(:,:) = tms(:,:) * frld(:,:) + ( 1. - tms(:,:) )   
143
144      CALL lbc_lnk( hsnif, 'T', 1. )
145      CALL lbc_lnk( sist , 'T', 1. , pval = rt0 )      ! set rt0 on closed boundary (required by bulk formulation)
146      DO jk = 1, jplayersp1
147         CALL lbc_lnk(tbif(:,:,jk), 'T', 1. )
148      END DO
149      CALL lbc_lnk( fsbbq  , 'T', 1. )
150      CALL lbc_lnk( qstoif , 'T', 1. )
151
152   END SUBROUTINE lim_istate_2
153
154   
155   SUBROUTINE lim_istate_init_2
156      !!-------------------------------------------------------------------
157      !!                   ***  ROUTINE lim_istate_init_2  ***
158      !!       
159      !! ** Purpose :   Definition of initial state of the ice
160      !!
161      !! ** Method  :   Read the namiceini namelist and check the parameter
162      !!       values called at the first timestep (nit000)
163      !!
164      !! ** input   :   Namelist namiceini
165      !!-------------------------------------------------------------------
166      INTEGER :: inum_ice
167      INTEGER :: ji,jj
168
169      NAMELIST/namiceini/ ln_limini, ttest, hninn, hginn, alinn, &
170         &                hnins, hgins, alins
171      !!-------------------------------------------------------------------
172      !
173      REWIND ( numnam_ice )               ! Read Namelist namiceini
174      READ   ( numnam_ice , namiceini )
175      !
176      IF(lwp) THEN
177         WRITE(numout,*)
178         WRITE(numout,*) 'lim_istate_init_2 : ice parameters inititialisation '
179         WRITE(numout,*) '~~~~~~~~~~~~~~~~~'
180         WRITE(numout,*) '         threshold water temp. for initial sea-ice    ttest      = ', ttest
181         WRITE(numout,*) '         initial snow thickness in the north          hninn      = ', hninn
182         WRITE(numout,*) '         initial ice thickness in the north           hginn      = ', hginn 
183         WRITE(numout,*) '         initial leads area in the north              alinn      = ', alinn           
184         WRITE(numout,*) '         initial snow thickness in the south          hnins      = ', hnins 
185         WRITE(numout,*) '         initial ice thickness in the south           hgins      = ', hgins
186         WRITE(numout,*) '         initial leads area in the south              alins      = ', alins
187         WRITE(numout,*) '         Ice state initialization using input file    ln_limini  = ', ln_limini
188      ENDIF
189
190      IF( ln_limini ) THEN                      ! Ice initialization using input file
191         !
192         CALL iom_open( 'Ice_initialization.nc', inum_ice )
193         !
194         IF( inum_ice > 0 ) THEN
195            IF(lwp) WRITE(numout,*)
196            IF(lwp) WRITE(numout,*) '                  ice state initialization with : Ice_initialization.nc'
197           
198            CALL iom_get( inum_ice, jpdom_data, 'hicif', hicif )     
199            CALL iom_get( inum_ice, jpdom_data, 'hsnif', hsnif )     
200            CALL iom_get( inum_ice, jpdom_data, 'frld' , frld  )     
201            CALL iom_get( inum_ice, jpdom_data, 'ts'   , sist  )
202            CALL iom_get( inum_ice, jpdom_unknown, 'tbif', tbif(1:nlci,1:nlcj,:),   &
203                 &        kstart = (/ mig(1),mjg(1),1 /), kcount = (/ nlci,nlcj,jplayersp1 /) )
204            ! put some values in the extra-halo...
205            DO jj = nlcj+1, jpj   ;   tbif(1:nlci,jj,:) = tbif(1:nlci,nlej,:)   ;   END DO
206            DO ji = nlci+1, jpi   ;   tbif(ji    ,: ,:) = tbif(nlei  ,:   ,:)   ;   END DO
207
208            CALL iom_close( inum_ice)
209            !
210         ENDIF
211      ENDIF
212      !     
213   END SUBROUTINE lim_istate_init_2
214
215#else
216   !!----------------------------------------------------------------------
217   !!   Default option :         Empty module      NO LIM 2.0 sea-ice model
218   !!----------------------------------------------------------------------
219CONTAINS
220   SUBROUTINE lim_istate_2        ! Empty routine
221   END SUBROUTINE lim_istate_2
222#endif
223
224   !!======================================================================
225END MODULE limistate_2
Note: See TracBrowser for help on using the repository browser.