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/cfgs/C1D_PAPA/MY_SRC – NEMO

source: NEMO/trunk/cfgs/C1D_PAPA/MY_SRC/usrdef_zgr.F90 @ 12377

Last change on this file since 12377 was 12377, checked in by acc, 4 years ago

The big one. Merging all 2019 developments from the option 1 branch back onto the trunk.

This changeset reproduces 2019/dev_r11943_MERGE_2019 on the trunk using a 2-URL merge
onto a working copy of the trunk. I.e.:

svn merge --ignore-ancestry \

svn+ssh://acc@forge.ipsl.jussieu.fr/ipsl/forge/projets/nemo/svn/NEMO/trunk \
svn+ssh://acc@forge.ipsl.jussieu.fr/ipsl/forge/projets/nemo/svn/NEMO/branches/2019/dev_r11943_MERGE_2019 ./

The --ignore-ancestry flag avoids problems that may otherwise arise from the fact that
the merge history been trunk and branch may have been applied in a different order but
care has been taken before this step to ensure that all applicable fixes and updates
are present in the merge branch.

The trunk state just before this step has been branched to releases/release-4.0-HEAD
and that branch has been immediately tagged as releases/release-4.0.2. Any fixes
or additions in response to tickets on 4.0, 4.0.1 or 4.0.2 should be done on
releases/release-4.0-HEAD. From now on future 'point' releases (e.g. 4.0.2) will
remain unchanged with periodic releases as needs demand. Note release-4.0-HEAD is a
transitional naming convention. Future full releases, say 4.2, will have a release-4.2
branch which fulfills this role and the first point release (e.g. 4.2.0) will be made
immediately following the release branch creation.

2020 developments can be started from any trunk revision later than this one.

  • Property svn:keywords set to Id
