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.
usrdef_zgr.F90 in branches/2016/dev_r6409_SIMPLIF_2_usrdef/NEMOGCM/CONFIG/LOCK_EXCHANGE/MY_SRC – NEMO

source: branches/2016/dev_r6409_SIMPLIF_2_usrdef/NEMOGCM/CONFIG/LOCK_EXCHANGE/MY_SRC/usrdef_zgr.F90 @ 6906

Last change on this file since 6906 was 6906, checked in by flavoni, 8 years ago

#1692 and ROBUST-3 : commit zgr and some update for LOCK EXCHANGE case

File size: 8.9 KB
Line 
1MODULE usrdef_zgr
2   !!==============================================================================
3   !!                       ***  MODULE usrdef_zgr  ***
4   !! Ocean domain : user defined vertical coordinate system
5   !!
6   !!                       ===      LOCK_EXCHANGE case      ===
7   !!
8   !!==============================================================================
9   !! History :  4.0  ! 2016-08  (G. Madec)  Original code
10   !!----------------------------------------------------------------------
11
12   !!----------------------------------------------------------------------
13   !!   usr_def_zgr      : user defined vertical coordinate system (required)
14   !!       zgr_z1d      : reference 1D z-coordinate
15   !!       zgr_zps      : 3D vertical coordinate in z-partial cell coordinate
16   !!---------------------------------------------------------------------
17   USE oce               ! ocean variables
18   USE dom_oce  ,  ONLY: ln_zco, ln_zps, ln_sco   ! ocean space and time domain
19   USE dom_oce  ,  ONLY: nimpp, njmpp             ! ocean space and time domain
20   USE dom_oce  ,  ONLY: glamt                    ! ocean space and time domain
21   USE usrdef_nam        ! User defined : namelist variables
22   !
23   USE in_out_manager    ! I/O manager
24   USE lbclnk            ! ocean lateral boundary conditions (or mpp link)
25   USE lib_mpp           ! distributed memory computing library
26   USE wrk_nemo          ! Memory allocation
27   USE timing            ! Timing
28
29   IMPLICIT NONE
30   PRIVATE
31
32   PUBLIC   usr_def_zgr        ! called by domzgr.F90
33
34  !! * Substitutions
35#  include "vectopt_loop_substitute.h90"
36   !!----------------------------------------------------------------------
37   !! NEMO/OPA 4.0 , NEMO Consortium (2016)
38   !! $Id: domzgr.F90 6624 2016-05-26 08:59:48Z gm $
39   !! Software governed by the CeCILL licence     (NEMOGCM/NEMO_CeCILL.txt)
40   !!----------------------------------------------------------------------
41CONTAINS             
42
43   SUBROUTINE usr_def_zgr( ld_zco  , ld_zps  , ld_sco  , ld_isfcav,    &   ! type of vertical coordinate
44      &                    pdept_1d, pdepw_1d, pe3t_1d , pe3w_1d  ,    &   ! 1D reference vertical coordinate
45      &                    pdept , pdepw ,                             &   ! 3D t & w-points depth
46      &                    pe3t  , pe3u  , pe3v , pe3f ,               &   ! vertical scale factors
47      &                    pe3w  , pe3uw , pe3vw,                      &   !     -      -      -
48      &                    k_top  , k_bot    )                             ! top & bottom ocean level
49      !!---------------------------------------------------------------------
50      !!              ***  ROUTINE usr_def_zgr  ***
51      !!
52      !! ** Purpose :   User defined the vertical coordinates
53      !!
54      !!----------------------------------------------------------------------
55      LOGICAL                   , INTENT(out) ::   ld_zco, ld_zps, ld_sco      ! vertical coordinate flags
56      LOGICAL                   , INTENT(out) ::   ld_isfcav                   ! under iceshelf cavity flag
57      REAL(wp), DIMENSION(:)    , INTENT(out) ::   pdept_1d, pdepw_1d          ! 1D grid-point depth     [m]
58      REAL(wp), DIMENSION(:)    , INTENT(out) ::   pe3t_1d , pe3w_1d           ! 1D grid-point depth     [m]
59      REAL(wp), DIMENSION(:,:,:), INTENT(out) ::   pdept, pdepw                ! grid-point depth        [m]
60      REAL(wp), DIMENSION(:,:,:), INTENT(out) ::   pe3t , pe3u , pe3v , pe3f   ! vertical scale factors  [m]
61      REAL(wp), DIMENSION(:,:,:), INTENT(out) ::   pe3w , pe3uw, pe3vw         ! i-scale factors
62      INTEGER , DIMENSION(:,:)  , INTENT(out) ::   k_top, k_bot                ! first & last ocean level
63      !
64      INTEGER  ::   ji, jj, jk        ! dummy indices
65      INTEGER  ::   ik                ! local integers
66      REAL(wp) ::   zfact, z1_jpkm1   ! local scalar
67      REAL(wp) ::   ze3min            ! local scalar
68      REAL(wp), DIMENSION(jpi,jpj) ::   zht, zhu, z2d   ! 2D workspace
69      !!----------------------------------------------------------------------
70      !
71      IF(lwp) WRITE(numout,*)
72      IF(lwp) WRITE(numout,*) 'usr_def_zgr : LOCK_EXCHANGE configuration (z-coordinate closed box ocean without cavities)'
73      IF(lwp) WRITE(numout,*) '~~~~~~~~~~~'
74      !
75      !
76      ! type of vertical coordinate
77      ! ---------------------------
78      ! set in usrdef_nam.F90 by reading the namusr_def namelist only ln_zco
79      ln_zps    = .FALSE.      ! z-partial-step coordinate
80      ln_sco    = .FALSE.      ! s-coordinate
81      ld_isfcav = .FALSE.      ! ISF Ice Shelves Flag
82      !
83      !
84      ! Build the vertical coordinate system
85      ! ------------------------------------
86      !
87      !                       !==  UNmasked meter bathymetry  ==!
88      !
89      ! flat bassin (20m deep and 64000m wide)
90      CALL zgr_z1d( pdept_1d, pdepw_1d, pe3t_1d , pe3w_1d )   ! Reference z-coordinate system
91      !
92      !
93      !                       !==  top masked level bathymetry  ==!  (all coordinates)
94      !
95      ! no ocean cavities : top ocean level is ONE, except over land
96      ! the ocean basin surrounded by land (1 grid-point) set through lbc_lnk call as jperio=0
97      z2d(:,:) = 1._wp                    ! surface ocean is the 1st level
98      CALL lbc_lnk( z2d, 'T', 1. )        ! closed basin
99      k_top(:,:) = z2d(:,:)
100      !
101      !                             
102      IF ( ln_zco ) THEN      !==  z-coordinate  ==!   (step-like topography)
103         !
104         !                                !* bottom ocean compute from the depth of grid-points
105         k_bot(:,:) = jpkm1 * k_top(:,:)     ! here use k_top as a land mask
106         !                                !* horizontally uniform coordinate (reference z-co everywhere)
107         DO jk = 1, jpk
108            pdept(:,:,jk) = pdept_1d(jk)
109            pdepw(:,:,jk) = pdepw_1d(jk)
110            pe3t (:,:,jk) = pe3t_1d (jk)
111            pe3u (:,:,jk) = pe3t_1d (jk)
112            pe3v (:,:,jk) = pe3t_1d (jk)
113            pe3f (:,:,jk) = pe3t_1d (jk)
114            pe3w (:,:,jk) = pe3w_1d (jk)
115            pe3uw(:,:,jk) = pe3w_1d (jk)
116            pe3vw(:,:,jk) = pe3w_1d (jk)
117         END DO
118      ENDIF
119      !
120      !
121   END SUBROUTINE usr_def_zgr
122
123
124   SUBROUTINE zgr_z1d( pdept_1d, pdepw_1d, pe3t_1d , pe3w_1d )   ! 1D reference vertical coordinate
125      !!----------------------------------------------------------------------
126      !!                   ***  ROUTINE zgr_z1d  ***
127      !!
128      !! ** Purpose :   set the depth of model levels and the resulting
129      !!      vertical scale factors.
130      !!
131      !! ** Method  :   z-coordinate system (use in all type of coordinate)
132      !!      The depth of model levels is defined from an analytical
133      !!      function the derivative of which gives the scale factors.
134      !!      both depth and scale factors only depend on k (1d arrays).
135      !!              w-level: pdepw_1d  = pdep(k)
136      !!                       pe3w_1d(k) = dk(pdep)(k)     = e3(k)
137      !!              t-level: pdept_1d  = pdep(k+0.5)
138      !!                       pe3t_1d(k) = dk(pdep)(k+0.5) = e3(k+0.5)
139      !!
140      !!            ===    Here constant vertical resolution   ===
141      !!
142      !! ** Action  : - pdept_1d, pdepw_1d : depth of T- and W-point (m)
143      !!              - pe3t_1d , pe3w_1d  : scale factors at T- and W-levels (m)
144      !!----------------------------------------------------------------------
145      REAL(wp), DIMENSION(:), INTENT(out) ::   pdept_1d, pdepw_1d   ! 1D grid-point depth        [m]
146      REAL(wp), DIMENSION(:), INTENT(out) ::   pe3t_1d , pe3w_1d    ! 1D vertical scale factors  [m]
147      !
148      INTEGER  ::   jk       ! dummy loop indices
149      REAL(wp) ::   zt, zw   ! local scalar
150      !!----------------------------------------------------------------------
151      !
152      IF(lwp) THEN                         ! Parameter print
153         WRITE(numout,*)
154         WRITE(numout,*) '    zgr_z1d : Reference vertical z-coordinates: uniform dz = ', rn_dz
155         WRITE(numout,*) '    ~~~~~~~'
156      ENDIF
157      !
158      ! Reference z-coordinate (depth - scale factor at T- and W-points)   ! Madec & Imbard 1996 function
159      ! ----------------------
160      DO jk = 1, jpk
161         zw = REAL( jk , wp )
162         zt = REAL( jk , wp ) + 0.5_wp
163         pdepw_1d(jk) =    rn_dz *   REAL( jk-1 , wp )
164         pdept_1d(jk) =    rn_dz * ( REAL( jk-1 , wp ) + 0.5_wp )
165         pe3w_1d (jk) =    rn_dz
166         pe3t_1d (jk) =    rn_dz
167      END DO
168      !
169      IF(lwp) THEN                        ! control print
170         WRITE(numout,*)
171         WRITE(numout,*) '              Reference 1D z-coordinate depth and scale factors:'
172         WRITE(numout, "(9x,' level  gdept_1d  gdepw_1d  e3t_1d   e3w_1d  ')" )
173         WRITE(numout, "(10x, i4, 4f9.2)" ) ( jk, pdept_1d(jk), pdepw_1d(jk), pe3t_1d(jk), pe3w_1d(jk), jk = 1, jpk )
174      ENDIF
175      !
176   END SUBROUTINE zgr_z1d
177   
178   !!======================================================================
179END MODULE usrdef_zgr
Note: See TracBrowser for help on using the repository browser.