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 branches/2016/dev_r6409_SIMPLIF_2_usrdef/NEMOGCM/NEMO/LIM_SRC_3 – NEMO

source: branches/2016/dev_r6409_SIMPLIF_2_usrdef/NEMOGCM/NEMO/LIM_SRC_3/limmsh.F90 @ 7110

Last change on this file since 7110 was 6596, checked in by gm, 8 years ago

#1692 - branch SIMPLIF_2_usrdef: remove from namcfg and namdom many obsolete variables ; remove izoom/jzoom option

  • Property svn:keywords set to Id
File size: 4.7 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         ! lateral boundary condition - MPP exchanges
19   USE lib_mpp        ! MPP library
20   USE lib_fortran    ! Fortran utilities (allows no signed zero when 'key_nosignedzero' defined) 
21
22   IMPLICIT NONE
23   PRIVATE
24
25   PUBLIC   lim_msh   ! routine called by sbcice_lim.F90
26
27   !!----------------------------------------------------------------------
28   !! NEMO/LIM3 4.0 , UCL - NEMO Consortium (2011)
29   !! $Id$
30   !! Software governed by the CeCILL licence     (NEMOGCM/NEMO_CeCILL.txt)
31   !!----------------------------------------------------------------------
32CONTAINS
33
34   SUBROUTINE lim_msh
35      !!-------------------------------------------------------------------
36      !!                  ***  ROUTINE lim_msh  ***
37      !!             
38      !! ** Purpose : Definition of the charact. of the numerical grid
39      !!       
40      !! ** Action  : - Initialisation of some variables
41      !!              - Definition of some constants linked with the grid
42      !!              - Definition of the metric coef. for the sea/ice
43      !!
44      !! Reference  : Deleersnijder et al. Ocean Modelling 100, 7-10
45      !!---------------------------------------------------------------------
46      INTEGER  ::   ji, jj   ! dummy loop indices
47      REAL(wp) ::   zusden   ! local 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      !                           !==  Equator position  ==!
57      njeq   = INT( jpj / 2 ) 
58      njeqm1 = njeq - 1 
59      !
60      IF( ff_t(1,1) * ff_t(1,nlcj) < 0._wp ) THEN   ! local domain include both hemisphere
61         l_jeq = .TRUE.
62         njeq  = 1
63         DO WHILE ( njeq <= jpj .AND. ff_t(1,njeq) < 0._wp )
64            njeq = njeq + 1
65         END DO
66         IF(lwp ) WRITE(numout,*) '          the equator is inside the domain at about njeq = ', njeq
67      ELSEIF( ff_t(1,1) < 0._wp ) THEN
68         l_jeq = .FALSE.
69         njeq = jpj
70         IF(lwp ) WRITE(numout,*) '          the model domain is entirely in the southern hemisphere: njeq = ', njeq
71      ELSE
72         l_jeq = .FALSE.
73         njeq = 2
74         IF(lwp ) WRITE(numout,*) '          the model domain is entirely in the northern hemisphere: njeq = ', njeq
75      ENDIF
76      !
77      njeqm1 = njeq - 1
78
79
80      !                           !==  metric coefficients for sea ice dynamic  ==!
81      wght(:,:,:,:) = 0._wp
82!!gm  Optimisation :  wght to be defined at F-point, not I-point  and change in limrhg
83      DO jj = 2, jpj
84         DO ji = 2, jpi
85            zusden = 1._wp / (  ( e1t(ji,jj) + e1t(ji-1,jj  ) )   &
86               &              * ( e2t(ji,jj) + e2t(ji  ,jj-1) ) )
87            wght(ji,jj,1,1) = zusden * e1t(ji  ,jj) * e2t(ji,jj  )
88            wght(ji,jj,1,2) = zusden * e1t(ji  ,jj) * e2t(ji,jj-1)
89            wght(ji,jj,2,1) = zusden * e1t(ji-1,jj) * e2t(ji,jj  )
90            wght(ji,jj,2,2) = zusden * e1t(ji-1,jj) * e2t(ji,jj-1)
91         END DO
92      END DO
93      CALL lbc_lnk( wght(:,:,1,1), 'I', 1. )      ! CAUTION: even with the lbc_lnk at ice U-V-point
94      CALL lbc_lnk( wght(:,:,1,2), 'I', 1. )      ! the value of wght at jpj is wrong
95      CALL lbc_lnk( wght(:,:,2,1), 'I', 1. )      ! but it is never used
96      CALL lbc_lnk( wght(:,:,2,2), 'I', 1. )
97!!gm end
98
99      !
100   END SUBROUTINE lim_msh
101
102#else
103   !!----------------------------------------------------------------------
104   !!   Default option            Dummy Module         NO LIM sea-ice model
105   !!----------------------------------------------------------------------
106CONTAINS
107   SUBROUTINE lim_msh           ! Dummy routine
108   END SUBROUTINE lim_msh
109#endif
110
111   !!======================================================================
112END MODULE limmsh
Note: See TracBrowser for help on using the repository browser.