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/UKMO/dev_r5107_hadgem3_cplfld/trunk/NEMOGCM/NEMO/LIM_SRC_2 – NEMO

source: branches/UKMO/dev_r5107_hadgem3_cplfld/trunk/NEMOGCM/NEMO/LIM_SRC_2/limmsh_2.F90 @ 5473

Last change on this file since 5473 was 5473, checked in by cguiavarch, 9 years ago

Clear svn keywords from UKMO/dev_r5107_hadgem3_cplfld

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