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 NEMO/trunk/tests/ICB/MY_SRC – NEMO

source: NEMO/trunk/tests/ICB/MY_SRC/usrdef_zgr.F90 @ 14227

Last change on this file since 14227 was 13899, checked in by mathiot, 4 years ago

ticket #1900: update branch to trunk and add ICB test case

File size: 5.4 KB
Line 
1MODULE usrdef_zgr
2   !!======================================================================
3   !!                   ***  MODULE  usrdef_zgr  ***
4   !!
5   !!                   ===      ICE_AGRIF case     ===
6   !!
7   !! Ocean domain : user defined vertical coordinate system
8   !!======================================================================
9   !! History :  4.0  ! 2016-08  (G. Madec, S. Flavoni)  Original code
10   !!----------------------------------------------------------------------
11
12   !!----------------------------------------------------------------------
13   !!   usr_def_zgr   : user defined vertical coordinate system (required)
14   !!---------------------------------------------------------------------
15   USE oce            ! ocean variables
16   USE dom_oce        ! ocean domain
17   USE usrdef_nam     ! User defined : namelist variables
18   !
19   USE in_out_manager ! I/O manager
20   USE lbclnk         ! ocean lateral boundary conditions (or mpp link)
21   USE lib_mpp        ! distributed memory computing library
22
23   IMPLICIT NONE
24   PRIVATE
25
26   PUBLIC   usr_def_zgr   ! called by domzgr.F90
27
28   !!----------------------------------------------------------------------
29   !! NEMO/OCE 4.0 , NEMO Consortium (2018)
30   !! $Id: usrdef_zgr.F90 12597 2020-03-25 08:57:21Z smasson $
31   !! Software governed by the CeCILL license (see ./LICENSE)
32   !!----------------------------------------------------------------------
33CONTAINS             
34
35   SUBROUTINE usr_def_zgr( ld_zco  , ld_zps  , ld_sco  , ld_isfcav,    &   ! type of vertical coordinate
36      &                    pdept_1d, pdepw_1d, pe3t_1d , pe3w_1d  ,    &   ! 1D reference vertical coordinate
37      &                    pdept , pdepw ,                             &   ! 3D t & w-points depth
38      &                    pe3t  , pe3u  , pe3v , pe3f ,               &   ! vertical scale factors
39      &                    pe3w  , pe3uw , pe3vw,                      &   !     -      -      -
40      &                    k_top  , k_bot    )                             ! top & bottom ocean level
41      !!---------------------------------------------------------------------
42      !!              ***  ROUTINE usr_def_zgr  ***
43      !!
44      !! ** Purpose :   User defined the vertical coordinates
45      !!
46      !!----------------------------------------------------------------------
47      LOGICAL                   , INTENT(out) ::   ld_zco, ld_zps, ld_sco      ! vertical coordinate flags
48      LOGICAL                   , INTENT(out) ::   ld_isfcav                   ! under iceshelf cavity flag
49      REAL(wp), DIMENSION(:)    , INTENT(out) ::   pdept_1d, pdepw_1d          ! 1D grid-point depth     [m]
50      REAL(wp), DIMENSION(:)    , INTENT(out) ::   pe3t_1d , pe3w_1d           ! 1D grid-point depth     [m]
51      REAL(wp), DIMENSION(:,:,:), INTENT(out) ::   pdept, pdepw                ! grid-point depth        [m]
52      REAL(wp), DIMENSION(:,:,:), INTENT(out) ::   pe3t , pe3u , pe3v , pe3f   ! vertical scale factors  [m]
53      REAL(wp), DIMENSION(:,:,:), INTENT(out) ::   pe3w , pe3uw, pe3vw         ! i-scale factors
54      INTEGER , DIMENSION(:,:)  , INTENT(out) ::   k_top, k_bot                ! first & last ocean level
55      !
56      INTEGER  ::   jk, k_dz  ! dummy indices
57      !!----------------------------------------------------------------------
58      !
59      IF(lwp) WRITE(numout,*)
60      IF(lwp) WRITE(numout,*) 'usr_def_zgr : ICE_AGRIF configuration '
61      IF(lwp) WRITE(numout,*) '~~~~~~~~~~~   (slab ocean - advection of an ice patch in a biperiodic square box domain)'
62      !
63      !
64      ! type of vertical coordinate  ==>>>   here ICE_AGRIF : slab ocean always
65      ! ---------------------------
66      ld_zco    = .TRUE.       ! z-full-step coordinate
67      ld_zps    = .FALSE.      ! z-partial-step coordinate
68      ld_sco    = .FALSE.      ! s-coordinate
69      ld_isfcav = .FALSE.      ! ISF Ice Shelves Flag
70      !
71      !
72      ! Build the vertical coordinate system
73      ! ------------------------------------
74      !
75      !                       !==  UNmasked meter bathymetry  ==!
76      !
77      !
78      k_dz = 10
79      pdepw_1d(1) = 0.0
80      pdept_1d(1) = k_dz / 2.0
81      pe3w_1d = k_dz
82      pe3t_1d = k_dz
83      !
84      DO jk = 2, jpk
85         pdepw_1d(jk) = pdepw_1d(jk-1) +   k_dz
86         pdept_1d(jk) = pdept_1d(jk-1) +   k_dz
87      END DO
88      !                       !==  top masked level bathymetry  ==!  (all coordinates)
89      !
90      ! no ocean cavities : top ocean level is ONE, except over land
91      k_top(:,:) = 1
92      !
93      !                       !==  z-coordinate  ==!   (step-like topography)
94      !                                !* bottom ocean compute from the depth of grid-points
95      jpkm1 = jpk-1
96      k_bot(:,:) = 10         ! here use k_top as a land mask
97      WHERE (( glamt < 10000 .OR. glamt > 30000 ))
98         k_bot(:,:) = 4
99      END WHERE
100      !                                !* horizontally uniform coordinate (reference z-co everywhere)
101      DO jk = 1, jpk
102         pdept(:,:,jk) = pdept_1d(jk)
103         pdepw(:,:,jk) = pdepw_1d(jk)
104         pe3t (:,:,jk) = pe3t_1d (jk)
105         pe3u (:,:,jk) = pe3t_1d (jk)
106         pe3v (:,:,jk) = pe3t_1d (jk)
107         pe3f (:,:,jk) = pe3t_1d (jk)
108         pe3w (:,:,jk) = pe3w_1d (jk)
109         pe3uw(:,:,jk) = pe3w_1d (jk)
110         pe3vw(:,:,jk) = pe3w_1d (jk)
111      END DO
112      !
113   END SUBROUTINE usr_def_zgr
114
115   !!======================================================================
116END MODULE usrdef_zgr
Note: See TracBrowser for help on using the repository browser.