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.
limtrp_2.F90 in branches/dev_r2586_dynamic_mem/NEMOGCM/NEMO/LIM_SRC_2 – NEMO

source: branches/dev_r2586_dynamic_mem/NEMOGCM/NEMO/LIM_SRC_2/limtrp_2.F90 @ 2633

Last change on this file since 2633 was 2633, checked in by trackstand2, 13 years ago

Renamed wrk_use => wrk_in_use and wrk_release => wrk_not_released

  • Property svn:keywords set to Id
File size: 16.9 KB
Line 
1MODULE limtrp_2
2   !!======================================================================
3   !!                       ***  MODULE limtrp_2   ***
4   !! LIM 2.0 transport ice model : sea-ice advection/diffusion
5   !!======================================================================
6   !! History :  LIM  !  2000-01 (UCL)  Original code
7   !!            2.0  !  2001-05 (G. Madec, R. Hordoir) opa norm
8   !!             -   !  2004-01 (G. Madec, C. Ethe)  F90, mpp
9   !!            3.3  !  2009-05  (G. Garric, C. Bricaud) addition of the lim2_evp case
10   !!----------------------------------------------------------------------
11#if defined key_lim2
12   !!----------------------------------------------------------------------
13   !!   'key_lim2' :                                  LIM 2.0 sea-ice model
14   !!----------------------------------------------------------------------
15   !!   lim_trp_2      : advection/diffusion process of sea ice
16   !!   lim_trp_init_2 : initialization and namelist read
17   !!----------------------------------------------------------------------
18   USE phycst          ! physical constant
19   USE sbc_oce         ! ocean surface boundary condition
20   USE dom_oce         ! ocean domain
21   USE in_out_manager  ! I/O manager
22   USE dom_ice_2       ! LIM-2 domain
23   USE ice_2           ! LIM-2 variables
24   USE limistate_2     ! LIM-2 initial state
25   USE limadv_2        ! LIM-2 advection
26   USE limhdf_2        ! LIM-2 horizontal diffusion
27   USE lbclnk          ! lateral boundary conditions -- MPP exchanges
28   USE lib_mpp         ! MPP library
29
30   IMPLICIT NONE
31   PRIVATE
32
33   PUBLIC   lim_trp_2   ! called by sbc_ice_lim_2
34
35   REAL(wp), PUBLIC ::   bound  = 0.e0          !: boundary condit. (0.0 no-slip, 1.0 free-slip)
36
37   REAL(wp)  ::   epsi06 = 1.e-06   ! constant values
38   REAL(wp)  ::   epsi03 = 1.e-03 
39   REAL(wp)  ::   epsi16 = 1.e-16 
40   REAL(wp)  ::   rzero  = 0.e0   
41   REAL(wp)  ::   rone   = 1.e0
42
43   !! * Substitution
44#  include "vectopt_loop_substitute.h90"
45   !!----------------------------------------------------------------------
46   !! NEMO/LIM2 3.3 , UCL - NEMO Consortium (2010)
47   !! $Id$
48   !! Software governed by the CeCILL licence (NEMOGCM/NEMO_CeCILL.txt)
49   !!----------------------------------------------------------------------
50
51CONTAINS
52
53   SUBROUTINE lim_trp_2( kt )
54      !!-------------------------------------------------------------------
55      !!                   ***  ROUTINE lim_trp_2 ***
56      !!                   
57      !! ** purpose : advection/diffusion process of sea ice
58      !!
59      !! ** method  : variables included in the process are scalar,   
60      !!     other values are considered as second order.
61      !!     For advection, a second order Prather scheme is used. 
62      !!
63      !! ** action :
64      !!---------------------------------------------------------------------
65      USE wrk_nemo, ONLY: wrk_in_use, wrk_not_released
66      USE wrk_nemo, ONLY: zui_u  => wrk_2d_1, zvi_v => wrk_2d_2, zsm  => wrk_2d_3
67      USE wrk_nemo, ONLY: zs0ice => wrk_2d_4, zs0sn => wrk_2d_5, zs0a => wrk_2d_6
68      USE wrk_nemo, ONLY: zs0c0 => wrk_2d_7,  zs0c1 => wrk_2d_8, zs0c2 => wrk_2d_9, &
69                          zs0st => wrk_2d_10
70      !!
71      INTEGER, INTENT(in) ::   kt     ! number of iteration
72      !!
73      INTEGER  ::   ji, jj, jk   ! dummy loop indices
74      INTEGER  ::   initad       ! number of sub-timestep for the advection
75      REAL(wp) ::   zindb  , zindsn , zindic, zacrith   ! local scalars
76      REAL(wp) ::   zusvosn, zusvoic, zignm , zindhe    !   -      -
77      REAL(wp) ::   zvbord , zcfl   , zusnit            !   -      -
78      REAL(wp) ::   zrtt   , ztsn   , ztic1 , ztic2     !   -      -
79      !---------------------------------------------------------------------
80
81      IF(wrk_in_use(2, 1,2,3,4,5,6,7,8,9,10))THEN
82         CALL ctl_stop('lim_trp_2 : requested workspace arrays unavailable.')
83         RETURN
84      END IF
85
86      IF( kt == nit000  )   CALL lim_trp_init_2      ! Initialization (first time-step only)
87
88      zsm(:,:) = area(:,:)
89     
90      IF( ln_limdyn ) THEN
91         !-------------------------------------!
92         !   Advection of sea ice properties   !
93         !-------------------------------------!
94
95         ! ice velocities at ocean U- and V-points (zui_u,zvi_v)
96         ! ---------------------------------------
97         IF( lk_lim2_vp ) THEN      ! VP rheology : B-grid sea-ice dynamics (I-point ice velocity)
98            zvbord = 1._wp + ( 1._wp - bound )      ! zvbord=2 no-slip, =0 free slip boundary conditions       
99            DO jj = 1, jpjm1
100               DO ji = 1, jpim1   ! NO vector opt.
101                  zui_u(ji,jj) = ( u_ice(ji+1,jj) + u_ice(ji+1,jj+1) ) / ( MAX( tmu(ji+1,jj)+tmu(ji+1,jj+1), zvbord ) )
102                  zvi_v(ji,jj) = ( v_ice(ji,jj+1) + v_ice(ji+1,jj+1) ) / ( MAX( tmu(ji,jj+1)+tmu(ji+1,jj+1), zvbord ) )
103               END DO
104            END DO
105            CALL lbc_lnk( zui_u, 'U', -1. )   ;   CALL lbc_lnk( zvi_v, 'V', -1. )      ! Lateral boundary conditions
106            !
107         ELSE                       ! EVP rheology : C-grid sea-ice dynamics (u- & v-points ice velocity)
108            zui_u(:,:) = u_ice(:,:)      ! EVP rheology: ice (u,v) at u- and v-points
109            zvi_v(:,:) = v_ice(:,:)
110         ENDIF
111
112         ! CFL test for stability
113         ! ----------------------
114         zcfl  = 0._wp
115         zcfl  = MAX( zcfl, MAXVAL( ABS( zui_u(1:jpim1, :     ) ) * rdt_ice / e1u(1:jpim1, :     ) ) )
116         zcfl  = MAX( zcfl, MAXVAL( ABS( zvi_v( :     ,1:jpjm1) ) * rdt_ice / e2v( :     ,1:jpjm1) ) )
117         !
118         IF(lk_mpp)   CALL mpp_max( zcfl )
119         !
120         IF( zcfl > 0.5 .AND. lwp )   WRITE(numout,*) 'lim_trp_2 : violation of cfl criterion the ',nday,'th day, cfl = ', zcfl
121
122         ! content of properties
123         ! ---------------------
124         zs0sn (:,:) =  hsnm(:,:)              * area  (:,:)  ! Snow volume.
125         zs0ice(:,:) =  hicm(:,:)              * area  (:,:)  ! Ice volume.
126         zs0a  (:,:) =  ( 1.0 - frld(:,:) )    * area  (:,:)  ! Surface covered by ice.
127         zs0c0 (:,:) =  tbif(:,:,1) / rt0_snow * zs0sn (:,:)  ! Heat content of the snow layer.
128         zs0c1 (:,:) =  tbif(:,:,2) / rt0_ice  * zs0ice(:,:)  ! Heat content of the first ice layer.
129         zs0c2 (:,:) =  tbif(:,:,3) / rt0_ice  * zs0ice(:,:)  ! Heat content of the second ice layer.
130         zs0st (:,:) =  qstoif(:,:) / xlic     * zs0a  (:,:)  ! Heat reservoir for brine pockets.
131         
132 
133         ! Advection (Prather scheme)
134         ! ---------
135         initad = 1 + INT( MAX( rzero, SIGN( rone, zcfl-0.5 ) ) )   ! If ice drift field is too fast,         
136         zusnit = 1.0 / REAL( initad )                              ! split the ice time step in two
137         !
138         IF( MOD( ( kt - 1) / nn_fsbc , 2 ) == 0) THEN        !==  odd ice time step:  adv_x then adv_y  ==!
139            DO jk = 1, initad
140               CALL lim_adv_x_2( zusnit, zui_u, rone , zsm, zs0ice, sxice, sxxice, syice, syyice, sxyice )
141               CALL lim_adv_y_2( zusnit, zvi_v, rzero, zsm, zs0ice, sxice, sxxice, syice, syyice, sxyice )
142               CALL lim_adv_x_2( zusnit, zui_u, rone , zsm, zs0sn , sxsn , sxxsn , sysn , syysn , sxysn  )
143               CALL lim_adv_y_2( zusnit, zvi_v, rzero, zsm, zs0sn , sxsn , sxxsn , sysn , syysn , sxysn  )
144               CALL lim_adv_x_2( zusnit, zui_u, rone , zsm, zs0a  , sxa  , sxxa  , sya  , syya  , sxya   )
145               CALL lim_adv_y_2( zusnit, zvi_v, rzero, zsm, zs0a  , sxa  , sxxa  , sya  , syya  , sxya   )
146               CALL lim_adv_x_2( zusnit, zui_u, rone , zsm, zs0c0 , sxc0 , sxxc0 , syc0 , syyc0 , sxyc0  )
147               CALL lim_adv_y_2( zusnit, zvi_v, rzero, zsm, zs0c0 , sxc0 , sxxc0 , syc0 , syyc0 , sxyc0  )
148               CALL lim_adv_x_2( zusnit, zui_u, rone , zsm, zs0c1 , sxc1 , sxxc1 , syc1 , syyc1 , sxyc1  )
149               CALL lim_adv_y_2( zusnit, zvi_v, rzero, zsm, zs0c1 , sxc1 , sxxc1 , syc1 , syyc1 , sxyc1  )
150               CALL lim_adv_x_2( zusnit, zui_u, rone , zsm, zs0c2 , sxc2 , sxxc2 , syc2 , syyc2 , sxyc2  )
151               CALL lim_adv_y_2( zusnit, zvi_v, rzero, zsm, zs0c2 , sxc2 , sxxc2 , syc2 , syyc2 , sxyc2  )
152               CALL lim_adv_x_2( zusnit, zui_u, rone , zsm, zs0st , sxst , sxxst , syst , syyst , sxyst  )
153               CALL lim_adv_y_2( zusnit, zvi_v, rzero, zsm, zs0st , sxst , sxxst , syst , syyst , sxyst  )
154            END DO
155         ELSE                                                 !==  even ice time step:  adv_x then adv_y  ==!
156            DO jk = 1, initad
157               CALL lim_adv_y_2( zusnit, zvi_v, rone , zsm, zs0ice, sxice, sxxice, syice, syyice, sxyice )
158               CALL lim_adv_x_2( zusnit, zui_u, rzero, zsm, zs0ice, sxice, sxxice, syice, syyice, sxyice )
159               CALL lim_adv_y_2( zusnit, zvi_v, rone , zsm, zs0sn , sxsn , sxxsn , sysn , syysn , sxysn  )
160               CALL lim_adv_x_2( zusnit, zui_u, rzero, zsm, zs0sn , sxsn , sxxsn , sysn , syysn , sxysn  )
161               CALL lim_adv_y_2( zusnit, zvi_v, rone , zsm, zs0a  , sxa  , sxxa  , sya  , syya  , sxya   )
162               CALL lim_adv_x_2( zusnit, zui_u, rzero, zsm, zs0a  , sxa  , sxxa  , sya  , syya  , sxya   )
163               CALL lim_adv_y_2( zusnit, zvi_v, rone , zsm, zs0c0 , sxc0 , sxxc0 , syc0 , syyc0 , sxyc0  )
164               CALL lim_adv_x_2( zusnit, zui_u, rzero, zsm, zs0c0 , sxc0 , sxxc0 , syc0 , syyc0 , sxyc0  )
165               CALL lim_adv_y_2( zusnit, zvi_v, rone , zsm, zs0c1 , sxc1 , sxxc1 , syc1 , syyc1 , sxyc1  )
166               CALL lim_adv_x_2( zusnit, zui_u, rzero, zsm, zs0c1 , sxc1 , sxxc1 , syc1 , syyc1 , sxyc1  )
167               CALL lim_adv_y_2( zusnit, zvi_v, rone , zsm, zs0c2 , sxc2 , sxxc2 , syc2 , syyc2 , sxyc2  )
168               CALL lim_adv_x_2( zusnit, zui_u, rzero, zsm, zs0c2 , sxc2 , sxxc2 , syc2 , syyc2 , sxyc2  )
169               CALL lim_adv_y_2( zusnit, zvi_v, rone , zsm, zs0st , sxst , sxxst , syst , syyst , sxyst  )
170               CALL lim_adv_x_2( zusnit, zui_u, rzero, zsm, zs0st , sxst , sxxst , syst , syyst , sxyst  )
171            END DO
172         ENDIF
173                       
174         ! recover the properties from their contents
175         ! ------------------------------------------
176!!gm Define in limmsh one for all area = 1 /area  (CPU time saved !)
177         zs0ice(:,:) = zs0ice(:,:) / area(:,:)
178         zs0sn (:,:) = zs0sn (:,:) / area(:,:)
179         zs0a  (:,:) = zs0a  (:,:) / area(:,:)
180         zs0c0 (:,:) = zs0c0 (:,:) / area(:,:)
181         zs0c1 (:,:) = zs0c1 (:,:) / area(:,:)
182         zs0c2 (:,:) = zs0c2 (:,:) / area(:,:)
183         zs0st (:,:) = zs0st (:,:) / area(:,:)
184
185
186         !-------------------------------------!
187         !   Diffusion of sea ice properties   !
188         !-------------------------------------!
189
190         ! Masked eddy diffusivity coefficient at ocean U- and V-points
191         ! ------------------------------------------------------------
192         DO jj = 1, jpjm1          ! NB: has not to be defined on jpj line and jpi row
193            DO ji = 1 , fs_jpim1   ! vector opt.
194               pahu(ji,jj) = ( 1.0 - MAX( rzero, SIGN( rone, -zs0a(ji  ,jj) ) ) )   &
195                  &        * ( 1.0 - MAX( rzero, SIGN( rone, -zs0a(ji+1,jj) ) ) ) * ahiu(ji,jj)
196               pahv(ji,jj) = ( 1.0 - MAX( rzero, SIGN( rone, -zs0a(ji,jj  ) ) ) )   &
197                  &        * ( 1.0 - MAX( rzero, SIGN( rone,- zs0a(ji,jj+1) ) ) ) * ahiv(ji,jj)
198            END DO
199         END DO
200!!gm more readable coding: (and avoid an error in F90 with sign of zero)
201!        DO jj = 1, jpjm1          ! NB: has not to be defined on jpj line and jpi row
202!           DO ji = 1 , fs_jpim1   ! vector opt.
203!              IF( MIN( zs0a(ji,jj) , zs0a(ji+1,jj) ) == 0.e0 )   pahu(ji,jj) = 0._wp
204!              IF( MIN( zs0a(ji,jj) , zs0a(ji,jj+1) ) == 0.e0 )   pahv(ji,jj) = 0._wp
205!           END DO
206!        END DO
207!!gm end
208
209         ! diffusion
210         ! ---------
211         CALL lim_hdf_2( zs0ice )
212         CALL lim_hdf_2( zs0sn  )
213         CALL lim_hdf_2( zs0a   )
214         CALL lim_hdf_2( zs0c0  )
215         CALL lim_hdf_2( zs0c1  )
216         CALL lim_hdf_2( zs0c2  )
217         CALL lim_hdf_2( zs0st  )
218
219!!gm see comment this can be skipped
220         zs0ice(:,:) = MAX( rzero, zs0ice(:,:) * area(:,:) )    !!bug:  useless
221         zs0sn (:,:) = MAX( rzero, zs0sn (:,:) * area(:,:) )    !!bug:  cf /area  just below
222         zs0a  (:,:) = MAX( rzero, zs0a  (:,:) * area(:,:) )    !! caution: the suppression of the 2 changes
223         zs0c0 (:,:) = MAX( rzero, zs0c0 (:,:) * area(:,:) )    !! the last digit of the results
224         zs0c1 (:,:) = MAX( rzero, zs0c1 (:,:) * area(:,:) )
225         zs0c2 (:,:) = MAX( rzero, zs0c2 (:,:) * area(:,:) )
226         zs0st (:,:) = MAX( rzero, zs0st (:,:) * area(:,:) )
227
228
229         !-------------------------------------------------------------------!
230         !   Updating and limitation of sea ice properties after transport   !
231         !-------------------------------------------------------------------!
232         DO jj = 1, jpj
233            zindhe = MAX( 0.e0, SIGN( 1.e0, fcor(1,jj) ) )              ! = 0 for SH, =1 for NH
234            DO ji = 1, jpi
235               !
236               ! Recover mean values over the grid squares.
237               zs0sn (ji,jj) = MAX( rzero, zs0sn (ji,jj)/area(ji,jj) )
238               zs0ice(ji,jj) = MAX( rzero, zs0ice(ji,jj)/area(ji,jj) )
239               zs0a  (ji,jj) = MAX( rzero, zs0a  (ji,jj)/area(ji,jj) )
240               zs0c0 (ji,jj) = MAX( rzero, zs0c0 (ji,jj)/area(ji,jj) )
241               zs0c1 (ji,jj) = MAX( rzero, zs0c1 (ji,jj)/area(ji,jj) )
242               zs0c2 (ji,jj) = MAX( rzero, zs0c2 (ji,jj)/area(ji,jj) )
243               zs0st (ji,jj) = MAX( rzero, zs0st (ji,jj)/area(ji,jj) )
244
245               ! Recover in situ values.
246               zindb         = MAX( rzero, SIGN( rone, zs0a(ji,jj) - epsi06 ) )
247               zacrith       = 1.0 - ( zindhe * acrit(1) + ( 1.0 - zindhe ) * acrit(2) )
248               zs0a (ji,jj)  = zindb * MIN( zs0a(ji,jj), zacrith )
249               hsnif(ji,jj)  = zindb * ( zs0sn(ji,jj) /MAX( zs0a(ji,jj), epsi16 ) )
250               hicif(ji,jj)  = zindb * ( zs0ice(ji,jj)/MAX( zs0a(ji,jj), epsi16 ) )
251               zindsn        = MAX( rzero, SIGN( rone, hsnif(ji,jj) - epsi06 ) )
252               zindic        = MAX( rzero, SIGN( rone, hicif(ji,jj) - epsi03 ) )
253               zindb         = MAX( zindsn, zindic )
254               zs0a (ji,jj)  = zindb * zs0a(ji,jj)
255               frld (ji,jj)  = 1.0 - zs0a(ji,jj)
256               hsnif(ji,jj)  = zindsn * hsnif(ji,jj)
257               hicif(ji,jj)  = zindic * hicif(ji,jj)
258               zusvosn       = 1.0/MAX( hsnif(ji,jj) * zs0a(ji,jj), epsi16 )
259               zusvoic       = 1.0/MAX( hicif(ji,jj) * zs0a(ji,jj), epsi16 )
260               zignm         = MAX( rzero,  SIGN( rone, hsndif - hsnif(ji,jj) ) )
261               zrtt          = 173.15 * rone 
262               ztsn          =          zignm   * tbif(ji,jj,1)  &
263                              + ( 1.0 - zignm ) * MIN( MAX( zrtt, rt0_snow * zusvosn * zs0c0(ji,jj)) , tfu(ji,jj) ) 
264               ztic1          = MIN( MAX( zrtt, rt0_ice * zusvoic * zs0c1(ji,jj) ) , tfu(ji,jj) )
265               ztic2          = MIN( MAX( zrtt, rt0_ice * zusvoic * zs0c2(ji,jj) ) , tfu(ji,jj) )
266 
267               tbif(ji,jj,1) = zindsn * ztsn  + ( 1.0 - zindsn ) * tfu(ji,jj)               
268               tbif(ji,jj,2) = zindic * ztic1 + ( 1.0 - zindic ) * tfu(ji,jj)
269               tbif(ji,jj,3) = zindic * ztic2 + ( 1.0 - zindic ) * tfu(ji,jj)
270               qstoif(ji,jj) = zindb  * xlic * zs0st(ji,jj) /  MAX( zs0a(ji,jj), epsi16 )
271            END DO
272         END DO
273         !
274      ENDIF
275      !
276      IF(wrk_not_released(2, 1,2,3,4,5,6,7,8,9,10))THEN
277         CALL ctl_stop('lim_trp_2 : failed to release workspace arrays.')
278      END IF
279      !
280   END SUBROUTINE lim_trp_2
281
282
283   SUBROUTINE lim_trp_init_2
284      !!-------------------------------------------------------------------
285      !!                  ***  ROUTINE lim_trp_init_2  ***
286      !!
287      !! ** Purpose :   initialization of ice advection parameters
288      !!
289      !! ** Method  :   Read the namicetrp namelist and check the parameter
290      !!              values called at the first timestep (nit000)
291      !!
292      !! ** input   :   Namelist namicetrp
293      !!-------------------------------------------------------------------
294      NAMELIST/namicetrp/ bound
295      !!-------------------------------------------------------------------
296      !
297      REWIND ( numnam_ice )      ! Read Namelist namicetrp
298      READ   ( numnam_ice  , namicetrp )
299      IF(lwp) THEN
300         WRITE(numout,*)
301         WRITE(numout,*) 'lim_trp_init_2 : Ice parameters for advection '
302         WRITE(numout,*) '~~~~~~~~~~~~~~'
303         WRITE(numout,*) '   boundary conditions (0. no-slip, 1. free-slip) bound  = ', bound
304      ENDIF
305      !
306   END SUBROUTINE lim_trp_init_2
307
308#else
309   !!----------------------------------------------------------------------
310   !!   Default option         Empty Module                No sea-ice model
311   !!----------------------------------------------------------------------
312CONTAINS
313   SUBROUTINE lim_trp_2        ! Empty routine
314   END SUBROUTINE lim_trp_2
315#endif
316
317   !!======================================================================
318END MODULE limtrp_2
Note: See TracBrowser for help on using the repository browser.