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.F90 in trunk/NEMO/LIM_SRC – NEMO

source: trunk/NEMO/LIM_SRC/limistate.F90 @ 359

Last change on this file since 359 was 299, checked in by opalod, 19 years ago

nemo_v1_update_012 : CT : Add a comment to detail why the frld(:,:) array must be equal to 1 over T- land points

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