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

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