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 branches/UKMO/r8727_WAVE-2_Clementi_add_coupling/NEMOGCM/CONFIG/TEST_CASES/LOCK_EXCHANGE/MY_SRC – NEMO

source: branches/UKMO/r8727_WAVE-2_Clementi_add_coupling/NEMOGCM/CONFIG/TEST_CASES/LOCK_EXCHANGE/MY_SRC/usrdef_istate.F90 @ 8749

Last change on this file since 8749 was 8749, checked in by jcastill, 6 years ago

Remove svn keywords

File size: 3.9 KB
Line 
1MODULE usrdef_istate
2   !!======================================================================
3   !!                     ***  MODULE usrdef_istate   ***
4   !!
5   !!                  ===  LOCK_EXCHANGE 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   !!----------------------------------------------------------------------
11
12   !!----------------------------------------------------------------------
13   !!  usr_def_istate : initial state in Temperature and salinity
14   !!----------------------------------------------------------------------
15   USE par_oce        ! ocean space and time domain
16   USE dom_oce , ONLY : glamt 
17   USE phycst         ! physical constants
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
27   !!----------------------------------------------------------------------
28   !! NEMO/OPA 4.0 , NEMO Consortium (2016)
29   !! $Id$
30   !! Software governed by the CeCILL licence     (NEMOGCM/NEMO_CeCILL.txt)
31   !!----------------------------------------------------------------------
32CONTAINS
33 
34   SUBROUTINE usr_def_istate( pdept, ptmask, pts, pu, pv, pssh )
35      !!----------------------------------------------------------------------
36      !!                   ***  ROUTINE usr_def_istate  ***
37      !!
38      !! ** Purpose :   Initialization of the dynamics and tracers
39      !!                Here LOCK_EXCHANGE configuration
40      !!
41      !! ** Method  : - set temprature field
42      !!              - set salinity   field
43      !!----------------------------------------------------------------------
44      REAL(wp), DIMENSION(jpi,jpj,jpk)     , INTENT(in   ) ::   pdept   ! depth of t-point               [m]
45      REAL(wp), DIMENSION(jpi,jpj,jpk)     , INTENT(in   ) ::   ptmask  ! t-point ocean mask             [m]
46      REAL(wp), DIMENSION(jpi,jpj,jpk,jpts), INTENT(  out) ::   pts     ! T & S fields      [Celsius ; g/kg]
47      REAL(wp), DIMENSION(jpi,jpj,jpk)     , INTENT(  out) ::   pu      ! i-component of the velocity  [m/s]
48      REAL(wp), DIMENSION(jpi,jpj,jpk)     , INTENT(  out) ::   pv      ! j-component of the velocity  [m/s]
49      REAL(wp), DIMENSION(jpi,jpj)         , INTENT(  out) ::   pssh    ! sea-surface height
50      !
51      INTEGER  ::   jk     ! dummy loop indices
52      REAL(wp) ::   zdam   ! location of dam [Km]
53      !!----------------------------------------------------------------------
54      !
55      IF(lwp) WRITE(numout,*)
56      IF(lwp) WRITE(numout,*) 'usr_def_istate : LOCK_EXCHANGE configuration, analytical definition of initial state'
57      IF(lwp) WRITE(numout,*) '~~~~~~~~~~~~~~   Ocean at rest, with a constant salinity (not used as rho=F(T) '
58      IF(lwp) WRITE(numout,*) '                 and a vertical density front with a 5 kg/m3 difference located at glam=32km'
59      IF(lwp) WRITE(numout,*) '                 (i.e. a temperature difference of 25 degrees with rn_a0 = 0.2'
60      !
61      !  rn_a0 =  0.2   !  thermal expension coefficient (nn_eos= 1)
62      !  rho = rau0 - rn_a0 * (T-10)
63      !  delta_T = 25 degrees  ==>>  delta_rho = 25 * rn_a0 = 5 kg/m3
64      !
65      pu  (:,:,:) = 0._wp        ! ocean at rest
66      pv  (:,:,:) = 0._wp
67      pssh(:,:)   = 0._wp
68      !
69      !                          ! T & S profiles
70      zdam = 32.                      ! density front position in kilometers
71      pts(:,:,:,jp_tem) = 30._wp * ptmask(:,:,:)
72      DO jk = 1, jpkm1
73         WHERE( glamt(:,:) <= zdam )   pts(:,:,jk,jp_tem) = 5._wp * ptmask(:,:,jk)
74      END DO
75      !
76      pts(:,:,:,jp_sal) = 35._wp * ptmask(:,:,:)
77      !   
78   END SUBROUTINE usr_def_istate
79
80   !!======================================================================
81END MODULE usrdef_istate
Note: See TracBrowser for help on using the repository browser.