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_002_LIM/NEMO/LIM_SRC_2 – NEMO

source: branches/dev_002_LIM/NEMO/LIM_SRC_2/limistate_2.F90 @ 833

Last change on this file since 833 was 823, checked in by rblod, 16 years ago

Final step to rename LIM_SRC in LIM_SRC_2

  • Property svn:eol-style set to native
  • Property svn:keywords set to Author Date Id Revision
File size: 12.5 KB
RevLine 
[821]1MODULE limistate_2
[3]2   !!======================================================================
[821]3   !!                     ***  MODULE  limistate_2  ***
[3]4   !!              Initialisation of diagnostics ice variables
5   !!======================================================================
[719]6   !! History :   2.0  !  01-04  (C. Ethe, G. Madec)  Original code
[508]7   !!                  !  04-04  (S. Theetten) initialization from a file
8   !!                  !  06-07  (S. Masson)  IOM to read the restart
9   !!--------------------------------------------------------------------
[821]10#if defined key_lim2
[3]11   !!----------------------------------------------------------------------
[821]12   !!   'key_lim2' :                                  LIM 2.0 sea-ice model
[3]13   !!----------------------------------------------------------------------
[508]14   !!----------------------------------------------------------------------
[821]15   !!   lim_istate_2      :  Initialisation of diagnostics ice variables
16   !!   lim_istate_init_2 :  initialization of ice state and namelist read
[3]17   !!----------------------------------------------------------------------
18   USE phycst
19   USE ocfzpt
[719]20   USE oce             ! dynamics and tracers variables      !!gm used???
21   USE dom_oce                                                     !!gm used???
[821]22   USE par_ice_2       ! ice parameters
[3]23   USE ice_oce         ! ice variables
[821]24   USE dom_ice_2
[508]25   USE lbclnk
[821]26   USE ice_2
[508]27   USE iom
28   USE in_out_manager
[3]29
30   IMPLICIT NONE
31   PRIVATE
32
[821]33   PUBLIC lim_istate_2      ! routine called by lim_init_2.F90
[3]34
[719]35   REAL(wp) ::           &  !!! ** init namelist (namiceini) **
[3]36      ttest  = 2.0  ,    &  ! threshold water temperature for initial sea ice
37      hninn  = 0.5  ,    &  ! initial snow thickness in the north
38      hginn  = 3.0  ,    &  ! initial ice thickness in the north
39      alinn  = 0.05 ,    &  ! initial leads area in the north
40      hnins  = 0.1  ,    &  ! initial snow thickness in the south
41      hgins  = 1.0  ,    &  ! initial ice thickness in the south
42      alins  = 0.1          ! initial leads area in the south
43
[77]44   REAL(wp)  ::          &  ! constant values
45      zzero   = 0.e0  ,  &
46      zone    = 1.e0
[3]47   !!----------------------------------------------------------------------
[508]48   !!   LIM 2.0,  UCL-LOCEAN-IPSL (2006)
[719]49   !! $Header$
[508]50   !! Software governed by the CeCILL licence (modipsl/doc/NEMO_CeCILL.txt)
[3]51   !!----------------------------------------------------------------------
52
53CONTAINS
54
[821]55   SUBROUTINE lim_istate_2
[3]56      !!-------------------------------------------------------------------
[821]57      !!                    ***  ROUTINE lim_istate_2  ***
[3]58      !!
[77]59      !! ** Purpose :   defined the sea-ice initial state
60      !!
61      !! ** Method  :   restart from a state defined in a binary file
62      !!                or from arbitrary sea-ice conditions
[3]63      !!--------------------------------------------------------------------
[508]64      INTEGER  ::   ji, jj, jk                ! dummy loop indices
65      REAL(wp) ::   zidto, zs0, ztf, zbin     ! temporary scalar
66      REAL(wp), DIMENSION(jpi,jpj) ::   ztn   ! workspace
[3]67      !--------------------------------------------------------------------
68
[821]69       CALL lim_istate_init_2   !  reading the initials parameters of the ice
[719]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      IF( ln_limini ) THEN    !
76       
77         ! Initialisation at tn if no ice or sst_ini if ice
78         ! Idem for salinity
79
80      !--- Criterion for presence (zidto=1.) or absence (zidto=0.) of ice
81         DO jj = 1 , jpj
82            DO ji = 1 , jpi
83               
84               zidto = MAX(zzero, - SIGN(1.,frld(ji,jj) - 1.))
85               
86               sst_io(ji,jj) = ( nfice - 1 ) * (zidto * sst_ini(ji,jj)  + &   ! use the ocean initial values
87                    &          (1.0 - zidto ) * ( tn(ji,jj,1) + rt0 ))        ! tricky trick *(nfice-1) !
88               sss_io(ji,jj) = ( nfice - 1 ) * (zidto * sss_ini(ji,jj) + &
89                    &          (1.0 - zidto ) *  sn(ji,jj,1) )
90
91               ! to avoid the the melting of ice, several layers (mixed layer) should be
92               ! set to sst_ini (sss_ini) if there is ice
93               ! example for one layer
94               ! tn(ji,jj,1) = zidto * ( sst_ini(ji,jj) - rt0 )  + (1.0 - zidto ) *  tn(ji,jj,1)
95               ! sn(ji,jj,1) = zidto * sss_ini(ji,jj)  + (1.0 - zidto ) *  sn(ji,jj,1)
96               ! tb(ji,jj,1) = tn(ji,jj,1)
97               ! sb(ji,jj,1) = sn(ji,jj,1)
98            END DO
99         END DO
[419]100         
[719]101         
102         !  tfu: Melting point of sea water
103         tfu(:,:)  = ztf   
104         
105         tfu(:,:)  = ABS ( rt0 - 0.0575       * sss_ini(:,:)                               &
106              &                    + 1.710523e-03 * sss_ini(:,:) * SQRT( sss_ini(:,:) )    &
107              &                    - 2.154996e-04 * sss_ini(:,:) * sss_ini(:,:) )
108      ELSE                     !
109
110         
[419]111         ! Initialisation at tn or -2 if ice
112         DO jj = 1, jpj
113            DO ji = 1, jpi
114               zbin = MAX( 0., SIGN( 1., fzptn(ji,jj) - tn(ji,jj,1) ) )
115               ztn(ji,jj) = ( (1.-zbin) * tn(ji,jj,1) - 2. * zbin + rt0 ) * tmask(ji,jj,1)
116            END DO
[77]117         END DO
[719]118         
119         u_io  (:,:) = 0.e0
120         v_io  (:,:) = 0.e0
121         sst_io(:,:) = ( nfice - 1 ) * ( tn(:,:,1) + rt0 )   ! use the ocean initial values
122         sss_io(:,:) = ( nfice - 1 ) *   sn(:,:,1)           ! tricky trick *(nfice-1) !
123         
124         ! reference salinity 34psu
[419]125         zs0 = 34.e0
[719]126         ztf = ABS ( rt0 - 0.0575       * zs0                           &
127              &                    + 1.710523e-03 * zs0 * SQRT( zs0 )   &
128              &                    - 2.154996e-04 * zs0 *zs0          )
[419]129         
[719]130         !  tfu: Melting point of sea water
131         tfu(:,:)  = ztf   
132         
[419]133         DO jj = 1, jpj
134            DO ji = 1, jpi
135               !--- Criterion for presence (zidto=1) or absence (zidto=0) of ice
136               zidto  = tms(ji,jj) * ( 1.0 - MAX(zzero, SIGN( zone, ztn(ji,jj) - tfu(ji,jj) - ttest) ) )
137               
138               IF( fcor(ji,jj) >= 0.e0 ) THEN     !--  Northern hemisphere.
139                  hicif(ji,jj)   = zidto * hginn
140                  frld(ji,jj)    = zidto * alinn + ( 1.0 - zidto ) * 1.0
141                  hsnif(ji,jj)   = zidto * hninn
142               ELSE                               !---  Southern hemisphere.
143                  hicif(ji,jj)   = zidto * hgins
144                  frld(ji,jj)    = zidto * alins + ( 1.0 - zidto ) * 1.0
145                  hsnif(ji,jj)   = zidto * hnins
146               ENDIF
147            END DO
148         END DO
149         
150         sist  (:,:)   = tfu(:,:)
151         tbif  (:,:,1) = tfu(:,:)
152         tbif  (:,:,2) = tfu(:,:)
153         tbif  (:,:,3) = tfu(:,:)
[719]154     
[419]155      ENDIF
[3]156      fsbbq (:,:)   = 0.e0
157      qstoif(:,:)   = 0.e0
[719]158      u_ice (:,:)   = 0.e0
159      v_ice (:,:)   = 0.e0
[3]160# if defined key_coupled
161      albege(:,:)   = 0.8 * tms(:,:)
162# endif
163
[77]164      !---  Moments for advection.             
[3]165
[77]166      sxice (:,:)  = 0.e0   ;   sxsn (:,:)  = 0.e0   ;   sxa  (:,:)  = 0.e0
167      syice (:,:)  = 0.e0   ;   sysn (:,:)  = 0.e0   ;   sya  (:,:)  = 0.e0
168      sxxice(:,:)  = 0.e0   ;   sxxsn(:,:)  = 0.e0   ;   sxxa (:,:)  = 0.e0
169      syyice(:,:)  = 0.e0   ;   syysn(:,:)  = 0.e0   ;   syya (:,:)  = 0.e0
170      sxyice(:,:)  = 0.e0   ;   sxysn(:,:)  = 0.e0   ;   sxya (:,:)  = 0.e0
[3]171
[77]172      sxc0  (:,:)  = 0.e0   ;   sxc1 (:,:)  = 0.e0   ;   sxc2 (:,:)  = 0.e0
173      syc0  (:,:)  = 0.e0   ;   syc1 (:,:)  = 0.e0   ;   syc2 (:,:)  = 0.e0
174      sxxc0 (:,:)  = 0.e0   ;   sxxc1(:,:)  = 0.e0   ;   sxxc2(:,:)  = 0.e0
175      syyc0 (:,:)  = 0.e0   ;   syyc1(:,:)  = 0.e0   ;   syyc2(:,:)  = 0.e0
176      sxyc0 (:,:)  = 0.e0   ;   sxyc1(:,:)  = 0.e0   ;   sxyc2(:,:)  = 0.e0
[3]177
[77]178      sxst  (:,:)  = 0.e0
179      syst  (:,:)  = 0.e0
180      sxxst (:,:)  = 0.e0
181      syyst (:,:)  = 0.e0
182      sxyst (:,:)  = 0.e0
[3]183
[77]184      !-- lateral boundary conditions
185      CALL lbc_lnk( hicif, 'T', 1. )
186      CALL lbc_lnk( frld , 'T', 1. )
[299]187
188      ! C A U T I O N  frld = 1 over land and lbc_lnk put zero along
189      ! *************  closed boundaries herefore we force to one over land
190      frld(:,:) = tms(:,:) * frld(:,:) + ( 1. - tms(:,:) )   
191
[77]192      CALL lbc_lnk( hsnif, 'T', 1. )
[719]193      CALL lbc_lnk( sist , 'T', 1. )
[77]194      DO jk = 1, jplayersp1
195         CALL lbc_lnk(tbif(:,:,jk), 'T', 1. )
196      END DO
197      CALL lbc_lnk( fsbbq  , 'T', 1. )
198      CALL lbc_lnk( qstoif , 'T', 1. )
[719]199      CALL lbc_lnk( sss_io , 'T', 1. )
200      !
[821]201   END SUBROUTINE lim_istate_2
[3]202
203   
[821]204   SUBROUTINE lim_istate_init_2
[3]205      !!-------------------------------------------------------------------
[821]206      !!                   ***  ROUTINE lim_istate_init_2  ***
[3]207      !!       
[77]208      !! ** Purpose :   Definition of initial state of the ice
[3]209      !!
[77]210      !! ** Method  :   Read the namiceini namelist and check the parameter
[719]211      !!                values called at the first timestep (nit000)
212      !!                or
213      !!                Read 7 variables from a previous restart file
214      !!                sst, sst, hicif, hsnif, frld, ts & tbif
[3]215      !!
[77]216      !! ** input   :   Namelist namiceini
[3]217      !!-------------------------------------------------------------------
[508]218      INTEGER :: inum_ice
[673]219      INTEGER :: ji,jj
[419]220
[675]221      NAMELIST/namiceini/ ln_limini, ttest, hninn, hginn, alinn, &
[419]222         &                hnins, hgins, alins
[3]223      !!-------------------------------------------------------------------
[719]224     
225      ! Read Namelist namiceini
226      REWIND ( numnam_ice )
[3]227      READ   ( numnam_ice , namiceini )
[719]228     
229      IF(.NOT. ln_limini) THEN
230         IF(lwp) THEN
231            WRITE(numout,*)
232            WRITE(numout,*) 'lim_istate_init : ice parameters inititialisation '
233            WRITE(numout,*) '~~~~~~~~~~~~~~~'
234            WRITE(numout,*) '         threshold water temp. for initial sea-ice    ttest      = ', ttest
235            WRITE(numout,*) '         initial snow thickness in the north          hninn      = ', hninn
236            WRITE(numout,*) '         initial ice thickness in the north           hginn      = ', hginn 
237            WRITE(numout,*) '         initial leads area in the north              alinn      = ', alinn           
238            WRITE(numout,*) '         initial snow thickness in the south          hnins      = ', hnins 
239            WRITE(numout,*) '         initial ice thickness in the south           hgins      = ', hgins
240            WRITE(numout,*) '         initial leads area in the south              alins      = ', alins
241         ENDIF
[3]242      ENDIF
[419]243
244      IF( ln_limini ) THEN                      ! Ice initialization using input file
[719]245
[508]246         CALL iom_open( 'Ice_initialization.nc', inum_ice )
[719]247
[508]248         IF( inum_ice > 0 ) THEN
[719]249            IF(lwp) THEN
250               WRITE(numout,*) ' '
251               WRITE(numout,*) 'lim_istate_init : ice state initialization with : Ice_initialization.nc'
252               WRITE(numout,*) '~~~~~~~~~~~~~~~'
253               WRITE(numout,*) '         Ice state initialization using input file    ln_limini  = ', ln_limini
254               WRITE(numout,*) ' '
255            ENDIF
[3]256           
[719]257            CALL iom_get( inum_ice, jpdom_data, 'sst'  , sst_ini(:,:) )       
258            CALL iom_get( inum_ice, jpdom_data, 'sss'  , sss_ini(:,:) )       
259            CALL iom_get( inum_ice, jpdom_data, 'hicif', hicif  (:,:) )     
260            CALL iom_get( inum_ice, jpdom_data, 'hsnif', hsnif  (:,:) )     
261            CALL iom_get( inum_ice, jpdom_data, 'frld' , frld   (:,:) )     
262            CALL iom_get( inum_ice, jpdom_data, 'ts'   , sist   (:,:) )
[673]263            CALL iom_get( inum_ice, jpdom_unknown, 'tbif', tbif(1:nlci,1:nlcj,:),   &
[508]264                 &        kstart = (/ mig(1),mjg(1),1 /), kcount = (/ nlci,nlcj,jplayersp1 /) )
[673]265            ! put some values in the extra-halo...
266            DO jj = nlcj+1, jpj   ;   tbif(1:nlci,jj,:) = tbif(1:nlci,nlej,:)   ;   END DO
267            DO ji = nlci+1, jpi   ;   tbif(ji    ,: ,:) = tbif(nlei  ,:   ,:)   ;   END DO
[508]268
269            CALL iom_close( inum_ice)
[719]270           
[419]271         ENDIF
272      ENDIF
[719]273      !
[821]274   END SUBROUTINE lim_istate_init_2
[3]275
276#else
277   !!----------------------------------------------------------------------
[821]278   !!   Default option :         Empty module      NO LIM 2.0 sea-ice model
[3]279   !!----------------------------------------------------------------------
280CONTAINS
[821]281   SUBROUTINE lim_istate_2        ! Empty routine
282   END SUBROUTINE lim_istate_2
[3]283#endif
284
285   !!======================================================================
[821]286END MODULE limistate_2
Note: See TracBrowser for help on using the repository browser.