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

source: NEMO/trunk/tests/OVERFLOW/MY_SRC/usrdef_istate.F90

Last change on this file was 14053, checked in by techene, 3 years ago

#2385 added to the trunk

  • Property svn:keywords set to Id
File size: 4.8 KB
Line 
1MODULE usrdef_istate
2   !!==============================================================================
3   !!                       ***  MODULE usrdef_istate  ***
4   !!
5   !!                      ===  OVERFLOW configuration  ===
6   !!
7   !! User defined : set the initial state of a user configuration
8   !!==============================================================================
9   !! History :  NEMO ! 2016-03  (S. Flavoni, G. Madec) Original code
10   !!                 ! 2020-11  (S. Techene, G. Madec) separate tsuv from ssh
11   !!----------------------------------------------------------------------
12
13   !!----------------------------------------------------------------------
14   !!  usr_def_istate : initial state in Temperature and salinity
15   !!----------------------------------------------------------------------
16   USE par_oce        ! ocean space and time domain
17   USE dom_oce , ONLY : glamt 
18   USE phycst         ! physical constants
19   !
20   USE in_out_manager ! I/O manager
21   USE lib_mpp        ! MPP library
22   
23   IMPLICIT NONE
24   PRIVATE
25
26   PUBLIC   usr_def_istate       ! called by istate.F90
27   PUBLIC   usr_def_istate_ssh   ! called by domqco.F90
28   
29   !!----------------------------------------------------------------------
30   !! NEMO/OCE 4.0 , NEMO Consortium (2018)
31   !! $Id$
32   !! Software governed by the CeCILL license (see ./LICENSE)
33   !!----------------------------------------------------------------------
34CONTAINS
35 
36   SUBROUTINE usr_def_istate( pdept, ptmask, pts, pu, pv )
37      !!----------------------------------------------------------------------
38      !!                   ***  ROUTINE usr_def_istate  ***
39      !!
40      !! ** Purpose :   Initialization of the dynamics and tracers
41      !!                Here OVERFLOW configuration
42      !!
43      !! ** Method  : - set temprature field
44      !!              - set salinity   field
45      !!----------------------------------------------------------------------
46      REAL(wp), DIMENSION(jpi,jpj,jpk)     , INTENT(in   ) ::   pdept   ! depth of t-point               [m]
47      REAL(wp), DIMENSION(jpi,jpj,jpk)     , INTENT(in   ) ::   ptmask  ! t-point ocean mask             [m]
48      REAL(wp), DIMENSION(jpi,jpj,jpk,jpts), INTENT(  out) ::   pts     ! T & S fields      [Celsius ; g/kg]
49      REAL(wp), DIMENSION(jpi,jpj,jpk)     , INTENT(  out) ::   pu      ! i-component of the velocity  [m/s]
50      REAL(wp), DIMENSION(jpi,jpj,jpk)     , INTENT(  out) ::   pv      ! j-component of the velocity  [m/s]
51      !
52      INTEGER  ::   jk     ! dummy loop indices
53      REAL(wp) ::   zdam   ! location of dam [Km]
54      !!----------------------------------------------------------------------
55      !
56      IF(lwp) WRITE(numout,*)
57      IF(lwp) WRITE(numout,*) 'usr_def_istate : OVERFLOW configuration, analytical definition of initial state'
58      IF(lwp) WRITE(numout,*) '~~~~~~~~~~~~~~   Ocean at rest, with a constant salinity (not used as rho=F(T) '
59      IF(lwp) WRITE(numout,*) '                 and a vertical density front with a 2 kg/m3 difference located at glam=20km'
60      IF(lwp) WRITE(numout,*) '                 (i.e. a temperature difference of 10 degrees with rn_a0 = 0.2'
61      !
62      !  rn_a0 =  0.2   !  thermal expension coefficient (nn_eos= 1)
63      !  rho = rho0 - rn_a0 * (T-10)
64      !  delta_T = 10 degrees  ==>>  delta_rho = 10 * rn_a0 = 2 kg/m3
65      !
66      pu  (:,:,:) = 0._wp        ! ocean at rest
67      pv  (:,:,:) = 0._wp
68      !
69      !                          ! T & S profiles
70      zdam = 20.                      ! density front position in kilometers
71      pts(:,:,:,jp_tem) = 20._wp * ptmask(:,:,:)
72      DO jk = 1, jpkm1
73         WHERE( glamt(:,:) <= zdam )   pts(:,:,jk,jp_tem) = 10._wp * ptmask(:,:,jk)
74      END DO
75      !
76      pts(:,:,:,jp_sal) = 35._wp * ptmask(:,:,:)
77      !   
78   END SUBROUTINE usr_def_istate
79
80
81   SUBROUTINE usr_def_istate_ssh( ptmask, pssh )
82      !!----------------------------------------------------------------------
83      !!                   ***  ROUTINE usr_def_istate_ssh  ***
84      !!
85      !! ** Purpose :   Initialization of the ssh
86      !!                Here  OVERFLOW configuration
87      !!
88      !! ** Method  :   set ssh to 0
89      !!----------------------------------------------------------------------
90      REAL(wp), DIMENSION(jpi,jpj,jpk)     , INTENT(in   ) ::   ptmask  ! t-point ocean mask   [m]
91      REAL(wp), DIMENSION(jpi,jpj)         , INTENT(  out) ::   pssh    ! sea-surface height   [m]
92      !!----------------------------------------------------------------------
93      !
94      IF(lwp) WRITE(numout,*)
95      IF(lwp) WRITE(numout,*) 'usr_def_istate_ssh : OVERFLOW configuration, analytical definition of initial state'
96      !
97      pssh(:,:)   = 0._wp
98      !
99   END SUBROUTINE usr_def_istate_ssh
100
101   !!======================================================================
102END MODULE usrdef_istate
Note: See TracBrowser for help on using the repository browser.