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

source: branches/DEV_r1879_FCM/NEMOGCM/NEMO/LIM_SRC_2/limmsh_2.F90 @ 2007

Last change on this file since 2007 was 2007, checked in by smasson, 14 years ago

update branches/DEV_r1879_FCM/NEMOGCM/NEMO with tags/nemo_v3_2_1/NEMO

  • Property svn:eol-style set to native
  • Property svn:keywords set to Id
File size: 10.7 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   !!   LIM 2.0,  UCL-LOCEAN-IPSL (2005)
27   !! $Id$
28   !! This software is governed by the CeCILL licence see modipsl/doc/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
53      REAL(wp), DIMENSION(jpi,jpj) ::  &
54         zd2d1 , zd1d2       ! Derivative of zh2 (resp. zh1) in the x direction
55         !                   ! (resp. y direction) (defined at the center)
56      REAL(wp) ::         &
57         zh1p  , zh2p   , &  ! Idem zh1, zh2 for the bottom left corner of the grid
58         zd2d1p, zd1d2p , &  ! Idem zd2d1, zd1d2 for the bottom left corner of the grid
59         zusden, zusden2     ! temporary scalars
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
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      akappa(:,:,:,:) = 0.e0
118      wght(:,:,:,:) = 0.e0
119      alambd(:,:,:,:,:,:) = 0.e0
120      tmu(:,:) = 0.e0
121!!i
122     
123     
124      ! metric coefficients for sea ice dynamic
125      !----------------------------------------
126      !                                                       ! akappa
127      DO jj = 2, jpj
128         zd1d2(:,jj) = e1v(:,jj) - e1v(:,jj-1)
129      END DO
130      CALL lbc_lnk( zd1d2, 'T', -1. )
131
132      DO ji = 2, jpi
133         zd2d1(ji,:) = e2u(ji,:) - e2u(ji-1,:)
134      END DO
135      CALL lbc_lnk( zd2d1, 'T', -1. )
136
137      akappa(:,:,1,1) =        1.0 / ( 2.0 * e1t(:,:) )
138      akappa(:,:,1,2) = zd1d2(:,:) / ( 4.0 * e1t(:,:) * e2t(:,:) )
139      akappa(:,:,2,1) = zd2d1(:,:) / ( 4.0 * e1t(:,:) * e2t(:,:) )
140      akappa(:,:,2,2) =        1.0 / ( 2.0 * e2t(:,:) )
141     
142      !                                                      ! weights (wght)
143      DO jj = 2, jpj
144         DO ji = 2, jpi
145            zusden = 1. / (  ( e1t(ji,jj) + e1t(ji-1,jj  ) )   &
146               &           * ( e2t(ji,jj) + e2t(ji  ,jj-1) ) )
147            wght(ji,jj,1,1) = zusden * e1t(ji  ,jj) * e2t(ji,jj  )
148            wght(ji,jj,1,2) = zusden * e1t(ji  ,jj) * e2t(ji,jj-1)
149            wght(ji,jj,2,1) = zusden * e1t(ji-1,jj) * e2t(ji,jj  )
150            wght(ji,jj,2,2) = zusden * e1t(ji-1,jj) * e2t(ji,jj-1)
151         END DO
152      END DO
153      CALL lbc_lnk( wght(:,:,1,1), 'I', 1. )      ! CAUTION: even with the lbc_lnk at ice U-V-point
154      CALL lbc_lnk( wght(:,:,1,2), 'I', 1. )      ! the value of wght at jpj is wrong
155      CALL lbc_lnk( wght(:,:,2,1), 'I', 1. )      ! but it is never used
156      CALL lbc_lnk( wght(:,:,2,2), 'I', 1. )
157   
158      ! Coefficients for divergence of the stress tensor
159      !-------------------------------------------------
160
161      DO jj = 2, jpj
162         DO ji = 2, jpi   ! NO vector opt.
163            zh1p  =  e1t(ji  ,jj  ) * wght(ji,jj,2,2)   &
164               &   + e1t(ji-1,jj  ) * wght(ji,jj,1,2)   &
165               &   + e1t(ji  ,jj-1) * wght(ji,jj,2,1)   &
166               &   + e1t(ji-1,jj-1) * wght(ji,jj,1,1)
167
168            zh2p  =  e2t(ji  ,jj  ) * wght(ji,jj,2,2)   &
169               &   + e2t(ji-1,jj  ) * wght(ji,jj,1,2)   &
170               &   + e2t(ji  ,jj-1) * wght(ji,jj,2,1)   &
171               &   + e2t(ji-1,jj-1) * wght(ji,jj,1,1)
172
173! better written but change the last digit and thus solver in less than 100 timestep
174!           zh1p  = e1t(ji-1,jj  ) * wght(ji,jj,1,2) + e1t(ji,jj  ) * wght(ji,jj,2,2)   &
175!              &  + e1t(ji-1,jj-1) * wght(ji,jj,1,1) + e1t(ji,jj-1) * wght(ji,jj,2,1)
176
177!           zh2p  = e2t(ji-1,jj  ) * wght(ji,jj,1,2) + e2t(ji,jj  ) * wght(ji,jj,2,2)   &
178!              &  + e2t(ji-1,jj-1) * wght(ji,jj,1,1) + e2t(ji,jj-1) * wght(ji,jj,2,1)
179
180!!ibug =0   zusden = 1.0 / ( zh1p * zh2p * 4.e0 )
181            zusden = 1.0 / MAX( zh1p * zh2p * 4.e0 , 1.e-20 )
182            zusden2 = zusden * 2.0 
183
184            zd1d2p = zusden * 0.5 * ( -e1t(ji-1,jj-1) + e1t(ji-1,jj  ) - e1t(ji,jj-1) + e1t(ji  ,jj)   )
185            zd2d1p = zusden * 0.5 * (  e2t(ji  ,jj-1) - e2t(ji-1,jj-1) + e2t(ji,jj  ) - e2t(ji-1,jj)   )
186
187            alambd(ji,jj,2,2,2,1) = zusden2 * e2t(ji  ,jj-1)
188            alambd(ji,jj,2,2,2,2) = zusden2 * e2t(ji  ,jj  )
189            alambd(ji,jj,2,2,1,1) = zusden2 * e2t(ji-1,jj-1)
190            alambd(ji,jj,2,2,1,2) = zusden2 * e2t(ji-1,jj  )
191
192            alambd(ji,jj,1,1,2,1) = zusden2 * e1t(ji  ,jj-1)
193            alambd(ji,jj,1,1,2,2) = zusden2 * e1t(ji  ,jj  )
194            alambd(ji,jj,1,1,1,1) = zusden2 * e1t(ji-1,jj-1)
195            alambd(ji,jj,1,1,1,2) = zusden2 * e1t(ji-1,jj  )
196
197            alambd(ji,jj,1,2,2,1) = zd1d2p
198            alambd(ji,jj,1,2,2,2) = zd1d2p
199            alambd(ji,jj,1,2,1,1) = zd1d2p
200            alambd(ji,jj,1,2,1,2) = zd1d2p
201
202            alambd(ji,jj,2,1,2,1) = zd2d1p
203            alambd(ji,jj,2,1,2,2) = zd2d1p
204            alambd(ji,jj,2,1,1,1) = zd2d1p
205            alambd(ji,jj,2,1,1,2) = zd2d1p
206         END DO
207      END DO
208
209      CALL lbc_lnk( alambd(:,:,2,2,2,1), 'I', 1. )      ! CAUTION: even with the lbc_lnk at ice U-V point
210      CALL lbc_lnk( alambd(:,:,2,2,2,2), 'I', 1. )      ! the value of wght at jpj is wrong
211      CALL lbc_lnk( alambd(:,:,2,2,1,1), 'I', 1. )      ! but it is never used
212      CALL lbc_lnk( alambd(:,:,2,2,1,2), 'I', 1. )      !
213
214      CALL lbc_lnk( alambd(:,:,1,1,2,1), 'I', 1. )      ! CAUTION: idem
215      CALL lbc_lnk( alambd(:,:,1,1,2,2), 'I', 1. )      !
216      CALL lbc_lnk( alambd(:,:,1,1,1,1), 'I', 1. )      !
217      CALL lbc_lnk( alambd(:,:,1,1,1,2), 'I', 1. )      !
218
219      CALL lbc_lnk( alambd(:,:,1,2,2,1), 'I', 1. )      ! CAUTION: idem
220      CALL lbc_lnk( alambd(:,:,1,2,2,2), 'I', 1. )      !
221      CALL lbc_lnk( alambd(:,:,1,2,1,1), 'I', 1. )      !
222      CALL lbc_lnk( alambd(:,:,1,2,1,2), 'I', 1. )      !
223
224      CALL lbc_lnk( alambd(:,:,2,1,2,1), 'I', 1. )      ! CAUTION: idem
225      CALL lbc_lnk( alambd(:,:,2,1,2,2), 'I', 1. )      !
226      CALL lbc_lnk( alambd(:,:,2,1,1,1), 'I', 1. )      !
227      CALL lbc_lnk( alambd(:,:,2,1,1,2), 'I', 1. )      !
228           
229
230      ! Initialization of ice masks
231      !----------------------------
232     
233      tms(:,:) = tmask(:,:,1)      ! ice T-point  : use surface tmask
234
235!i here we can use umask with a i and j shift of -1,-1
236      tmu(:,1) = 0.e0
237      tmu(1,:) = 0.e0
238      DO jj = 2, jpj               ! ice U.V-point: computed from ice T-point mask
239         DO ji = 2, jpim1   ! NO vector opt.
240            tmu(ji,jj) =  tms(ji,jj) * tms(ji-1,jj) * tms(ji,jj-1) * tms(ji-1,jj-1)           
241         END DO
242      END DO
243     
244      !--lateral boundary conditions   
245      CALL lbc_lnk( tmu(:,:), 'I', 1. )
246     
247      ! unmasked and masked area of T-grid cell
248      area(:,:) = e1t(:,:) * e2t(:,:)
249     
250   END SUBROUTINE lim_msh_2
251
252#else
253   !!----------------------------------------------------------------------
254   !!   Default option            Dummy Module         NO LIM sea-ice model
255   !!----------------------------------------------------------------------
256CONTAINS
257   SUBROUTINE lim_msh_2           ! Dummy routine
258   END SUBROUTINE lim_msh_2
259#endif
260
261   !!======================================================================
262END MODULE limmsh_2
Note: See TracBrowser for help on using the repository browser.