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/src/OCE/USR – NEMO

source: NEMO/branches/2020/dev_r12563_ASINTER-06_ABL_improvement/src/OCE/USR/usrdef_zgr.F90 @ 13159

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

merge trunk@r13136 into ASINTER-06 branch; pass all SETTE tests; results identical to trunk@r13136; ticket #2419

  • Property svn:keywords set to Id
File size: 12.5 KB
RevLine 
[6667]1MODULE usrdef_zgr
[6923]2   !!======================================================================
3   !!                       ***  MODULE  usrdef_zgr  ***
[6667]4   !!
[6923]5   !!                       ===  GYRE configuration  ===
[6667]6   !!
[6923]7   !! User defined : vertical coordinate system of a user configuration
8   !!======================================================================
[6667]9   !! History :  4.0  ! 2016-06  (G. Madec)  Original code
10   !!----------------------------------------------------------------------
11
12   !!----------------------------------------------------------------------
[7188]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
[6667]17   !!---------------------------------------------------------------------
[7188]18   USE oce            ! ocean variables
19   USE dom_oce        ! ocean domain
20   USE depth_e3       ! depth <=> e3
[6667]21   !
[7188]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
[6667]25
26   IMPLICIT NONE
27   PRIVATE
28
29   PUBLIC   usr_def_zgr        ! called by domzgr.F90
30
31   !!----------------------------------------------------------------------
[9598]32   !! NEMO/OCE 4.0 , NEMO Consortium (2018)
[10068]33   !! $Id$
34   !! Software governed by the CeCILL license (see ./LICENSE)
[6667]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 : GYRE configuration (z-coordinate closed flat box ocean without cavities)'
66      IF(lwp) WRITE(numout,*) '~~~~~~~~~~~'
67      !
68      !
69      ! type of vertical coordinate
70      ! ---------------------------
[7188]71      ld_zco    = .TRUE.         ! GYRE case:  z-coordinate without ocean cavities
[6667]72      ld_zps    = .FALSE.
73      ld_sco    = .FALSE.
74      ld_isfcav = .FALSE.
75      !
76      !
77      ! Build the vertical coordinate system
78      ! ------------------------------------
[7188]79      CALL zgr_z( pdept_1d, pdepw_1d, pe3t_1d , pe3w_1d )   ! Reference z-coordinate system
[6667]80      !
[7188]81      CALL zgr_msk_top_bot( k_top , k_bot )                 ! masked top and bottom ocean t-level indices
[6667]82      !
[7188]83      !                                                     ! z-coordinate (3D arrays) from the 1D z-coord.
[6667]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      !!
[7164]96      !! ** Purpose :   set the 1D depth of model levels and the resulting
[6904]97      !!              vertical scale factors.
[6667]98      !!
[7188]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
[7200]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.
[6667]113      !!
[7188]114      !!       Here the Madec & Imbard (1996) function is used.
[6667]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) ::   zt, zw   ! local scalars
127      REAL(wp) ::   zsur, za0, za1, zkth, zacr   ! Values for the Madec & Imbard (1996) function 
128      !!----------------------------------------------------------------------
129      !
[7164]130      ! Set parameters of z(k) function
131      ! -------------------------------
[6667]132      zsur = -2033.194295283385_wp       
133      za0  =   155.8325369664153_wp 
134      za1  =   146.3615918601890_wp
135      zkth =    17.28520372419791_wp   
136      zacr =     5.0_wp       
137      !
[7164]138      IF(lwp) THEN            ! Parameter print
[6667]139         WRITE(numout,*)
140         WRITE(numout,*) '    zgr_z   : Reference vertical z-coordinates '
141         WRITE(numout,*) '    ~~~~~~~'
142         WRITE(numout,*) '       GYRE case : MI96 function with the following coefficients :'
143         WRITE(numout,*) '                 zsur = ', zsur
144         WRITE(numout,*) '                 za0  = ', za0
145         WRITE(numout,*) '                 za1  = ', za1
146         WRITE(numout,*) '                 zkth = ', zkth
147         WRITE(numout,*) '                 zacr = ', zacr
148      ENDIF
149
[7164]150      !
151      ! 1D Reference z-coordinate    (using Madec & Imbard 1996 function)
152      ! -------------------------
153      !
154      DO jk = 1, jpk          ! depth at T and W-points
[6667]155         zw = REAL( jk , wp )
156         zt = REAL( jk , wp ) + 0.5_wp
157         pdepw_1d(jk) = ( zsur + za0 * zw + za1 * zacr *  LOG( COSH( (zw-zkth) / zacr ) )  )
158         pdept_1d(jk) = ( zsur + za0 * zt + za1 * zacr *  LOG( COSH( (zt-zkth) / zacr ) )  )
159      END DO
[7188]160      !
161      !                       ! e3t and e3w from depth
162      CALL depth_to_e3( pdept_1d, pdepw_1d, pe3t_1d, pe3w_1d ) 
163      !
164      !                       ! recompute depths from SUM(e3)  <== needed
165      CALL e3_to_depth( pe3t_1d, pe3w_1d, pdept_1d, pdepw_1d ) 
166      !
[6667]167      IF(lwp) THEN                        ! control print
168         WRITE(numout,*)
169         WRITE(numout,*) '              Reference 1D z-coordinate depth and scale factors:'
170         WRITE(numout, "(9x,' level  gdept_1d  gdepw_1d  e3t_1d   e3w_1d  ')" )
171         WRITE(numout, "(10x, i4, 4f9.2)" ) ( jk, pdept_1d(jk), pdepw_1d(jk), pe3t_1d(jk), pe3w_1d(jk), jk = 1, jpk )
172      ENDIF
173      !
174   END SUBROUTINE zgr_z
175
176
[6904]177   SUBROUTINE zgr_msk_top_bot( k_top , k_bot )
[6667]178      !!----------------------------------------------------------------------
[6904]179      !!                    ***  ROUTINE zgr_msk_top_bot  ***
[6667]180      !!
[6904]181      !! ** Purpose :   set the masked top and bottom ocean t-levels
[6667]182      !!
183      !! ** Method  :   GYRE case = closed flat box ocean without ocean cavities
184      !!                   k_top = 1     except along north, south, east and west boundaries
185      !!                   k_bot = jpk-1 except along north, south, east and west boundaries
186      !!
[7164]187      !! ** Action  : - k_top : first wet ocean level index
188      !!              - k_bot : last  wet ocean level index
[6667]189      !!----------------------------------------------------------------------
[7164]190      INTEGER , DIMENSION(:,:), INTENT(out) ::   k_top , k_bot   ! first & last wet ocean level
[6667]191      !
192      REAL(wp), DIMENSION(jpi,jpj) ::   z2d   ! 2D local workspace
193      !!----------------------------------------------------------------------
194      !
195      IF(lwp) WRITE(numout,*)
[7164]196      IF(lwp) WRITE(numout,*) '    zgr_top_bot : defines the top and bottom wet ocean levels.'
[6667]197      IF(lwp) WRITE(numout,*) '    ~~~~~~~~~~~'
198      IF(lwp) WRITE(numout,*) '       GYRE case : closed flat box ocean without ocean cavities'
199      !
[7753]200      z2d(:,:) = REAL( jpkm1 , wp )          ! flat bottom
[6667]201      !
[10425]202      CALL lbc_lnk( 'usrdef_zgr', z2d, 'T', 1. )           ! set surrounding land to zero (here jperio=0 ==>> closed)
[6667]203      !
[13159]204      k_bot(:,:) = NINT( z2d(:,:) )          ! =jpkm1 over the ocean point, =0 elsewhere
[6667]205      !
[7753]206      k_top(:,:) = MIN( 1 , k_bot(:,:) )     ! = 1    over the ocean point, =0 elsewhere
207      !
[6904]208   END SUBROUTINE zgr_msk_top_bot
[6667]209   
210
211   SUBROUTINE zgr_zco( pdept_1d, pdepw_1d, pe3t_1d, pe3w_1d,   &   ! in : 1D reference vertical coordinate
212      &                pdept   , pdepw   ,                     &   ! out: 3D t & w-points depth
213      &                pe3t    , pe3u    , pe3v   , pe3f   ,   &   !      vertical scale factors
214      &                pe3w    , pe3uw   , pe3vw             )     !          -      -      -
215      !!----------------------------------------------------------------------
216      !!                  ***  ROUTINE zgr_zco  ***
217      !!
218      !! ** Purpose :   define the reference z-coordinate system
219      !!
220      !! ** Method  :   set 3D coord. arrays to reference 1D array
221      !!----------------------------------------------------------------------
222      REAL(wp), DIMENSION(:)    , INTENT(in   ) ::   pdept_1d, pdepw_1d          ! 1D grid-point depth       [m]
223      REAL(wp), DIMENSION(:)    , INTENT(in   ) ::   pe3t_1d , pe3w_1d           ! 1D vertical scale factors [m]
224      REAL(wp), DIMENSION(:,:,:), INTENT(  out) ::   pdept, pdepw                ! grid-point depth          [m]
225      REAL(wp), DIMENSION(:,:,:), INTENT(  out) ::   pe3t , pe3u , pe3v , pe3f   ! vertical scale factors    [m]
226      REAL(wp), DIMENSION(:,:,:), INTENT(  out) ::   pe3w , pe3uw, pe3vw         !    -       -      -
227      !
[7753]228      INTEGER  ::   jk
[6667]229      !!----------------------------------------------------------------------
230      !
231      DO jk = 1, jpk
[7753]232         pdept(:,:,jk) = pdept_1d(jk)
233         pdepw(:,:,jk) = pdepw_1d(jk)
234         pe3t (:,:,jk) = pe3t_1d (jk)
235         pe3u (:,:,jk) = pe3t_1d (jk)
236         pe3v (:,:,jk) = pe3t_1d (jk)
237         pe3f (:,:,jk) = pe3t_1d (jk)
238         pe3w (:,:,jk) = pe3w_1d (jk)
239         pe3uw(:,:,jk) = pe3w_1d (jk)
240         pe3vw(:,:,jk) = pe3w_1d (jk)
[6667]241      END DO
242      !
243   END SUBROUTINE zgr_zco
244
245   !!======================================================================
246END MODULE usrdef_zgr
Note: See TracBrowser for help on using the repository browser.