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_r14116_HPC-04_mcastril_Mixed_Precision_implementation_final/tests/TSUNAMI/MY_SRC – NEMO

source: NEMO/branches/2020/dev_r14116_HPC-04_mcastril_Mixed_Precision_implementation_final/tests/TSUNAMI/MY_SRC/usrdef_zgr.F90 @ 14644

Last change on this file since 14644 was 14644, checked in by sparonuz, 3 years ago

Merge trunk -r14642:HEAD

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