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/branches/2020/dev_r12563_ASINTER-06_ABL_improvement/tests/VORTEX/MY_SRC – NEMO

source: NEMO/branches/2020/dev_r12563_ASINTER-06_ABL_improvement/tests/VORTEX/MY_SRC/usrdef_zgr.F90 @ 13197

Last change on this file since 13197 was 13197, checked in by gsamson, 4 years ago

merge with trunk@r13136 with a more recent svn version; pass all SETTE tests; results identical to trunk@r13136; ticket #2419

  • Property svn:keywords set to Id
File size: 11.8 KB
Line 
1MODULE usrdef_zgr
2   !!======================================================================
3   !!                       ***  MODULE  usrdef_zgr  ***
4   !!
5   !!                      ===  VORTEX configuration  ===
6   !!
7   !! User defined : vertical coordinate system of a user configuration
8   !!======================================================================
9   !! History :  4.0  ! 2017-11  (J. Chanut)  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   !
22   USE in_out_manager ! I/O manager
23   USE lbclnk         ! ocean lateral boundary conditions (or mpp link)
24   USE lib_mpp        ! distributed memory computing library
25
26   IMPLICIT NONE
27   PRIVATE
28
29   PUBLIC   usr_def_zgr        ! called by domzgr.F90
30
31   !!----------------------------------------------------------------------
32   !! NEMO/OCE 4.0 , NEMO Consortium (2018)
33   !! $Id$
34   !! Software governed by the CeCILL license (see ./LICENSE)
35   !!----------------------------------------------------------------------
36CONTAINS             
37
38   SUBROUTINE usr_def_zgr( ld_zco  , ld_zps  , ld_sco  , ld_isfcav,    &   ! type of vertical coordinate
39      &                    pdept_1d, pdepw_1d, pe3t_1d , pe3w_1d  ,    &   ! 1D reference vertical coordinate
40      &                    pdept , pdepw ,                             &   ! 3D t & w-points depth
41      &                    pe3t  , pe3u  , pe3v   , pe3f ,             &   ! vertical scale factors
42      &                    pe3w  , pe3uw , pe3vw         ,             &   !     -      -      -
43      &                    k_top  , k_bot    )                             ! top & bottom ocean level
44      !!---------------------------------------------------------------------
45      !!              ***  ROUTINE usr_def_zgr  ***
46      !!
47      !! ** Purpose :   User defined the vertical coordinates
48      !!
49      !!----------------------------------------------------------------------
50      LOGICAL                   , INTENT(out) ::   ld_zco, ld_zps, ld_sco      ! vertical coordinate flags
51      LOGICAL                   , INTENT(out) ::   ld_isfcav                   ! under iceshelf cavity flag
52      REAL(wp), DIMENSION(:)    , INTENT(out) ::   pdept_1d, pdepw_1d          ! 1D grid-point depth     [m]
53      REAL(wp), DIMENSION(:)    , INTENT(out) ::   pe3t_1d , pe3w_1d           ! 1D grid-point depth     [m]
54      REAL(wp), DIMENSION(:,:,:), INTENT(out) ::   pdept, pdepw                ! grid-point depth        [m]
55      REAL(wp), DIMENSION(:,:,:), INTENT(out) ::   pe3t , pe3u , pe3v , pe3f   ! vertical scale factors  [m]
56      REAL(wp), DIMENSION(:,:,:), INTENT(out) ::   pe3w , pe3uw, pe3vw         ! i-scale factors
57      INTEGER , DIMENSION(:,:)  , INTENT(out) ::   k_top, k_bot                ! first & last ocean level
58      !
59      INTEGER  ::   inum   ! local logical unit
60      REAL(WP) ::   z_zco, z_zps, z_sco, z_cav
61      REAL(wp), DIMENSION(jpi,jpj) ::   z2d   ! 2D workspace
62      !!----------------------------------------------------------------------
63      !
64      IF(lwp) WRITE(numout,*)
65      IF(lwp) WRITE(numout,*) 'usr_def_zgr : VORTEX configuration (z-coordinate closed flat box ocean)'
66      IF(lwp) WRITE(numout,*) '~~~~~~~~~~~'
67      !
68      !
69      ! type of vertical coordinate
70      ! ---------------------------
71      ld_zco    = .TRUE.         ! VORTEX case:  z-coordinate without ocean cavities
72      ld_zps    = .FALSE.
73      ld_sco    = .FALSE.
74      ld_isfcav = .FALSE.
75      !
76      !
77      ! Build the vertical coordinate system
78      ! ------------------------------------
79      CALL zgr_z( pdept_1d, pdepw_1d, pe3t_1d , pe3w_1d )   ! Reference z-coordinate system
80      !
81      CALL zgr_msk_top_bot( k_top , k_bot )                 ! masked top and bottom ocean t-level indices
82      !
83      !                                                     ! z-coordinate (3D arrays) from the 1D z-coord.
84      CALL zgr_zco( pdept_1d, pdepw_1d, pe3t_1d, pe3w_1d,   &   ! in  : 1D reference vertical coordinate
85         &          pdept   , pdepw   ,                     &   ! out : 3D t & w-points depth
86         &          pe3t    , pe3u    , pe3v   , pe3f   ,   &   !       vertical scale factors
87         &          pe3w    , pe3uw   , pe3vw             )     !           -      -      -
88      !
89   END SUBROUTINE usr_def_zgr
90
91
92   SUBROUTINE zgr_z( pdept_1d, pdepw_1d, pe3t_1d , pe3w_1d )   ! 1D reference vertical coordinate
93      !!----------------------------------------------------------------------
94      !!                   ***  ROUTINE zgr_z  ***
95      !!
96      !! ** Purpose :   set the 1D depth of model levels and the resulting
97      !!              vertical scale factors.
98      !!
99      !! ** Method  :   1D z-coordinate system (use in all type of coordinate)
100      !!       The depth of model levels is set from dep(k), an analytical function:
101      !!                   w-level: depw_1d  = dep(k)
102      !!                   t-level: dept_1d  = dep(k+0.5)
103      !!       The scale factors are the discrete derivative of the depth:
104      !!                   e3w_1d(jk) = dk[ dept_1d ]
105      !!                   e3t_1d(jk) = dk[ depw_1d ]
106      !!           with at top and bottom :
107      !!                   e3w_1d( 1 ) = 2 * ( dept_1d( 1 ) - depw_1d( 1 ) )
108      !!                   e3t_1d(jpk) = 2 * ( dept_1d(jpk) - depw_1d(jpk) )
109      !!       The depth are then re-computed from the sum of e3. This ensures
110      !!    that depths are identical when reading domain configuration file.
111      !!    Indeed, only e3. are saved in this file, depth are compute by a call
112      !!    to the e3_to_depth subroutine.
113      !!
114      !!       Here the Madec & Imbard (1996) function is used.
115      !!
116      !! ** Action  : - pdept_1d, pdepw_1d : depth of T- and W-point (m)
117      !!              - pe3t_1d , pe3w_1d  : scale factors at T- and W-levels (m)
118      !!
119      !! Reference : Marti, Madec & Delecluse, 1992, JGR, 97, No8, 12,763-12,766.
120      !!             Madec and Imbard, 1996, Clim. Dyn.
121      !!----------------------------------------------------------------------
122      REAL(wp), DIMENSION(:)    , INTENT(out) ::   pdept_1d, pdepw_1d   ! 1D grid-point depth        [m]
123      REAL(wp), DIMENSION(:)    , INTENT(out) ::   pe3t_1d , pe3w_1d    ! 1D vertical scale factors  [m]
124      !
125      INTEGER  ::   jk       ! dummy loop indices
126      REAL(wp) ::   zd       ! local scalar
127      !!----------------------------------------------------------------------
128      !
129      zd = 5000._wp/FLOAT(jpkm1)
130      !
131      IF(lwp) THEN            ! Parameter print
132         WRITE(numout,*)
133         WRITE(numout,*) '    zgr_z   : Reference vertical z-coordinates '
134         WRITE(numout,*) '    ~~~~~~~'
135         WRITE(numout,*) '       VORTEX case : uniform vertical grid :'
136         WRITE(numout,*) '                     with thickness = ', zd
137      ENDIF
138
139      !
140      ! 1D Reference z-coordinate    (using Madec & Imbard 1996 function)
141      ! -------------------------
142      !
143      pdepw_1d(1) = 0._wp
144      pdept_1d(1) = 0.5_wp * zd
145      !
146      DO jk = 2, jpk          ! depth at T and W-points
147         pdepw_1d(jk) = pdepw_1d(jk-1) + zd 
148         pdept_1d(jk) = pdept_1d(jk-1) + zd 
149      END DO
150      !
151      !                       ! e3t and e3w from depth
152      CALL depth_to_e3( pdept_1d, pdepw_1d, pe3t_1d, pe3w_1d ) 
153      !
154      !                       ! recompute depths from SUM(e3)  <== needed
155      CALL e3_to_depth( pe3t_1d, pe3w_1d, pdept_1d, pdepw_1d ) 
156      !
157      IF(lwp) THEN                        ! control print
158         WRITE(numout,*)
159         WRITE(numout,*) '              Reference 1D z-coordinate depth and scale factors:'
160         WRITE(numout, "(9x,' level  gdept_1d  gdepw_1d  e3t_1d   e3w_1d  ')" )
161         WRITE(numout, "(10x, i4, 4f9.2)" ) ( jk, pdept_1d(jk), pdepw_1d(jk), pe3t_1d(jk), pe3w_1d(jk), jk = 1, jpk )
162      ENDIF
163      !
164   END SUBROUTINE zgr_z
165
166
167   SUBROUTINE zgr_msk_top_bot( k_top , k_bot )
168      !!----------------------------------------------------------------------
169      !!                    ***  ROUTINE zgr_msk_top_bot  ***
170      !!
171      !! ** Purpose :   set the masked top and bottom ocean t-levels
172      !!
173      !! ** Method  :   VORTEX case = closed flat box ocean without ocean cavities
174      !!                   k_top = 1     except along north, south, east and west boundaries
175      !!                   k_bot = jpk-1 except along north, south, east and west boundaries
176      !!
177      !! ** Action  : - k_top : first wet ocean level index
178      !!              - k_bot : last  wet ocean level index
179      !!----------------------------------------------------------------------
180      INTEGER , DIMENSION(:,:), INTENT(out) ::   k_top , k_bot   ! first & last wet ocean level
181      !
182      REAL(wp), DIMENSION(jpi,jpj) ::   z2d   ! 2D local workspace
183      !!----------------------------------------------------------------------
184      !
185      IF(lwp) WRITE(numout,*)
186      IF(lwp) WRITE(numout,*) '    zgr_top_bot : defines the top and bottom wet ocean levels.'
187      IF(lwp) WRITE(numout,*) '    ~~~~~~~~~~~'
188      IF(lwp) WRITE(numout,*) '       VORTEX case : closed flat box ocean without ocean cavities'
189      !
190      z2d(:,:) = REAL( jpkm1 , wp )          ! flat bottom
191      !
192      CALL lbc_lnk( 'usrdef_zgr', z2d, 'T', 1. )           ! set surrounding land to zero (here jperio=0 ==>> closed)
193      !
194      k_bot(:,:) = NINT( z2d(:,:) )          ! =jpkm1 over the ocean point, =0 elsewhere
195      !
196      k_top(:,:) = MIN( 1 , k_bot(:,:) )     ! = 1    over the ocean point, =0 elsewhere
197      !
198   END SUBROUTINE zgr_msk_top_bot
199   
200
201   SUBROUTINE zgr_zco( pdept_1d, pdepw_1d, pe3t_1d, pe3w_1d,   &   ! in : 1D reference vertical coordinate
202      &                pdept   , pdepw   ,                     &   ! out: 3D t & w-points depth
203      &                pe3t    , pe3u    , pe3v   , pe3f   ,   &   !      vertical scale factors
204      &                pe3w    , pe3uw   , pe3vw             )     !          -      -      -
205      !!----------------------------------------------------------------------
206      !!                  ***  ROUTINE zgr_zco  ***
207      !!
208      !! ** Purpose :   define the reference z-coordinate system
209      !!
210      !! ** Method  :   set 3D coord. arrays to reference 1D array
211      !!----------------------------------------------------------------------
212      REAL(wp), DIMENSION(:)    , INTENT(in   ) ::   pdept_1d, pdepw_1d          ! 1D grid-point depth       [m]
213      REAL(wp), DIMENSION(:)    , INTENT(in   ) ::   pe3t_1d , pe3w_1d           ! 1D vertical scale factors [m]
214      REAL(wp), DIMENSION(:,:,:), INTENT(  out) ::   pdept, pdepw                ! grid-point depth          [m]
215      REAL(wp), DIMENSION(:,:,:), INTENT(  out) ::   pe3t , pe3u , pe3v , pe3f   ! vertical scale factors    [m]
216      REAL(wp), DIMENSION(:,:,:), INTENT(  out) ::   pe3w , pe3uw, pe3vw         !    -       -      -
217      !
218      INTEGER  ::   jk
219      !!----------------------------------------------------------------------
220      !
221      DO jk = 1, jpk
222         pdept(:,:,jk) = pdept_1d(jk)
223         pdepw(:,:,jk) = pdepw_1d(jk)
224         pe3t (:,:,jk) = pe3t_1d (jk)
225         pe3u (:,:,jk) = pe3t_1d (jk)
226         pe3v (:,:,jk) = pe3t_1d (jk)
227         pe3f (:,:,jk) = pe3t_1d (jk)
228         pe3w (:,:,jk) = pe3w_1d (jk)
229         pe3uw(:,:,jk) = pe3w_1d (jk)
230         pe3vw(:,:,jk) = pe3w_1d (jk)
231      END DO
232      !
233   END SUBROUTINE zgr_zco
234
235   !!======================================================================
236END MODULE usrdef_zgr
Note: See TracBrowser for help on using the repository browser.