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

source: branches/DEV_r1837_mass_heat_salt_fluxes/NEMO/LIM_SRC_2/limistate_2.F90 @ 1855

Last change on this file since 1855 was 1855, checked in by gm, 14 years ago

ticket:#665 style change only, with the suppression of thd_ice_2 (merged in ice_2)

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