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

source: branches/nemo_v3_3_beta/NEMOGCM/NEMO/LIM_SRC_2/limmsh_2.F90 @ 2319

Last change on this file since 2319 was 2319, checked in by cbricaud, 14 years ago

put new EVP rheology lost during the merge

  • Property svn:keywords set to Id
File size: 12.0 KB
Line 
1MODULE limmsh_2
2   !!======================================================================
3   !!                     ***  MODULE  limmsh_2  ***
4   !! LIM 2.0 ice model :   definition of the ice mesh parameters
5   !!======================================================================
6#if defined key_lim2
7   !!----------------------------------------------------------------------
8   !!   'key_lim2'                                     LIM 2.0sea-ice model
9   !!----------------------------------------------------------------------
10   !!   lim_msh_2   : definition of the ice mesh
11   !!----------------------------------------------------------------------
12   !! * Modules used
13   USE phycst
14   USE dom_oce
15   USE dom_ice_2
16   USE lbclnk
17   USE in_out_manager
18
19   IMPLICIT NONE
20   PRIVATE
21
22   !! * Accessibility
23   PUBLIC lim_msh_2      ! routine called by ice_ini_2.F90
24
25   !!----------------------------------------------------------------------
26   !! NEMO/LIM2 3.3 , UCL - NEMO Consortium (2010)
27   !! $Id$
28   !! Software governed by the CeCILL licence (NEMOGCM/NEMO_CeCILL.txt)
29   !!----------------------------------------------------------------------
30
31CONTAINS
32
33   SUBROUTINE lim_msh_2
34      !!-------------------------------------------------------------------
35      !!                  ***  ROUTINE lim_msh_2  ***
36      !!             
37      !! ** Purpose : Definition of the charact. of the numerical grid
38      !!       
39      !! ** Action  : - Initialisation of some variables
40      !!              - Definition of some constants linked with the grid
41      !!              - Definition of the metric coef. for the sea/ice
42      !!              - Initialization of the ice masks (tmsk, umsk)
43      !!
44      !! ** Refer.  : Deleersnijder et al. Ocean Modelling 100, 7-10
45      !!
46      !! ** History :
47      !!         original    : 01-04 (LIM)
48      !!         addition    : 02-08 (C. Ethe, G. Madec)
49      !!---------------------------------------------------------------------
50      !! * Local variables
51      INTEGER :: ji, jj      ! dummy loop indices
52      REAL(wp) ::   zusden   ! local scalars
53
54#if defined key_lim2_vp
55      REAL(wp) ::   zusden2           ! local scalars
56      REAL(wp) ::   zh1p  , zh2p      !   -      -
57      REAL(wp) ::   zd2d1p, zd1d2p    !   -      -
58      REAL(wp), DIMENSION(jpi,jpj) ::   zd2d1 , zd1d2   ! 2D workspace
59#endif
60      !!---------------------------------------------------------------------
61
62      IF(lwp) THEN
63         WRITE(numout,*)
64         WRITE(numout,*) 'lim_msh_2 : LIM 2.0 sea-ice model, mesh initialization'
65         WRITE(numout,*) '~~~~~~~~~'
66      ENDIF
67     
68      IF( jphgr_msh == 2 .OR. jphgr_msh == 3 .OR. jphgr_msh == 5 )   &
69          &      CALL ctl_stop(' Coriolis parameter in LIM not set for f- or beta-plane' )
70
71      !----------------------------------------------------------                         
72      !    Initialization of local and some global (common) variables
73      !------------------------------------------------------------------
74     
75      njeq   = INT( jpj / 2 )   !i bug mpp potentiel
76      njeqm1 = njeq - 1 
77
78      fcor(:,:) = 2. * omega * SIN( gphit(:,:) * rad )   !  coriolis factor at T-point
79 
80!i    DO jj = 1, jpj
81!i       zmsk(jj) = SUM( tmask(:,jj,:) )   ! = 0          if land  everywhere on a j-line
82!!ii     write(numout,*) jj, zind(jj)
83!i    END DO
84
85      IF( fcor(1,1) * fcor(1,nlcj) < 0.e0 ) THEN   ! local domain include both hemisphere
86         l_jeq = .TRUE.
87         njeq  = 1
88         DO WHILE ( njeq <= jpj .AND. fcor(1,njeq) < 0.e0 )
89            njeq = njeq + 1
90         END DO
91         IF(lwp ) WRITE(numout,*) '          the equator is inside the domain at about njeq = ', njeq
92      ELSEIF( fcor(1,1) < 0.e0 ) THEN
93         l_jeq = .FALSE.
94         njeq = jpj
95         IF(lwp ) WRITE(numout,*) '          the model domain is entirely in the southern hemisphere: njeq = ', njeq
96      ELSE
97         l_jeq = .FALSE.
98         njeq = 2
99         IF(lwp ) WRITE(numout,*) '          the model domain is entirely in the northern hemisphere: njeq = ', njeq
100      ENDIF
101
102      njeqm1 = njeq - 1
103
104
105      !   For each grid, definition of geometric tables
106      !------------------------------------------------------------------
107     
108      !-------------------
109      ! Conventions :    !
110      !-------------------
111      !  indices 1 \ 2 <-> localisation in the 2 direction x \ y
112      !  3rd indice <-> localisation on the mesh :
113      !  0 = Centre ;  1 = corner W x(i-1/2) ; 2 = corner S y(j-1/2) ;
114      !  3 = corner SW x(i-1/2),y(j-1/2)
115      !-------------------
116!!ibug ???
117      wght(:,:,:,:) = 0.e0
118      tmu(:,:)      = 0.e0
119#if defined key_lim2_vp 
120      akappa(:,:,:,:)     = 0.e0
121      alambd(:,:,:,:,:,:) = 0.e0
122#else
123      tmv(:,:) = 0.e0
124      tmf(:,:) = 0.e0
125#endif
126!!i
127     
128
129#if defined key_lim2_vp     
130      ! metric coefficients for sea ice dynamic
131      !----------------------------------------
132      !                                                       ! akappa
133      DO jj = 2, jpj
134         zd1d2(:,jj) = e1v(:,jj) - e1v(:,jj-1)
135      END DO
136      CALL lbc_lnk( zd1d2, 'T', -1. )
137
138      DO ji = 2, jpi
139         zd2d1(ji,:) = e2u(ji,:) - e2u(ji-1,:)
140      END DO
141      CALL lbc_lnk( zd2d1, 'T', -1. )
142
143      akappa(:,:,1,1) =        1.0 / ( 2.0 * e1t(:,:) )
144      akappa(:,:,1,2) = zd1d2(:,:) / ( 4.0 * e1t(:,:) * e2t(:,:) )
145      akappa(:,:,2,1) = zd2d1(:,:) / ( 4.0 * e1t(:,:) * e2t(:,:) )
146      akappa(:,:,2,2) =        1.0 / ( 2.0 * e2t(:,:) )
147     
148      !                                                      ! weights (wght)
149      DO jj = 2, jpj
150         DO ji = 2, jpi
151            zusden = 1. / (  ( e1t(ji,jj) + e1t(ji-1,jj  ) )   &
152               &           * ( e2t(ji,jj) + e2t(ji  ,jj-1) ) )
153            wght(ji,jj,1,1) = zusden * e1t(ji  ,jj) * e2t(ji,jj  )
154            wght(ji,jj,1,2) = zusden * e1t(ji  ,jj) * e2t(ji,jj-1)
155            wght(ji,jj,2,1) = zusden * e1t(ji-1,jj) * e2t(ji,jj  )
156            wght(ji,jj,2,2) = zusden * e1t(ji-1,jj) * e2t(ji,jj-1)
157         END DO
158      END DO
159      CALL lbc_lnk( wght(:,:,1,1), 'I', 1. )      ! CAUTION: even with the lbc_lnk at ice U-V-point
160      CALL lbc_lnk( wght(:,:,1,2), 'I', 1. )      ! the value of wght at jpj is wrong
161      CALL lbc_lnk( wght(:,:,2,1), 'I', 1. )      ! but it is never used
162      CALL lbc_lnk( wght(:,:,2,2), 'I', 1. )
163#else
164      ! metric coefficients for sea ice dynamic (EVP rheology)
165      !----------------------------------------
166      DO jj = 1, jpjm1                                       ! weights (wght) at F-points
167         DO ji = 1, jpim1
168            zusden = 1. / (  ( e1t(ji+1,jj  ) + e1t(ji,jj) )   &
169               &           * ( e2t(ji  ,jj+1) + e2t(ji,jj) ) ) 
170            wght(ji,jj,1,1) = zusden * e1t(ji+1,jj) * e2t(ji,jj+1)
171            wght(ji,jj,1,2) = zusden * e1t(ji+1,jj) * e2t(ji,jj  )
172            wght(ji,jj,2,1) = zusden * e1t(ji  ,jj) * e2t(ji,jj+1)
173            wght(ji,jj,2,2) = zusden * e1t(ji  ,jj) * e2t(ji,jj  )
174         END DO
175      END DO
176      CALL lbc_lnk( wght(:,:,1,1), 'F', 1. )   ;   CALL lbc_lnk( wght(:,:,1,2),'F', 1. )       ! lateral boundary cond.   
177      CALL lbc_lnk( wght(:,:,2,1), 'F', 1. )   ;   CALL lbc_lnk( wght(:,:,2,2),'F', 1. )
178#endif
179   
180      ! Coefficients for divergence of the stress tensor
181      !-------------------------------------------------
182
183#if defined key_lim2_vp
184      DO jj = 2, jpj
185         DO ji = 2, jpi   ! NO vector opt.
186            zh1p  =  e1t(ji  ,jj  ) * wght(ji,jj,2,2)   &
187               &   + e1t(ji-1,jj  ) * wght(ji,jj,1,2)   &
188               &   + e1t(ji  ,jj-1) * wght(ji,jj,2,1)   &
189               &   + e1t(ji-1,jj-1) * wght(ji,jj,1,1)
190
191            zh2p  =  e2t(ji  ,jj  ) * wght(ji,jj,2,2)   &
192               &   + e2t(ji-1,jj  ) * wght(ji,jj,1,2)   &
193               &   + e2t(ji  ,jj-1) * wght(ji,jj,2,1)   &
194               &   + e2t(ji-1,jj-1) * wght(ji,jj,1,1)
195
196! better written but change the last digit and thus solver in less than 100 timestep
197!           zh1p  = e1t(ji-1,jj  ) * wght(ji,jj,1,2) + e1t(ji,jj  ) * wght(ji,jj,2,2)   &
198!              &  + e1t(ji-1,jj-1) * wght(ji,jj,1,1) + e1t(ji,jj-1) * wght(ji,jj,2,1)
199
200!           zh2p  = e2t(ji-1,jj  ) * wght(ji,jj,1,2) + e2t(ji,jj  ) * wght(ji,jj,2,2)   &
201!              &  + e2t(ji-1,jj-1) * wght(ji,jj,1,1) + e2t(ji,jj-1) * wght(ji,jj,2,1)
202
203!!ibug =0   zusden = 1.0 / ( zh1p * zh2p * 4.e0 )
204            zusden = 1.0 / MAX( zh1p * zh2p * 4.e0 , 1.e-20 )
205            zusden2 = zusden * 2.0 
206
207            zd1d2p = zusden * 0.5 * ( -e1t(ji-1,jj-1) + e1t(ji-1,jj  ) - e1t(ji,jj-1) + e1t(ji  ,jj)   )
208            zd2d1p = zusden * 0.5 * (  e2t(ji  ,jj-1) - e2t(ji-1,jj-1) + e2t(ji,jj  ) - e2t(ji-1,jj)   )
209
210            alambd(ji,jj,2,2,2,1) = zusden2 * e2t(ji  ,jj-1)
211            alambd(ji,jj,2,2,2,2) = zusden2 * e2t(ji  ,jj  )
212            alambd(ji,jj,2,2,1,1) = zusden2 * e2t(ji-1,jj-1)
213            alambd(ji,jj,2,2,1,2) = zusden2 * e2t(ji-1,jj  )
214
215            alambd(ji,jj,1,1,2,1) = zusden2 * e1t(ji  ,jj-1)
216            alambd(ji,jj,1,1,2,2) = zusden2 * e1t(ji  ,jj  )
217            alambd(ji,jj,1,1,1,1) = zusden2 * e1t(ji-1,jj-1)
218            alambd(ji,jj,1,1,1,2) = zusden2 * e1t(ji-1,jj  )
219
220            alambd(ji,jj,1,2,2,1) = zd1d2p
221            alambd(ji,jj,1,2,2,2) = zd1d2p
222            alambd(ji,jj,1,2,1,1) = zd1d2p
223            alambd(ji,jj,1,2,1,2) = zd1d2p
224
225            alambd(ji,jj,2,1,2,1) = zd2d1p
226            alambd(ji,jj,2,1,2,2) = zd2d1p
227            alambd(ji,jj,2,1,1,1) = zd2d1p
228            alambd(ji,jj,2,1,1,2) = zd2d1p
229         END DO
230      END DO
231
232      CALL lbc_lnk( alambd(:,:,2,2,2,1), 'I', 1. )      ! CAUTION: even with the lbc_lnk at ice U-V point
233      CALL lbc_lnk( alambd(:,:,2,2,2,2), 'I', 1. )      ! the value of wght at jpj is wrong
234      CALL lbc_lnk( alambd(:,:,2,2,1,1), 'I', 1. )      ! but it is never used
235      CALL lbc_lnk( alambd(:,:,2,2,1,2), 'I', 1. )      !
236
237      CALL lbc_lnk( alambd(:,:,1,1,2,1), 'I', 1. )      ! CAUTION: idem
238      CALL lbc_lnk( alambd(:,:,1,1,2,2), 'I', 1. )      !
239      CALL lbc_lnk( alambd(:,:,1,1,1,1), 'I', 1. )      !
240      CALL lbc_lnk( alambd(:,:,1,1,1,2), 'I', 1. )      !
241
242      CALL lbc_lnk( alambd(:,:,1,2,2,1), 'I', 1. )      ! CAUTION: idem
243      CALL lbc_lnk( alambd(:,:,1,2,2,2), 'I', 1. )      !
244      CALL lbc_lnk( alambd(:,:,1,2,1,1), 'I', 1. )      !
245      CALL lbc_lnk( alambd(:,:,1,2,1,2), 'I', 1. )      !
246
247      CALL lbc_lnk( alambd(:,:,2,1,2,1), 'I', 1. )      ! CAUTION: idem
248      CALL lbc_lnk( alambd(:,:,2,1,2,2), 'I', 1. )      !
249      CALL lbc_lnk( alambd(:,:,2,1,1,1), 'I', 1. )      !
250      CALL lbc_lnk( alambd(:,:,2,1,1,2), 'I', 1. )      !
251#endif
252           
253
254      ! Initialization of ice masks
255      !----------------------------
256     
257      tms(:,:) = tmask(:,:,1)      ! ice T-point  : use surface tmask
258
259#if defined key_lim2_vp
260      ! VP rheology : ice velocity point is I-point
261!i here we can use umask with a i and j shift of -1,-1
262      tmu(:,1) = 0.e0
263      tmu(1,:) = 0.e0
264      DO jj = 2, jpj               ! ice U.V-point: computed from ice T-point mask
265         DO ji = 2, jpim1   ! NO vector opt.
266            tmu(ji,jj) =  tms(ji,jj) * tms(ji-1,jj) * tms(ji,jj-1) * tms(ji-1,jj-1)           
267         END DO
268      END DO
269     
270      !--lateral boundary conditions   
271      CALL lbc_lnk( tmu(:,:), 'I', 1. )
272#else
273      ! EVP rheology : ice velocity point are U- & V-points ; ice vorticity
274      ! point is F-point
275      tmu(:,:) = umask(:,:,1)
276      tmv(:,:) = vmask(:,:,1)
277      tmf(:,:) = 0.e0                        ! used of fmask except its special value along the coast (rn_shlat)
278      WHERE( fmask(:,:,1) == 1.e0 )   tmf(:,:) = 1.e0
279#endif
280     
281      ! unmasked and masked area of T-grid cell
282      area(:,:) = e1t(:,:) * e2t(:,:)
283     
284   END SUBROUTINE lim_msh_2
285
286#else
287   !!----------------------------------------------------------------------
288   !!   Default option            Dummy Module         NO LIM sea-ice model
289   !!----------------------------------------------------------------------
290CONTAINS
291   SUBROUTINE lim_msh_2           ! Dummy routine
292   END SUBROUTINE lim_msh_2
293#endif
294
295   !!======================================================================
296END MODULE limmsh_2
Note: See TracBrowser for help on using the repository browser.