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/tests/SWG/MY_SRC – NEMO

source: NEMO/trunk/tests/SWG/MY_SRC/usrdef_zgr.F90 @ 14433

Last change on this file since 14433 was 14433, checked in by smasson, 3 years ago

trunk: merge dev_r14312_MPI_Interface into the trunk, #2598

File size: 12.8 KB
RevLine 
[13503]1MODULE usrdef_zgr
2   !!======================================================================
3   !!                       ***  MODULE  usrdef_zgr  ***
4   !!
[13752]5   !!                       ===  SWG configuration  ===
[13503]6   !!
7   !! User defined : vertical coordinate system of a user configuration
8   !!======================================================================
9   !! History :  4.0  ! 2016-06  (G. Madec)  Original code
[13599]10   !!             -   ! 2020-03  (A. Nasser) Shallow Water Eq. configuration
[13503]11   !!----------------------------------------------------------------------
12
13   !!----------------------------------------------------------------------
14   !!   usr_def_zgr   : user defined vertical coordinate system
15   !!      zgr_z      : reference 1D z-coordinate
16   !!      zgr_top_bot: ocean top and bottom level indices
17   !!      zgr_zco    : 3D verticl coordinate in pure z-coordinate case
18   !!---------------------------------------------------------------------
19   USE oce            ! ocean variables
20   USE dom_oce        ! ocean domain
21   USE depth_e3       ! depth <=> e3
22   USE usrdef_nam
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 10425 2018-12-19 21:54:16Z 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,*)
[13752]67      IF(lwp) WRITE(numout,*) 'usr_def_zgr : SWG configuration (z-coordinate closed flat box ocean without cavities)'
[13503]68      IF(lwp) WRITE(numout,*) '~~~~~~~~~~~'
69      !
70      !
71      ! type of vertical coordinate
72      ! ---------------------------
[13752]73      ld_zco    = .FALSE.         ! SWG case:  z-coordinate without ocean cavities
[13503]74      ld_zps    = .FALSE.
75      ld_sco    = .TRUE.
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        !!----------------------------------------------------------------------
129      !
130        !
131      IF(lwp) THEN            ! Parameter print
132         WRITE(numout,*)
133         WRITE(numout,*) '    zgr_z   : Reference vertical z-coordinates '
134         WRITE(numout,*) '    ~~~~~~~'
135      ENDIF
136
137      !
138      ! 1D Reference z-coordinate    (using Madec & Imbard 1996 function)
139      ! -------------------------
140      !
141      ! depth at T and W-points
142      pdepw_1d(1) =   0._wp
143      pdept_1d(1) = 250._wp
144      !
145      pdepw_1d(2) = 500._wp
146      pdept_1d(2) = 750._wp
147      !
148      !                       ! e3t and e3w from depth
149      CALL depth_to_e3( pdept_1d, pdepw_1d, pe3t_1d, pe3w_1d ) 
150      !
151      !                       ! recompute depths from SUM(e3)  <== needed
152      CALL e3_to_depth( pe3t_1d, pe3w_1d, pdept_1d, pdepw_1d ) 
153      !
154      IF(lwp) THEN                        ! control print
155         WRITE(numout,*)
156         WRITE(numout,*) '              Reference 1D z-coordinate depth and scale factors:'
157         WRITE(numout, "(9x,' level  gdept_1d  gdepw_1d  e3t_1d   e3w_1d  ')" )
158         WRITE(numout, "(10x, i4, 4f9.2)" ) ( jk, pdept_1d(jk), pdepw_1d(jk), pe3t_1d(jk), pe3w_1d(jk), jk = 1, jpk )
159      ENDIF
160      !
161   END SUBROUTINE zgr_z
162
163
164   SUBROUTINE zgr_msk_top_bot( k_top , k_bot)
165      !!----------------------------------------------------------------------
166      !!                    ***  ROUTINE zgr_msk_top_bot  ***
167      !!
168      !! ** Purpose :   set the masked top and bottom ocean t-levels
169      !!
[13752]170      !! ** Method  :   SWG case = closed flat box ocean without ocean cavities
[13503]171      !!                   k_top = 1     except along north, south, east and west boundaries
172      !!                   k_bot = jpk-1 except along north, south, east and west boundaries
173      !!
174      !! ** Action  : - k_top : first wet ocean level index
175      !!              - k_bot : last  wet ocean level index
176      !!----------------------------------------------------------------------
177      INTEGER , DIMENSION(:,:), INTENT(out) ::   k_top , k_bot   ! first & last wet ocean level
178      !
179      REAL(wp), DIMENSION(jpi,jpj) ::   z2d   ! 2D local workspace
180      INTEGER  ::   ji, jj                    ! dummy loop indices
181      REAL(wp) ::   zylim0, zylim1, zxlim0, zxlim1 ! limit of the domain [m]
182      REAL(WP) ::   zcoeff    ! local scalar
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,*) '    ~~~~~~~~~~~'
[13752]188      IF(lwp) WRITE(numout,*) '       SWG case : closed flat box ocean without ocean cavities'
[13503]189      !
190      z2d(:,:) = REAL( jpkm1 , wp )          ! flat bottom
191      !
[14433]192      CALL lbc_lnk( 'usrdef_zgr', z2d, 'T', 1. )           ! set surrounding land to zero (closed boundaries)
[13503]193      !
194      zylim0 =   10000._wp    ! +10km
195      zylim1 = 2010000._wp    ! 2010km
196      zxlim0 =   10000._wp    ! +10km
197      zxlim1 = 2010000._wp    ! 2010km
198      !
199      DO jj = 1, jpj
200         DO ji = 1, jpi
201         ! if T point in the 2000 km x 2000 km domain
202         ! IF ( gphit(ji,jj) > zylim0 .AND. gphit(ji,jj) < zylim1 .AND. &
203         !   & glamt(ji,jj) > zxlim0 .AND. glamt(ji,jj) < zxlim1       )  THEN
204         ! if U,V points are in the 2000 km x 2000 km domain
205         IF ( gphiv(ji,jj) > zylim0 .AND. gphiv(ji,jj) < zylim1 .AND. & 
206            & glamu(ji,jj) > zxlim0 .AND. glamu(ji,jj) < zxlim1       )  THEN
207         k_top(ji,jj) = 1    ! = ocean
208         k_bot(ji,jj) = NINT( z2d(ji,jj) )
209         ELSE
210         k_top(ji,jj) = 0    ! = land
211         k_bot(ji,jj) = 0
212         END IF
213         END DO
214      END DO
215      ! mask the lonely corners
[14204]216      DO jj = 2, jpjm1
[13503]217         DO ji = 2, jpim1
218         zcoeff = k_top(ji+1,jj) + k_top(ji,jj+1)   &
219            +     k_top(ji-1,jj) + k_top(ji,jj-1)
220         IF ( zcoeff <= 1._wp )   THEN
221            k_top(ji,jj) = 0    ! = land
222            k_bot(ji,jj) = 0
223         END IF
224         END DO
225      END DO
226      !
227      !
228   END SUBROUTINE zgr_msk_top_bot
229   
230
231   SUBROUTINE zgr_zco( pdept_1d, pdepw_1d, pe3t_1d, pe3w_1d,   &   ! in : 1D reference vertical coordinate
232      &                pdept   , pdepw   ,                     &   ! out: 3D t & w-points depth
233      &                pe3t    , pe3u    , pe3v   , pe3f   ,   &   !      vertical scale factors
234      &                pe3w    , pe3uw   , pe3vw             )     !          -      -      -
235      !!----------------------------------------------------------------------
236      !!                  ***  ROUTINE zgr_zco  ***
237      !!
238      !! ** Purpose :   define the reference z-coordinate system
239      !!
240      !! ** Method  :   set 3D coord. arrays to reference 1D array
241      !!----------------------------------------------------------------------
242      REAL(wp), DIMENSION(:)    , INTENT(in   ) ::   pdept_1d, pdepw_1d          ! 1D grid-point depth       [m]
243      REAL(wp), DIMENSION(:)    , INTENT(in   ) ::   pe3t_1d , pe3w_1d           ! 1D vertical scale factors [m]
244      REAL(wp), DIMENSION(:,:,:), INTENT(  out) ::   pdept, pdepw                ! grid-point depth          [m]
245      REAL(wp), DIMENSION(:,:,:), INTENT(  out) ::   pe3t , pe3u , pe3v , pe3f   ! vertical scale factors    [m]
246      REAL(wp), DIMENSION(:,:,:), INTENT(  out) ::   pe3w , pe3uw, pe3vw         !    -       -      -
247      !
248      INTEGER  ::   jk
249      !!----------------------------------------------------------------------
250      !
251      DO jk = 1, jpk
252         pdept(:,:,jk) = pdept_1d(jk)
253         pdepw(:,:,jk) = pdepw_1d(jk)
254         pe3t (:,:,jk) = pe3t_1d (jk)
255         pe3u (:,:,jk) = pe3t_1d (jk)
256         pe3v (:,:,jk) = pe3t_1d (jk)
257         pe3f (:,:,jk) = pe3t_1d (jk)
258         pe3w (:,:,jk) = pe3w_1d (jk)
259         pe3uw(:,:,jk) = pe3w_1d (jk)
260         pe3vw(:,:,jk) = pe3w_1d (jk)
261      END DO
262      !
263   END SUBROUTINE zgr_zco
264
265   !!======================================================================
266END MODULE usrdef_zgr
Note: See TracBrowser for help on using the repository browser.