File size: 9.1 KB
Line 
1MODULE usrdef_zgr
2   !!======================================================================
3   !!                       ***  MODULE  usrdef_zgr  ***
4   !!
5   !!                       ===  C1D_PAPA configuration  ===
6   !!
7   !! User defined : vertical coordinate system of a user configuration
8   !!======================================================================
9   !! History :  4.0  ! 2016-06  (R. Bourdalle-Badie)  Original code
10   !!----------------------------------------------------------------------
11
12   !!----------------------------------------------------------------------
13   !!   usr_def_zgr   : user defined vertical coordinate system
14   !!      zgr_z      : reference 1D z-coordinate
15   !!      zgr_top_bot: ocean top and bottom level indices
16   !!      zgr_zco    : 3D verticl coordinate in pure z-coordinate case
17   !!---------------------------------------------------------------------
18   USE oce            ! ocean variables
19   USE dom_oce        ! ocean domain
20   USE depth_e3       ! depth <=> e3
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
27   IMPLICIT NONE
28   PRIVATE
29
30   PUBLIC   usr_def_zgr        ! called by domzgr.F90
31
32   !!----------------------------------------------------------------------
33   !! NEMO/OCE 4.0 , NEMO Consortium (2018)
34   !! $Id$
35   !! Software governed by the CeCILL license (see ./LICENSE)
36   !!----------------------------------------------------------------------
37CONTAINS             
38
39   SUBROUTINE usr_def_zgr( ld_zco  , ld_zps  , ld_sco  , ld_isfcav,    &   ! type of vertical coordinate
40      &                    pdept_1d, pdepw_1d, pe3t_1d , pe3w_1d  ,    &   ! 1D reference vertical coordinate
41      &                    pdept , pdepw ,                             &   ! 3D t & w-points depth
42      &                    pe3t  , pe3u  , pe3v   , pe3f ,             &   ! vertical scale factors
43      &                    pe3w  , pe3uw , pe3vw         ,             &   !     -      -      -
44      &                    k_top  , k_bot    )                             ! top & bottom ocean level
45      !!---------------------------------------------------------------------
46      !!              ***  ROUTINE usr_def_zgr  ***
47      !!
48      !! ** Purpose :   User defined the vertical coordinates
49      !!
50      !!----------------------------------------------------------------------
51      LOGICAL                   , INTENT(out) ::   ld_zco, ld_zps, ld_sco      ! vertical coordinate flags
52      LOGICAL                   , INTENT(out) ::   ld_isfcav                   ! under iceshelf cavity flag
53      REAL(wp), DIMENSION(:)    , INTENT(out) ::   pdept_1d, pdepw_1d          ! 1D grid-point depth     [m]
54      REAL(wp), DIMENSION(:)    , INTENT(out) ::   pe3t_1d , pe3w_1d           ! 1D grid-point depth     [m]
55      REAL(wp), DIMENSION(:,:,:), INTENT(out) ::   pdept, pdepw                ! grid-point depth        [m]
56      REAL(wp), DIMENSION(:,:,:), INTENT(out) ::   pe3t , pe3u , pe3v , pe3f   ! vertical scale factors  [m]
57      REAL(wp), DIMENSION(:,:,:), INTENT(out) ::   pe3w , pe3uw, pe3vw         ! i-scale factors
58      INTEGER , DIMENSION(:,:)  , INTENT(out) ::   k_top, k_bot                ! first & last ocean level
59      !
60      INTEGER  ::   ji, jj, jk        ! dummy indices
61      INTEGER  ::   ik                ! local integers
62      REAL(wp) ::   zfact, z1_jpkm1   ! local scalar
63      REAL(wp) ::   ze3min            ! local scalar
64      REAL(wp) ::   zt, zw            ! local scalars
65      REAL(wp) ::   zsur, za0, za1, zkth, zacr        ! Values for the Madec & Imbard (1996) function
66      REAL(wp) ::   za2, zkth2, zacr2                 ! Values for optional double tanh function set from parameters
67      REAL(wp), DIMENSION(jpi,jpj) ::   zht, zhu, z2d ! 2D workspace
68
69      !!----------------------------------------------------------------------
70      !
71      IF(lwp) WRITE(numout,*)
72      IF(lwp) WRITE(numout,*) 'usr_def_zgr : C1D configuration (zps-coordinate closed box ocean without cavities)'
73      IF(lwp) WRITE(numout,*) '~~~~~~~~~~~'
74      !
75      ! type of vertical coordinate
76      ! ---------------------------
77      ld_zco    = .FALSE.         ! C1D case:  z-coordinate without ocean cavities
78      ld_zps    = .TRUE.
79      ld_sco    = .FALSE.
80      ld_isfcav = .FALSE.
81      !
82      ! Build the vertical coordinate system
83      ! ------------------------------------
84      !
85      ! Set parameters of z(k) function
86      ! -------------------------------
87      zsur =   -3958.95137127683
88      za0  =    103.953009600000
89      za1  =    2.41595126900000
90      zkth =    15.3510137000000
91      zacr =    7.00000000000000
92      za2  =    100.760928500000
93      zkth2=    48.0298937200000
94      zacr2=    13.0000000000000
95      !
96      IF(lwp) THEN            ! Parameter print
97         WRITE(numout,*)
98         WRITE(numout,*) '     zgr_z75L   : Reference vertical z-coordinates '
99         WRITE(numout,*) '     ~~~~~~~'
100         WRITE(numout,*) '       C1D case : L75 function with the following coefficients :'
101         WRITE(numout,*) '                 zsur = ', zsur
102         WRITE(numout,*) '                 za0  = ', za0
103         WRITE(numout,*) '                 za1  = ', za1
104         WRITE(numout,*) '                 zkth = ', zkth
105         WRITE(numout,*) '                 zacr = ', zacr
106         WRITE(numout,*) '                 za2  = ', za2
107         WRITE(numout,*) '                 zkth2= ', zkth2
108         WRITE(numout,*) '                 zacr2= ', zacr2
109      ENDIF
110
111      !                       !==  UNmasked meter bathymetry  ==!
112      !
113      zht(:,:) = rn_bathy
114      !
115      DO jk = 1, jpk          ! depth at T and W-points
116         zw = REAL( jk , wp )
117         zt = REAL( jk , wp ) + 0.5_wp
118         pdepw_1d(jk) = ( zsur + za0 * zw + za1 * zacr * LOG ( COSH( (zw-zkth ) / zacr  ) )    &
119                  &                    + za2 * zacr2* LOG ( COSH( (zw-zkth2) / zacr2 ) )  )
120         pdept_1d(jk) = ( zsur + za0 * zt + za1 * zacr * LOG ( COSH( (zt-zkth ) / zacr  ) )    &
121                  &                    + za2 * zacr2* LOG ( COSH( (zt-zkth2) / zacr2 ) )  )
122      END DO
123      !
124      !                       ! e3t and e3w from depth
125      CALL depth_to_e3( pdept_1d, pdepw_1d, pe3t_1d, pe3w_1d )
126      !
127      !                       ! recompute depths from SUM(e3)  <== needed
128      CALL e3_to_depth( pe3t_1d, pe3w_1d, pdept_1d, pdepw_1d )
129      !
130      IF(lwp) THEN                        ! control print
131         WRITE(numout,*)
132         WRITE(numout,*) '              Reference 1D z-coordinate depth and scale factors:'
133         WRITE(numout, "(9x,' level  gdept_1d  gdepw_1d  e3t_1d   e3w_1d  ')" )
134         WRITE(numout, "(10x, i4, 4f9.2)" ) ( jk, pdept_1d(jk), pdepw_1d(jk), pe3t_1d(jk), pe3w_1d(jk), jk = 1, jpk )
135      ENDIF
136      !
137      !                       !==  top masked level bathymetry  ==!  (all coordinates)
138      !
139      k_top(:,:) = 1 
140      !                                   !* bottom ocean compute from the depth of grid-points
141      k_bot(:,:) = jpkm1
142      DO jk = jpkm1, 1, -1
143        ze3min = 0.1_wp * pe3t_1d (jk)
144         WHERE( zht(:,:) < pdepw_1d(jk) + ze3min )   k_bot(:,:) = jk-1
145      END DO
146      !
147      !                                !* vertical coordinate system
148      DO jk = 1, jpk                      ! initialization to the reference z-coordinate
149         pdept(:,:,jk) = pdept_1d(jk)
150         pdepw(:,:,jk) = pdepw_1d(jk)
151         pe3t (:,:,jk) = pe3t_1d (jk)
152         pe3u (:,:,jk) = pe3t_1d (jk)
153         pe3v (:,:,jk) = pe3t_1d (jk)
154         pe3f (:,:,jk) = pe3t_1d (jk)
155         pe3w (:,:,jk) = pe3w_1d (jk)
156         pe3uw(:,:,jk) = pe3w_1d (jk)
157         pe3vw(:,:,jk) = pe3w_1d (jk)
158      END DO
159      DO jj = 1, jpj                      ! bottom scale factors and depth at T- and W-points
160         DO ji = 1, jpi
161            ik = k_bot(ji,jj)
162            pdepw(ji,jj,ik+1) = MIN( zht(ji,jj) , pdepw_1d(ik+1) )
163            pe3t (ji,jj,ik  ) = pdepw(ji,jj,ik+1) - pdepw(ji,jj,ik)
164            pe3t (ji,jj,ik+1) = pe3t (ji,jj,ik  ) 
165            !
166            pdept(ji,jj,ik  ) = pdepw(ji,jj,ik  ) + pe3t (ji,jj,ik  ) * 0.5_wp
167            pdept(ji,jj,ik+1) = pdepw(ji,jj,ik+1) + pe3t (ji,jj,ik+1) * 0.5_wp
168            pe3w (ji,jj,ik+1) = pdept(ji,jj,ik+1) - pdept(ji,jj,ik)              ! = pe3t (ji,jj,ik  )
169         END DO
170      END DO         
171      !                                   ! bottom scale factors and depth at  U-, V-, UW and VW-points
172      !                                   ! usually Computed as the minimum of neighbooring scale factors
173      pe3u (:,:,:) = pe3t(:,:,:)          ! HERE C1D configuration :
174      pe3v (:,:,:) = pe3t(:,:,:)          !    e3 increases with k-index
175      pe3f (:,:,:) = pe3t(:,:,:)          !    so e3 minimum of (i,i+1) points is (i) point
176      pe3uw(:,:,:) = pe3w(:,:,:)          !    in j-direction e3v=e3t and e3f=e3v
177      pe3vw(:,:,:) = pe3w(:,:,:)          !    ==>>  no need of lbc_lnk calls
178      !     
179      !
180   END SUBROUTINE usr_def_zgr
181
182   !!======================================================================
183END MODULE usrdef_zgr
Note: See TracBrowser for help on using the repository browser.