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_istate.F90 in NEMO/trunk/tests/DOME/MY_SRC – NEMO

source: NEMO/trunk/tests/DOME/MY_SRC/usrdef_istate.F90 @ 14133

Last change on this file since 14133 was 14133, checked in by jchanut, 3 years ago

Now rn_a0 is public, use it in test cases instead of harcoded values

File size: 6.2 KB
Line 
1MODULE usrdef_istate
2   !!==============================================================================
3   !!                       ***  MODULE usrdef_istate  ***
4   !!
5   !!                        ===  DOME configuration  ===
6   !!
7   !! User defined : set the initial state of a user configuration
8   !!==============================================================================
9   !! History :  NEMO 4.x ! 2020-12  (J. Chanut) Original code
10   !!----------------------------------------------------------------------
11
12   !!----------------------------------------------------------------------
13   !!  usr_def_istate : initial state in Temperature and salinity
14   !!----------------------------------------------------------------------
15   USE par_oce        ! ocean space and time domain
16   USE phycst         ! physical constants
17   USE eosbn2, ONLY: rn_a0
18   !
19   USE in_out_manager ! I/O manager
20   USE lib_mpp        ! MPP library
21   
22   IMPLICIT NONE
23   PRIVATE
24
25   PUBLIC   usr_def_istate   ! called by istate.F90
26   PUBlIC   usr_def_istate_ssh
27   !!----------------------------------------------------------------------
28   !! NEMO/OCE 4.0 , NEMO Consortium (2018)
29   !! $Id: usrdef_istate.F90 12489 2020-02-28 15:55:11Z davestorkey $
30   !! Software governed by the CeCILL license (see ./LICENSE)
31   !!----------------------------------------------------------------------
32   !! * Substitutions
33#  include "do_loop_substitute.h90"
34
35CONTAINS
36 
37   SUBROUTINE usr_def_istate( pdept, ptmask, pts, pu, pv )
38      !!----------------------------------------------------------------------
39      !!                   ***  ROUTINE usr_def_istate  ***
40      !!
41      !! ** Purpose :   Initialization of the dynamics and tracers
42      !!                Here OVERFLOW configuration
43      !!
44      !! ** Method  : - set temprature field
45      !!              - set salinity   field
46      !!
47      !! ** Reference: Legg, S., Hallberg, R. W.  and J. B. Girton, 2006:
48      !!               Comparison of entrainment in overflows simulated by z-coordinate,
49      !!               isopycnal and non-hydrostatic models. Ocean Modelling, 11, 69-97.
50      !!
51      !!----------------------------------------------------------------------
52      REAL(wp), DIMENSION(jpi,jpj,jpk)     , INTENT(in   ) ::   pdept   ! depth of t-point               [m]
53      REAL(wp), DIMENSION(jpi,jpj,jpk)     , INTENT(in   ) ::   ptmask  ! t-point ocean mask             [m]
54      REAL(wp), DIMENSION(jpi,jpj,jpk,jpts), INTENT(  out) ::   pts     ! T & S fields      [Celsius ; g/kg]
55      REAL(wp), DIMENSION(jpi,jpj,jpk)     , INTENT(  out) ::   pu      ! i-component of the velocity  [m/s]
56      REAL(wp), DIMENSION(jpi,jpj,jpk)     , INTENT(  out) ::   pv      ! j-component of the velocity  [m/s]
57      !
58      INTEGER  :: ji,jj,jk     ! dummy loop indices
59      REAL(wp) :: zdt, zn2, zrho1, zdb, zh, zstar, zxw, zro, zhe, zh0, zf
60      REAL(wp) :: zri1, zri2, zri, ztd, ztu
61      !!----------------------------------------------------------------------
62      !
63      IF(lwp) WRITE(numout,*)
64      IF(lwp) WRITE(numout,*) 'usr_def_istate : DOME configuration, analytical definition of initial state'
65      IF(lwp) WRITE(numout,*) '~~~~~~~~~~~~~~   Ocean at rest, filled with a constant stratification '
66      IF(lwp) WRITE(numout,*) '                 salinity is used as a passive tracer here, initially=0' 
67      IF(lwp) WRITE(numout,*) '                 and set to 1 inside inlet' 
68      !
69      !
70      pu  (:,:,:) = 0._wp        ! ocean at rest
71      pv  (:,:,:) = 0._wp
72      pts(:,:,:,:) = 0._wp
73      !
74      zn2 = (2.3e-3)**2 ! brunt vaisala squared
75      zdb = 0.019       ! buoyancy anomaly
76      zh0 = 300._wp
77      zhe = 600._wp
78      zro = sqrt(zdb*zh0) / 1.e-4 ! Rossby radius
79      zri = 1._wp/3._wp 
80      zri1 =  zri / (2._wp-zri)
81      zri2 = -zri / (2._wp+zri) 
82      !                          ! T & S profiles
83      DO_2D( 1, 1, 1, 1 )
84         DO jk = 1, jpkm1
85            zdt =  pdept(ji,jj,jk)
86            zxw = (glamt(ji,jj) + 50._wp) * 1.e3 ! Distance from western wall
87            zh = zh0 * exp(-zxw/zro) 
88!            zstar = (zdt - zh - zhe) / zh
89!            IF (zstar.ge.zri1 ) THEN
90!               zf = 1._wp
91!            ELSEIF ( (zstar.gt.zri2).AND.(zstar.lt.zri1) ) THEN
92!               zf = zstar/(1._wp+zstar)/zri + 0.5_wp
93!            ELSE
94!               zf = 0._wp
95!            ENDIF
96            IF (zdt > zhe-zh) THEN
97               zf = 0._wp
98            ELSE
99               zf = 1._wp
100            ENDIF   
101            zrho1 = rho0*zn2*zdt/grav/rn_a0
102            pts(ji,jj,jk,jp_tem) = (15._wp - zrho1) * ptmask(ji,jj,jk)
103! Mass conserving initialization:
104            ztd = 15._wp*gdepw_0(ji,jj,jk+1)-0.5*rho0*zn2/(rn_a0*grav)*gdepw_0(ji,jj,jk+1)**2
105            ztu = 15._wp*gdepw_0(ji,jj,jk  )-0.5*rho0*zn2/(rn_a0*grav)*gdepw_0(ji,jj,jk  )**2
106            pts(ji,jj,jk,jp_tem) = (ztd - ztu)/e3t_0(ji,jj,jk) * ptmask(ji,jj,jk)
107            IF (Agrif_root().AND.(  mjg0(jj) == Nj0glo-2 ) )  THEN
108               pv(ji,jj,jk) = -sqrt(zdb*zh0)*exp(-zxw/zro)*(1._wp-zf) * ptmask(ji,jj,jk)
109            ENDIF
110            IF (Agrif_root().AND.(  mjg0(jj) == Nj0glo-1 ) )  THEN
111               pts(ji,jj,jk,jp_tem) = MIN(pts(ji,jj,jk,jp_tem), 15._wp - zdb*rho0/grav/rn_a0*(1._wp-zf)) * ptmask(ji,jj,jk) 
112               pts(ji,jj,jk,jp_sal) = 1._wp * ptmask(ji,jj,jk) 
113            ENDIF
114         END DO
115      END_2D
116      !   
117   END SUBROUTINE usr_def_istate
118
119 
120   SUBROUTINE usr_def_istate_ssh( ptmask, pssh )
121      !!----------------------------------------------------------------------
122      !!                   ***  ROUTINE usr_def_istate  ***
123      !!
124      !! ** Purpose :   Initialization of ssh
125      !!                Here DOME configuration
126      !!
127      !! ** Method  :   set no initial sea level anomaly
128      !! 
129      !!----------------------------------------------------------------------
130      REAL(wp), DIMENSION(jpi,jpj,jpk)     , INTENT(in   ) ::   ptmask  !
131      REAL(wp), DIMENSION(jpi,jpj)         , INTENT(  out) ::   pssh    !
132      !
133      !!----------------------------------------------------------------------
134      !
135      pssh(:,:) = 0._wp
136      !
137   END SUBROUTINE usr_def_istate_ssh
138
139   !!======================================================================
140END MODULE usrdef_istate
Note: See TracBrowser for help on using the repository browser.