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 NEMO/branches/2019/dev_r11351_fldread_with_XIOS/src/OCE/DOM – NEMO

source: NEMO/branches/2019/dev_r11351_fldread_with_XIOS/src/OCE/DOM/depth_e3.F90 @ 13463

Last change on this file since 13463 was 13463, checked in by andmirek, 4 years ago

Ticket #2195:update to trunk 13461

  • Property svn:keywords set to Id
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 oce               ! ocean variables
17   USE dom_oce           ! ocean domain
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   USE timing            ! Timing
23
24   IMPLICIT NONE
25   PRIVATE
26 
27   INTERFACE depth_to_e3
28      MODULE PROCEDURE depth_to_e3_1d, depth_to_e3_3d
29   END INTERFACE
30
31   INTERFACE e3_to_depth
32      MODULE PROCEDURE e3_to_depth_1d, e3_to_depth_3d
33   END INTERFACE
34
35   PUBLIC   depth_to_e3        ! called by usrdef_zgr
36   PUBLIC   e3_to_depth        ! called by domzgr.F90
37     
38   !!----------------------------------------------------------------------
39   !! NEMO/OCE 4.0 , NEMO Consortium (2018)
40   !! $Id$
41   !! Software governed by the CeCILL license (see ./LICENSE)
42   !!----------------------------------------------------------------------
43CONTAINS             
44
45   SUBROUTINE depth_to_e3_1d( pdept_1d, pdepw_1d, pe3t_1d, pe3w_1d )
46      !!---------------------------------------------------------------------
47      !!              ***  ROUTINE depth_to_e3_1d  ***
48      !!
49      !! ** Purpose :   compute e3t & e3w scale factors from t- & w-depths of model levels
50      !!
51      !! ** Method  :   The scale factors are given by the discrete derivative
52      !!              of the depth:
53      !!                               e3w(jk) = dk[ dept_1d ]
54      !!                               e3t(jk) = dk[ depw_1d ]
55      !!              with, at top and bottom :
56      !!                      e3w( 1 ) = 2 * ( dept( 1 ) - depw( 1 ) )
57      !!                      e3t(jpk) = 2 * ( dept(jpk) - depw(jpk) )   
58      !!
59      !! ** Action  : - pe3t_1d , pe3w_1d  : scale factors at T- and W-levels (m)
60      !!----------------------------------------------------------------------
61      REAL(wp), DIMENSION(:), INTENT(in   ) ::   pdept_1d, pdepw_1d   ! depths          [m]
62      REAL(wp), DIMENSION(:), INTENT(  out) ::   pe3t_1d , pe3w_1d    ! e3.=dk[depth]   [m]
63      !
64      INTEGER  ::   jk           ! dummy loop indices
65      !!----------------------------------------------------------------------
66      !
67      ! use pdep. at w- and t-points to compute e3. (e3. = dk[depth])
68      !
69      pe3w_1d( 1 ) = 2._wp * ( pdept_1d(1) - pdepw_1d(1) ) 
70      DO jk = 1, jpkm1
71         pe3w_1d(jk+1) = pdept_1d(jk+1) - pdept_1d(jk) 
72         pe3t_1d(jk  ) = pdepw_1d(jk+1) - pdepw_1d(jk) 
73      END DO
74      pe3t_1d(jpk) = 2._wp * ( pdept_1d(jpk) - pdepw_1d(jpk) )
75      !
76   END SUBROUTINE depth_to_e3_1d
77   
78     
79   SUBROUTINE depth_to_e3_3d( pdept_3d, pdepw_3d, pe3t_3d, pe3w_3d )
80      !!---------------------------------------------------------------------
81      !!              ***  ROUTINE depth_to_e3_3d  ***
82      !!
83      !! ** Purpose :   compute e3t & e3w scale factors from t- & w-depths of model levels
84      !!
85      !! ** Method  :   The scale factors are given by the discrete derivative
86      !!              of the depth:
87      !!                               e3w(jk) = dk[ dept_1d ]
88      !!                               e3t(jk) = dk[ depw_1d ]
89      !!              with, at top and bottom :
90      !!                      e3w( 1 ) = 2 * ( dept( 1 ) - depw( 1 ) )
91      !!                      e3t(jpk) = 2 * ( dept(jpk) - depw(jpk) )   
92      !!
93      !! ** Action  : - pe3t_1d , pe3w_1d  : scale factors at T- and W-levels (m)
94      !!----------------------------------------------------------------------
95      REAL(wp), DIMENSION(:,:,:), INTENT(in   ) ::   pdept_3d, pdepw_3d   ! depth           [m]
96      REAL(wp), DIMENSION(:,:,:), INTENT(  out) ::   pe3t_3d , pe3w_3d    ! e3.=dk[depth]   [m]
97      !
98      INTEGER  ::   jk           ! dummy loop indices
99      !!----------------------------------------------------------------------     
100      pe3w_3d(:,:, 1 ) = 2._wp * ( pdept_3d(:,:,1) - pdepw_3d(:,:,1) ) 
101      DO jk = 1, jpkm1
102         pe3w_3d(:,:,jk+1) = pdept_3d(:,:,jk+1) - pdept_3d(:,:,jk) 
103         pe3t_3d(:,:,jk  ) = pdepw_3d(:,:,jk+1) - pdepw_3d(:,:,jk) 
104      END DO
105      pe3t_3d(:,:,jpk) = 2._wp * ( pdept_3d(:,:,jpk) - pdepw_3d(:,:,jpk) )   
106      !
107   END SUBROUTINE depth_to_e3_3d
108
109
110   SUBROUTINE e3_to_depth_1d( pe3t_1d, pe3w_1d, pdept_1d, pdepw_1d )
111      !!---------------------------------------------------------------------
112      !!              ***  ROUTINE e3_to_depth_1d  ***
113      !!
114      !! ** Purpose :   compute t- & w-depths of model levels from e3t & e3w scale factors
115      !!
116      !! ** Method  :   The t- & w-depth are given by the summation of e3w & e3t, resp.
117      !!
118      !! ** Action  : - pe3t_1d, pe3w_1d : scale factor of t- and w-point (m)
119      !!----------------------------------------------------------------------
120      REAL(wp), DIMENSION(:), INTENT(in   ) ::   pe3t_1d , pe3w_1d    ! vert. scale factors   [m]
121      REAL(wp), DIMENSION(:), INTENT(  out) ::   pdept_1d, pdepw_1d   ! depth = SUM( e3 )     [m]
122      !
123      INTEGER  ::   jk           ! dummy loop indices
124      !!----------------------------------------------------------------------
125      !
126      pdepw_1d(1) = 0.0_wp
127      pdept_1d(1) = 0.5_wp * pe3w_1d(1)
128      DO jk = 2, jpk
129         pdepw_1d(jk) = pdepw_1d(jk-1) + pe3t_1d(jk-1) 
130         pdept_1d(jk) = pdept_1d(jk-1) + pe3w_1d(jk  ) 
131      END DO
132      !
133   END SUBROUTINE e3_to_depth_1d
134   
135     
136   SUBROUTINE e3_to_depth_3d( pe3t_3d, pe3w_3d, pdept_3d, pdepw_3d )
137      !!---------------------------------------------------------------------
138      !!              ***  ROUTINE e3_to_depth_3d  ***
139      !!
140      !! ** Purpose :   compute t- & w-depths of model levels from e3t & e3w scale factors
141      !!
142      !! ** Method  :   The t- & w-depth are given by the summation of e3w & e3t, resp.
143      !!
144      !! ** Action  : - pe3t_1d, pe3w_1d : scale factor of t- and w-point (m)
145      !!----------------------------------------------------------------------
146      REAL(wp), DIMENSION(:,:,:), INTENT(in   ) ::   pe3t_3d , pe3w_3d    ! vert. scale factors   [m]
147      REAL(wp), DIMENSION(:,:,:), INTENT(  out) ::   pdept_3d, pdepw_3d   ! depth = SUM( e3 )     [m]
148      !
149      INTEGER  ::   jk           ! dummy loop indices
150      !!----------------------------------------------------------------------     
151      !
152      pdepw_3d(:,:,1) = 0.0_wp
153      pdept_3d(:,:,1) = 0.5_wp * pe3w_3d(:,:,1)
154      DO jk = 2, jpk
155         pdepw_3d(:,:,jk) = pdepw_3d(:,:,jk-1) + pe3t_3d(:,:,jk-1) 
156         pdept_3d(:,:,jk) = pdept_3d(:,:,jk-1) + pe3w_3d(:,:,jk  ) 
157      END DO
158      !
159   END SUBROUTINE e3_to_depth_3d
160
161   !!======================================================================
162END MODULE depth_e3
Note: See TracBrowser for help on using the repository browser.