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/branches/UKMO/NEMO_4.0.2_SEAMOUNT/tests/SEAMOUNT/MY_SRC – NEMO

source: NEMO/branches/UKMO/NEMO_4.0.2_SEAMOUNT/tests/SEAMOUNT/MY_SRC/usrdef_istate.F90 @ 12868

Last change on this file since 12868 was 12868, checked in by ayoung, 4 years ago

SEAMOUNT configuration files (EXPREF and MY_SRC)

File size: 4.0 KB
Line 
1MODULE usrdef_istate
2   !!======================================================================
3   !!                     ***  MODULE usrdef_istate   ***
4   !!
5   !!                  ===  WAD_TEST_CASES configuration  ===
6   !!
7   !! User defined : set the initial state of a user configuration
8   !!======================================================================
9   !! History :  4.0 ! 2016-03  (S. Flavoni) 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 : mi0, mig, mjg, glamt, gphit, ht_0
17   USE phycst         ! physical constants
18   USE wet_dry        ! Wetting and drying
19   !
20   USE in_out_manager ! I/O manager
21   USE lib_mpp        ! MPP library
22   USE usrdef_nam
23
24   IMPLICIT NONE
25   PRIVATE
26
27   PUBLIC   usr_def_istate   ! called in istate.F90
28
29   !!----------------------------------------------------------------------
30   !! NEMO/OCE 4.0 , NEMO Consortium (2018)
31   !! $Id: usrdef_istate.F90 10074 2018-08-28 16:15:49Z nicolasmartin $
32   !! Software governed by the CeCILL license (see ./LICENSE)
33   !!----------------------------------------------------------------------
34CONTAINS
35 
36   SUBROUTINE usr_def_istate( pdept, ptmask, pts, pu, pv, pssh )
37      !!----------------------------------------------------------------------
38      !!                   ***  ROUTINE usr_def_istate  ***
39      !!
40      !! ** Purpose :   Initialization of the dynamics and tracers
41      !!                Here WAD_TEST_CASES 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      REAL(wp), DIMENSION(jpi,jpj)         , INTENT(  out) ::   pssh    ! sea-surface height
52      INTEGER  ::   ji, jj            ! dummy loop indices
53      REAL(wp) ::   zi, zj
54      !
55      INTEGER  ::   jk     ! dummy loop indices
56      REAL(wp) ::   zdam   ! location of dam [Km]
57      REAL(wp) ::   rn_a0
58      !!----------------------------------------------------------------------
59      !
60      IF(lwp) WRITE(numout,*)
61      IF(lwp) WRITE(numout,*) 'usr_def_istate : SEAMOUNT_TEST_CASE configuration, analytical definition of initial state'
62      IF(lwp) WRITE(numout,*) '~~~~~~~~~~~~~~   Ocean at rest, with an initial density profile = rho_ref + rho_pert     '
63      IF(lwp) WRITE(numout,*) '                 defined via temperature.  Constant salinity (not used as rho=F(T)       '
64      !
65      rn_a0 = 0.16550_wp
66      IF(lwp) WRITE(numout,*) '                 Surface-floor density delta for Burger number S = ', rn_s, ' is rho_delta = ', rn_drho 
67      !
68      pu  (:,:,:) = 0._wp        ! ocean at rest
69      pv  (:,:,:) = 0._wp
70      pssh(:,:)   = 0._wp
71      !
72      !                          ! T & S profiles
73      DO jk = 1, jpk
74         pts(:,:,jk,jp_tem) = - ptmask(:,:,jk) * ( 28._wp - rn_drho * EXP( - pdept(:,:,jk) / 1000._wp ) - rn_initrho * EXP( - pdept(:,:,jk) / 1000._wp ) ) / rn_a0
75      END DO
76      !
77      pts(:,:,:,jp_sal) = 35._wp * ptmask(:,:,:)
78      !!----------------------------------------------------------------------
79      !
80   END SUBROUTINE usr_def_istate
81
82   !!======================================================================
83END MODULE usrdef_istate
Note: See TracBrowser for help on using the repository browser.