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.F90 in trunk/NEMO/LIM_SRC_3 – NEMO

source: trunk/NEMO/LIM_SRC_3/limmsh.F90 @ 1694

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

avoid out of bounds access, see ticket:576

  • Property svn:keywords set to Id
File size: 5.5 KB
Line 
1MODULE limmsh
2   !!======================================================================
3   !!                     ***  MODULE  limmsh  ***
4   !! LIM ice model :   definition of the ice mesh parameters
5   !!======================================================================
6   !! History :  3.2  !  2008-01 (NEMO team)  LIM-3: adaptation from LIM-2
7   !!----------------------------------------------------------------------
8#if defined key_lim3
9   !!----------------------------------------------------------------------
10   !!   'key_lim3'                                      LIM3 sea-ice model
11   !!----------------------------------------------------------------------
12   !!   lim_msh   : definition of the ice mesh
13   !!----------------------------------------------------------------------
14   USE phycst         ! physical constants
15   USE dom_oce        ! ocean domain
16   USE dom_ice        ! sea-ice domain
17   USE in_out_manager ! I/O manager
18   USE lbclnk         !
19
20   IMPLICIT NONE
21   PRIVATE
22
23   PUBLIC   lim_msh   ! routine called by ice_ini.F90
24
25   !!----------------------------------------------------------------------
26   !! NEMO/LIM 3.2,  UCL-ASTR-LOCEAN-IPSL (2009)
27   !! $Id$
28   !! Software governed by the CeCILL licence (modipsl/doc/NEMO_CeCILL.txt)
29   !!----------------------------------------------------------------------
30
31CONTAINS
32
33   SUBROUTINE lim_msh
34      !!-------------------------------------------------------------------
35      !!                  ***  ROUTINE lim_msh  ***
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      !! Reference  : Deleersnijder et al. Ocean Modelling 100, 7-10
45      !!---------------------------------------------------------------------
46      INTEGER  ::   ji, jj   ! dummy loop indices
47      REAL(wp) ::   zusden   ! temporary scalar
48      !!---------------------------------------------------------------------
49
50      IF(lwp) THEN
51         WRITE(numout,*)
52         WRITE(numout,*) 'lim_msh : LIM-3 sea-ice model, mesh initialization'
53         WRITE(numout,*) '~~~~~~~'
54      ENDIF
55
56      !                           !==  coriolis factor & Equator position ==!
57      njeq   = INT( jpj / 2 ) 
58      njeqm1 = njeq - 1 
59      !
60      fcor(:,:) = 2. * omega * SIN( gphit(:,:) * rad )   ! coriolis factor
61      !
62      IF( fcor(1,1) * fcor(1,nlcj) < 0.e0 ) THEN   ! local domain include both hemisphere
63         l_jeq = .TRUE.
64         njeq  = 1
65         DO WHILE ( njeq <= jpj .AND. fcor(1,njeq) < 0.e0 )
66            njeq = njeq + 1
67         END DO
68         IF(lwp ) WRITE(numout,*) '          the equator is inside the domain at about njeq = ', njeq
69      ELSEIF( fcor(1,1) < 0.e0 ) THEN
70         l_jeq = .FALSE.
71         njeq = jpj
72         IF(lwp ) WRITE(numout,*) '          the model domain is entirely in the southern hemisphere: njeq = ', njeq
73      ELSE
74         l_jeq = .FALSE.
75         njeq = 2
76         IF(lwp ) WRITE(numout,*) '          the model domain is entirely in the northern hemisphere: njeq = ', njeq
77      ENDIF
78      !
79      njeqm1 = njeq - 1
80
81
82      !                           !==  metric coefficients for sea ice dynamic  ==!
83      wght(:,:,:,:) = 0.e0
84!!gm  Optimisation :  wght to be defined at F-point, not I-point  and change in limrhg
85      DO jj = 2, jpj
86         DO ji = 2, jpi
87            zusden = 1.e0 / (  ( e1t(ji,jj) + e1t(ji-1,jj  ) )   &
88               &             * ( e2t(ji,jj) + e2t(ji  ,jj-1) ) )
89            wght(ji,jj,1,1) = zusden * e1t(ji  ,jj) * e2t(ji,jj  )
90            wght(ji,jj,1,2) = zusden * e1t(ji  ,jj) * e2t(ji,jj-1)
91            wght(ji,jj,2,1) = zusden * e1t(ji-1,jj) * e2t(ji,jj  )
92            wght(ji,jj,2,2) = zusden * e1t(ji-1,jj) * e2t(ji,jj-1)
93         END DO
94      END DO
95      CALL lbc_lnk( wght(:,:,1,1), 'I', 1. )      ! CAUTION: even with the lbc_lnk at ice U-V-point
96      CALL lbc_lnk( wght(:,:,1,2), 'I', 1. )      ! the value of wght at jpj is wrong
97      CALL lbc_lnk( wght(:,:,2,1), 'I', 1. )      ! but it is never used
98      CALL lbc_lnk( wght(:,:,2,2), 'I', 1. )
99!!gm end
100
101      !                           !==  ice masks  ==!
102      tms(:,:) = tmask(:,:,1)             ! ice T-point  : use surface tmask
103      tmu(:,:) = umask(:,:,1)             ! ice U-point  : use surface umask  (C-grid EVP)
104      tmv(:,:) = vmask(:,:,1)             ! ice V-point  : use surface vmask  (C-grid EVP)
105      DO jj = 1, jpjm1                    ! ice F-point  : recompute fmask (due to nn_shlat)
106         DO ji = 1 , jpim1   ! NO vector opt.
107            tmf(ji,jj) =  tms(ji,jj) * tms(ji+1,jj) * tms(ji,jj+1) * tms(ji+1,jj+1)
108         END DO
109      END DO
110      CALL lbc_lnk( tmf(:,:), 'F', 1. )           ! lateral boundary conditions
111
112      !                           !==  unmasked and masked area of T-grid cell
113      area(:,:) = e1t(:,:) * e2t(:,:)
114      !
115   END SUBROUTINE lim_msh
116
117#else
118   !!----------------------------------------------------------------------
119   !!   Default option            Dummy Module         NO LIM sea-ice model
120   !!----------------------------------------------------------------------
121CONTAINS
122   SUBROUTINE lim_msh           ! Dummy routine
123   END SUBROUTINE lim_msh
124#endif
125
126   !!======================================================================
127END MODULE limmsh
Note: See TracBrowser for help on using the repository browser.