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/2013/dev_r3853_CNRS9_ConfSetting/NEMOGCM/NEMO/LIM_SRC_2 – NEMO

source: branches/2013/dev_r3853_CNRS9_ConfSetting/NEMOGCM/NEMO/LIM_SRC_2/limistate_2.F90 @ 3901

Last change on this file since 3901 was 3901, checked in by clevy, 11 years ago

Configuration Setting/Step2, see ticket:#1074

  • Property svn:keywords set to Id
File size: 10.4 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 par_ice_2       ! ice parameters
22   USE dom_ice_2
23   USE eosbn2          ! equation of state
24   USE lbclnk
25   USE oce
26   USE ice_2
27   USE iom
28   USE in_out_manager
29   USE lib_fortran     ! Fortran utilities (allows no signed zero when 'key_nosignedzero' defined) 
30
31   IMPLICIT NONE
32   PRIVATE
33
34   PUBLIC lim_istate_2      ! routine called by lim_init_2.F90
35
36   !!! **  namelist (namiceini) **
37   LOGICAL  ::   ln_limini   !: Ice initialization state
38   REAL(wp) ::   ttest       ! threshold water temperature for initial sea ice
39   REAL(wp) ::   hninn       ! initial snow thickness in the north
40   REAL(wp) ::   hginn       ! initial ice thickness in the north
41   REAL(wp) ::   alinn       ! initial leads area in the north
42   REAL(wp) ::   hnins       ! initial snow thickness in the south
43   REAL(wp) ::   hgins       ! initial ice thickness in the south
44   REAL(wp) ::   alins       ! initial leads area in the south
45   
46   REAL(wp) ::   zero      = 0.e0     ! constant value = 0
47   REAL(wp) ::   zone      = 1.e0     ! constant value = 1
48   !!----------------------------------------------------------------------
49   !! NEMO/LIM2 3.3 , UCL - NEMO Consortium (2010)
50   !! $Id$
51   !! Software governed by the CeCILL licence (NEMOGCM/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                     ! temporary scalar
67      !--------------------------------------------------------------------
68 
69      CALL lim_istate_init_2     !  reading the initials parameters of the ice
70
71      IF( .NOT. ln_limini ) THEN 
72         
73         tfu(:,:) = tfreez( tsn(:,:,1,jp_sal) ) * tmask(:,:,1)       ! freezing/melting point of sea water [Celcius]
74
75         DO jj = 1, jpj
76            DO ji = 1, jpi
77               !                     ! ice if sst <= t-freez + ttest
78               IF( tsn(ji,jj,1,jp_tem)  - tfu(ji,jj) >= ttest ) THEN   ;   zidto = 0.e0      ! no ice
79               ELSE                                                    ;   zidto = 1.e0      !    ice
80               ENDIF
81               !
82               IF( fcor(ji,jj) >= 0.e0 ) THEN     !--  Northern hemisphere.
83                  hicif(ji,jj)   = zidto * hginn
84                  frld(ji,jj)    = zidto * alinn + ( 1.0 - zidto ) * 1.0
85                  hsnif(ji,jj)   = zidto * hninn
86               ELSE                               !---  Southern hemisphere.
87                  hicif(ji,jj)   = zidto * hgins
88                  frld(ji,jj)    = zidto * alins + ( 1.0 - zidto ) * 1.0
89                  hsnif(ji,jj)   = zidto * hnins
90               ENDIF
91            END DO
92         END DO
93
94         tfu(:,:) = tfu(:,:) + rt0       ! ftu converted from Celsius to Kelvin (rt0 over land)
95         
96         sist  (:,:)   = tfu(:,:)
97         tbif  (:,:,1) = tfu(:,:)
98         tbif  (:,:,2) = tfu(:,:)
99         tbif  (:,:,3) = tfu(:,:)
100
101      ENDIF
102     
103      fsbbq (:,:)   = 0.e0
104      qstoif(:,:)   = 0.e0
105      u_ice (:,:)   = 0.e0
106      v_ice (:,:)   = 0.e0
107
108      !---  Moments for advection.             
109
110      sxice (:,:)  = 0.e0   ;   sxsn (:,:)  = 0.e0   ;   sxa  (:,:)  = 0.e0
111      syice (:,:)  = 0.e0   ;   sysn (:,:)  = 0.e0   ;   sya  (:,:)  = 0.e0
112      sxxice(:,:)  = 0.e0   ;   sxxsn(:,:)  = 0.e0   ;   sxxa (:,:)  = 0.e0
113      syyice(:,:)  = 0.e0   ;   syysn(:,:)  = 0.e0   ;   syya (:,:)  = 0.e0
114      sxyice(:,:)  = 0.e0   ;   sxysn(:,:)  = 0.e0   ;   sxya (:,:)  = 0.e0
115
116      sxc0  (:,:)  = 0.e0   ;   sxc1 (:,:)  = 0.e0   ;   sxc2 (:,:)  = 0.e0
117      syc0  (:,:)  = 0.e0   ;   syc1 (:,:)  = 0.e0   ;   syc2 (:,:)  = 0.e0
118      sxxc0 (:,:)  = 0.e0   ;   sxxc1(:,:)  = 0.e0   ;   sxxc2(:,:)  = 0.e0
119      syyc0 (:,:)  = 0.e0   ;   syyc1(:,:)  = 0.e0   ;   syyc2(:,:)  = 0.e0
120      sxyc0 (:,:)  = 0.e0   ;   sxyc1(:,:)  = 0.e0   ;   sxyc2(:,:)  = 0.e0
121
122      sxst  (:,:)  = 0.e0
123      syst  (:,:)  = 0.e0
124      sxxst (:,:)  = 0.e0
125      syyst (:,:)  = 0.e0
126      sxyst (:,:)  = 0.e0
127#if ! defined key_lim2_vp
128      stress1_i (:,:) = 0._wp                          ! EVP rheology
129      stress2_i (:,:) = 0._wp
130      stress12_i(:,:) = 0._wp
131#endif
132
133      !-- lateral boundary conditions
134      CALL lbc_lnk( hicif, 'T', 1. )
135      CALL lbc_lnk( frld , 'T', 1. )
136
137      ! C A U T I O N  frld = 1 over land and lbc_lnk put zero along
138      ! *************  closed boundaries herefore we force to one over land
139      frld(:,:) = tms(:,:) * frld(:,:) + ( 1. - tms(:,:) )   
140
141      CALL lbc_lnk( hsnif, 'T', 1. )
142      CALL lbc_lnk( sist , 'T', 1. , pval = rt0 )      ! set rt0 on closed boundary (required by bulk formulation)
143      DO jk = 1, jplayersp1
144         CALL lbc_lnk(tbif(:,:,jk), 'T', 1. )
145      END DO
146      CALL lbc_lnk( fsbbq  , 'T', 1. )
147      CALL lbc_lnk( qstoif , 'T', 1. )
148
149   END SUBROUTINE lim_istate_2
150
151   
152   SUBROUTINE lim_istate_init_2
153      !!-------------------------------------------------------------------
154      !!                   ***  ROUTINE lim_istate_init_2  ***
155      !!       
156      !! ** Purpose :   Definition of initial state of the ice
157      !!
158      !! ** Method  :   Read the namiceini namelist and check the parameter
159      !!       values called at the first timestep (nit000)
160      !!
161      !! ** input   :   Namelist namiceini
162      !!-------------------------------------------------------------------
163      INTEGER :: inum_ice
164      INTEGER :: ji,jj
165      INTEGER :: ios                 ! Local integer output status for namelist read
166
167      NAMELIST/namiceini/ ln_limini, ttest, hninn, hginn, alinn, &
168         &                hnins, hgins, alins
169      !!-------------------------------------------------------------------
170                   
171      REWIND( numnam_ice_ref )              ! Namelist namiceini in reference namelist : Ice initial state
172      READ  ( numnam_ice_ref, namiceini, IOSTAT = ios, ERR = 901)
173901   IF( ios /= 0 ) CALL ctl_nam ( ios , 'namiceini in reference namelist', lwp )
174
175      REWIND( numnam_ice_cfg )              ! Namelist namiceini in configuration namelist : Ice initial state
176      READ  ( numnam_ice_cfg, namiceini, IOSTAT = ios, ERR = 902 )
177902   IF( ios /= 0 ) CALL ctl_nam ( ios , 'namiceini in configuration namelist', lwp )
178      WRITE ( numoni, namiceini )
179      !
180      IF(lwp) THEN
181         WRITE(numout,*)
182         WRITE(numout,*) 'lim_istate_init_2 : ice parameters inititialisation '
183         WRITE(numout,*) '~~~~~~~~~~~~~~~~~'
184         WRITE(numout,*) '         threshold water temp. for initial sea-ice    ttest      = ', ttest
185         WRITE(numout,*) '         initial snow thickness in the north          hninn      = ', hninn
186         WRITE(numout,*) '         initial ice thickness in the north           hginn      = ', hginn 
187         WRITE(numout,*) '         initial leads area in the north              alinn      = ', alinn           
188         WRITE(numout,*) '         initial snow thickness in the south          hnins      = ', hnins 
189         WRITE(numout,*) '         initial ice thickness in the south           hgins      = ', hgins
190         WRITE(numout,*) '         initial leads area in the south              alins      = ', alins
191         WRITE(numout,*) '         Ice state initialization using input file    ln_limini  = ', ln_limini
192      ENDIF
193
194      IF( ln_limini ) THEN                      ! Ice initialization using input file
195         !
196         CALL iom_open( 'Ice_initialization.nc', inum_ice )
197         !
198         IF( inum_ice > 0 ) THEN
199            IF(lwp) WRITE(numout,*)
200            IF(lwp) WRITE(numout,*) '                  ice state initialization with : Ice_initialization.nc'
201           
202            CALL iom_get( inum_ice, jpdom_data, 'hicif', hicif )     
203            CALL iom_get( inum_ice, jpdom_data, 'hsnif', hsnif )     
204            CALL iom_get( inum_ice, jpdom_data, 'frld' , frld  )     
205            CALL iom_get( inum_ice, jpdom_data, 'ts'   , sist  )
206            CALL iom_get( inum_ice, jpdom_unknown, 'tbif', tbif(1:nlci,1:nlcj,:),   &
207                 &        kstart = (/ mig(1),mjg(1),1 /), kcount = (/ nlci,nlcj,jplayersp1 /) )
208            ! put some values in the extra-halo...
209            DO jj = nlcj+1, jpj   ;   tbif(1:nlci,jj,:) = tbif(1:nlci,nlej,:)   ;   END DO
210            DO ji = nlci+1, jpi   ;   tbif(ji    ,: ,:) = tbif(nlei  ,:   ,:)   ;   END DO
211
212            CALL iom_close( inum_ice)
213            !
214         ENDIF
215      ENDIF
216      !     
217   END SUBROUTINE lim_istate_init_2
218
219#else
220   !!----------------------------------------------------------------------
221   !!   Default option :         Empty module      NO LIM 2.0 sea-ice model
222   !!----------------------------------------------------------------------
223CONTAINS
224   SUBROUTINE lim_istate_2        ! Empty routine
225   END SUBROUTINE lim_istate_2
226#endif
227
228   !!======================================================================
229END MODULE limistate_2
Note: See TracBrowser for help on using the repository browser.