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.
depth_e3.F90 in utils/tools_dev_r12970_AGRIF_CMEMS/DOMAINcfg/src – NEMO

source: utils/tools_dev_r12970_AGRIF_CMEMS/DOMAINcfg/src/depth_e3.F90 @ 13024

Last change on this file since 13024 was 13024, checked in by rblod, 4 years ago

First version of new nesting tools merged with domaincfg, see ticket #2129

File size: 7.4 KB
Line 
1MODULE depth_e3
2   !!======================================================================
3   !!                       ***  MODULE  depth_e3  ***
4   !!
5   !! zgr : vertical coordinate system
6   !!======================================================================
7   !! History :  4.0  ! 2016-11  (S. Flavoni, G. Madec)  Original code
8   !!----------------------------------------------------------------------
9
10   !!----------------------------------------------------------------------
11   !!   depth_to_e3   : use the depth of t- and w-points to calculate e3t & e3w
12   !!                   (generic interface for 1D and 3D fields)
13   !!   e3_to_depth   : use e3t & e3w to calculate the depth of t- and w-points
14   !!                   (generic interface for 1D and 3D fields)
15   !!---------------------------------------------------------------------
16   USE dom_oce           ! ocean domain
17   !
18   USE in_out_manager    ! I/O manager
19   USE lbclnk            ! ocean lateral boundary conditions (or mpp link)
20   USE lib_mpp           ! distributed memory computing library
21   USE timing            ! Timing
22
23   IMPLICIT NONE
24   PRIVATE
25 
26   INTERFACE depth_to_e3
27      MODULE PROCEDURE depth_to_e3_1d, depth_to_e3_3d
28   END INTERFACE
29
30   INTERFACE e3_to_depth
31      MODULE PROCEDURE e3_to_depth_1d, e3_to_depth_3d
32   END INTERFACE
33
34   PUBLIC   depth_to_e3        ! called by usrdef_zgr
35   PUBLIC   e3_to_depth        ! called by domzgr.F90
36     
37   !! * Substitutions
38#  include "vectopt_loop_substitute.h90"
39   !!----------------------------------------------------------------------
40   !! NEMO/OCE 4.0 , NEMO Consortium (2018)
41   !! $Id: depth_e3.F90 10069 2018-08-28 14:12:24Z nicolasmartin $
42   !! Software governed by the CeCILL license (see ./LICENSE)
43   !!----------------------------------------------------------------------
44CONTAINS             
45
46   SUBROUTINE depth_to_e3_1d( pdept_1d, pdepw_1d, pe3t_1d, pe3w_1d )
47      !!---------------------------------------------------------------------
48      !!              ***  ROUTINE depth_to_e3_1d  ***
49      !!
50      !! ** Purpose :   compute e3t & e3w scale factors from t- & w-depths of model levels
51      !!
52      !! ** Method  :   The scale factors are given by the discrete derivative
53      !!              of the depth:
54      !!                               e3w(jk) = dk[ dept_1d ]
55      !!                               e3t(jk) = dk[ depw_1d ]
56      !!              with, at top and bottom :
57      !!                      e3w( 1 ) = 2 * ( dept( 1 ) - depw( 1 ) )
58      !!                      e3t(jpk) = 2 * ( dept(jpk) - depw(jpk) )   
59      !!
60      !! ** Action  : - pe3t_1d , pe3w_1d  : scale factors at T- and W-levels (m)
61      !!----------------------------------------------------------------------
62      REAL(wp), DIMENSION(:), INTENT(in   ) ::   pdept_1d, pdepw_1d   ! depths          [m]
63      REAL(wp), DIMENSION(:), INTENT(  out) ::   pe3t_1d , pe3w_1d    ! e3.=dk[depth]   [m]
64      !
65      INTEGER  ::   jk           ! dummy loop indices
66      !!----------------------------------------------------------------------
67      !
68      ! use pdep. at w- and t-points to compute e3. (e3. = dk[depth])
69      !
70      pe3w_1d( 1 ) = 2._wp * ( pdept_1d(1) - pdepw_1d(1) ) 
71      DO jk = 1, jpkm1
72         pe3w_1d(jk+1) = pdept_1d(jk+1) - pdept_1d(jk) 
73         pe3t_1d(jk  ) = pdepw_1d(jk+1) - pdepw_1d(jk) 
74      END DO
75      pe3t_1d(jpk) = 2._wp * ( pdept_1d(jpk) - pdepw_1d(jpk) )
76      !
77   END SUBROUTINE depth_to_e3_1d
78   
79     
80   SUBROUTINE depth_to_e3_3d( pdept_3d, pdepw_3d, pe3t_3d, pe3w_3d )
81      !!---------------------------------------------------------------------
82      !!              ***  ROUTINE depth_to_e3_3d  ***
83      !!
84      !! ** Purpose :   compute e3t & e3w scale factors from t- & w-depths of model levels
85      !!
86      !! ** Method  :   The scale factors are given by the discrete derivative
87      !!              of the depth:
88      !!                               e3w(jk) = dk[ dept_1d ]
89      !!                               e3t(jk) = dk[ depw_1d ]
90      !!              with, at top and bottom :
91      !!                      e3w( 1 ) = 2 * ( dept( 1 ) - depw( 1 ) )
92      !!                      e3t(jpk) = 2 * ( dept(jpk) - depw(jpk) )   
93      !!
94      !! ** Action  : - pe3t_1d , pe3w_1d  : scale factors at T- and W-levels (m)
95      !!----------------------------------------------------------------------
96      REAL(wp), DIMENSION(:,:,:), INTENT(in   ) ::   pdept_3d, pdepw_3d   ! depth           [m]
97      REAL(wp), DIMENSION(:,:,:), INTENT(  out) ::   pe3t_3d , pe3w_3d    ! e3.=dk[depth]   [m]
98      !
99      INTEGER  ::   jk           ! dummy loop indices
100      !!----------------------------------------------------------------------     
101      pe3w_3d(:,:, 1 ) = 2._wp * ( pdept_3d(:,:,1) - pdepw_3d(:,:,1) ) 
102      DO jk = 1, jpkm1
103         pe3w_3d(:,:,jk+1) = pdept_3d(:,:,jk+1) - pdept_3d(:,:,jk) 
104         pe3t_3d(:,:,jk  ) = pdepw_3d(:,:,jk+1) - pdepw_3d(:,:,jk) 
105      END DO
106      pe3t_3d(:,:,jpk) = 2._wp * ( pdept_3d(:,:,jpk) - pdepw_3d(:,:,jpk) )   
107      !
108   END SUBROUTINE depth_to_e3_3d
109
110
111   SUBROUTINE e3_to_depth_1d( pe3t_1d, pe3w_1d, pdept_1d, pdepw_1d )
112      !!---------------------------------------------------------------------
113      !!              ***  ROUTINE e3_to_depth_1d  ***
114      !!
115      !! ** Purpose :   compute t- & w-depths of model levels from e3t & e3w scale factors
116      !!
117      !! ** Method  :   The t- & w-depth are given by the summation of e3w & e3t, resp.
118      !!
119      !! ** Action  : - pe3t_1d, pe3w_1d : scale factor of t- and w-point (m)
120      !!----------------------------------------------------------------------
121      REAL(wp), DIMENSION(:), INTENT(in   ) ::   pe3t_1d , pe3w_1d    ! vert. scale factors   [m]
122      REAL(wp), DIMENSION(:), INTENT(  out) ::   pdept_1d, pdepw_1d   ! depth = SUM( e3 )     [m]
123      !
124      INTEGER  ::   jk           ! dummy loop indices
125      !!----------------------------------------------------------------------
126      !
127      pdepw_1d(1) = 0.0_wp
128      pdept_1d(1) = 0.5_wp * pe3w_1d(1)
129      DO jk = 2, jpk
130         pdepw_1d(jk) = pdepw_1d(jk-1) + pe3t_1d(jk-1) 
131         pdept_1d(jk) = pdept_1d(jk-1) + pe3w_1d(jk  ) 
132      END DO
133      !
134   END SUBROUTINE e3_to_depth_1d
135   
136     
137   SUBROUTINE e3_to_depth_3d( pe3t_3d, pe3w_3d, pdept_3d, pdepw_3d )
138      !!---------------------------------------------------------------------
139      !!              ***  ROUTINE e3_to_depth_3d  ***
140      !!
141      !! ** Purpose :   compute t- & w-depths of model levels from e3t & e3w scale factors
142      !!
143      !! ** Method  :   The t- & w-depth are given by the summation of e3w & e3t, resp.
144      !!
145      !! ** Action  : - pe3t_1d, pe3w_1d : scale factor of t- and w-point (m)
146      !!----------------------------------------------------------------------
147      REAL(wp), DIMENSION(:,:,:), INTENT(in   ) ::   pe3t_3d , pe3w_3d    ! vert. scale factors   [m]
148      REAL(wp), DIMENSION(:,:,:), INTENT(  out) ::   pdept_3d, pdepw_3d   ! depth = SUM( e3 )     [m]
149      !
150      INTEGER  ::   jk           ! dummy loop indices
151      !!----------------------------------------------------------------------     
152      !
153      pdepw_3d(:,:,1) = 0.0_wp
154      pdept_3d(:,:,1) = 0.5_wp * pe3w_3d(:,:,1)
155      DO jk = 2, jpk
156         pdepw_3d(:,:,jk) = pdepw_3d(:,:,jk-1) + pe3t_3d(:,:,jk-1) 
157         pdept_3d(:,:,jk) = pdept_3d(:,:,jk-1) + pe3w_3d(:,:,jk  ) 
158      END DO
159      !
160   END SUBROUTINE e3_to_depth_3d
161
162   !!======================================================================
163END MODULE depth_e3
Note: See TracBrowser for help on using the repository browser.