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/2020/dev_r13327_KERNEL-06_2_techene_e3/tests/BENCH/MY_SRC – NEMO

source: NEMO/branches/2020/dev_r13327_KERNEL-06_2_techene_e3/tests/BENCH/MY_SRC/usrdef_istate.F90 @ 13762

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

#2385 set ssh separately from istate variables to remove domqco.F90 duplicates

File size: 6.2 KB
Line 
1MODULE usrdef_istate
2   !!======================================================================
3   !!                     ***  MODULE usrdef_istate   ***
4   !!
5   !!                      ===  BENCH configuration  ===
6   !!
7   !! User defined : set the initial state of a user configuration
8   !!======================================================================
9   !! History :  NEMO !
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       
17   USE phycst         ! physical constants
18   !
19   USE in_out_manager ! I/O manager
20   USE lib_mpp        ! MPP library
21   USE lbclnk          ! lateral boundary conditions - mpp exchanges
22   !   
23   USE usrdef_nam
24   
25   IMPLICIT NONE
26   PRIVATE
27
28   PUBLIC   usr_def_istate   ! called by istate.F90
29   PUBLIC   usr_def_ssh      ! called by domqco.F90
30
31   !! * Substitutions
32#  include "do_loop_substitute.h90"
33   !!----------------------------------------------------------------------
34   !! NEMO/OPA 4.0 , NEMO Consortium (2016)
35   !! $Id$
36   !! Software governed by the CeCILL licence     (NEMOGCM/NEMO_CeCILL.txt)
37   !!----------------------------------------------------------------------
38CONTAINS
39 
40   SUBROUTINE usr_def_istate( pdept, ptmask, pts, pu, pv, pssh )
41      !!----------------------------------------------------------------------
42      !!                   ***  ROUTINE usr_def_istate  ***
43      !!
44      !! ** Purpose :   Initialization of the dynamics and tracers
45      !!                Here BENCH configuration
46      !!
47      !! ** Method  :   Set a gaussian anomaly of pressure and associated
48      !!                geostrophic velocities
49      !!----------------------------------------------------------------------
50      REAL(wp), DIMENSION(jpi,jpj,jpk)     , INTENT(in   ) ::   pdept   ! depth of t-point               [m]
51      REAL(wp), DIMENSION(jpi,jpj,jpk)     , INTENT(in   ) ::   ptmask  ! t-point ocean mask             [m]
52      REAL(wp), DIMENSION(jpi,jpj,jpk,jpts), INTENT(  out) ::   pts     ! T & S fields      [Celsius ; g/kg]
53      REAL(wp), DIMENSION(jpi,jpj,jpk)     , INTENT(  out) ::   pu      ! i-component of the velocity  [m/s]
54      REAL(wp), DIMENSION(jpi,jpj,jpk)     , INTENT(  out) ::   pv      ! j-component of the velocity  [m/s]
55      REAL(wp), DIMENSION(jpi,jpj)         , INTENT(  out) ::   pssh    ! sea-surface height
56      !
57      REAL(wp), DIMENSION(jpi,jpj) ::   z2d   ! 2D workspace
58      REAL(wp) ::   zfact
59      INTEGER  ::   ji, jj, jk
60      INTEGER  ::   igloi, igloj   ! to be removed in the future, see comment bellow
61      !!----------------------------------------------------------------------
62      !
63      IF(lwp) WRITE(numout,*)
64      IF(lwp) WRITE(numout,*) 'usr_def_istate : BENCH configuration, analytical definition of initial state'
65      IF(lwp) WRITE(numout,*) '~~~~~~~~~~~~~~   '
66      !
67      ! define unique value on each point of the inner global domain. z2d ranging from 0.05 to -0.05
68      !
69      ! WARNING: to keep compatibility with the trunk that was including periodocity into the input data,
70      ! we must define z2d as bellow.
71      ! Once we decide to forget trunk compatibility, we must simply define z2d as:
72!!$      DO_2D( 0, 0, 0, 0 )
73!!$         z2d(ji,jj) = 0.1 * ( 0.5 - REAL( mig0_oldcmp(ji) + (mjg0_oldcmp(jj)-1) * Ni0glo, wp ) / REAL( Ni0glo * Nj0glo, wp ) )
74!!$      END_2D
75      igloi = Ni0glo + 2 * COUNT( (/ jperio == 1 .OR. jperio == 4 .OR. jperio == 6 .OR. jperio == 7 /) )
76      igloj = Nj0glo + 2 * COUNT( (/ jperio == 2 .OR. jperio == 7 /) ) + 1 * COUNT( (/ jperio >= 4 .AND. jperio <= 6 /) )
77      DO_2D( 0, 0, 0, 0 )
78         z2d(ji,jj) = 0.1 * ( 0.5 - REAL( mig0_oldcmp(ji) + (mjg0_oldcmp(jj)-1) * igloi, wp ) / REAL( igloi * igloj, wp ) )
79      END_2D
80      !
81      ! sea level:
82      pssh(:,:) = z2d(:,:)                                                ! +/- 0.05 m
83      !
84      DO_3D( 0, 0, 0, 0, 1, jpkm1 )
85         zfact = REAL(jk-1,wp) / REAL(jpk-1,wp)   ! 0 to 1 to add a basic stratification
86         ! temperature choosen to lead to ~50% ice at the beginning if rn_thres_sst = 0.5
87         pts(:,:,jk,jp_tem) = 20._wp*z2d(:,:) - 1._wp - 0.5_wp * zfact    ! -1 to -1.5 +/-1.0 degG
88         ! salinity: 
89         pts(:,:,jk,jp_sal) = 30._wp + 1._wp * zfact + z2d(:,:)           ! 30 to 31 +/- 0.05 psu
90         ! velocities:
91         pu(:,:,jk) = z2d(:,:) *  0.1_wp * umask(:,:,jk)                  ! +/- 0.005  m/s
92         pv(:,:,jk) = z2d(:,:) * 0.01_wp * vmask(:,:,jk)                  ! +/- 0.0005 m/s
93      END_3D
94      pts(:,:,jpk,:) = 0._wp
95      pu( :,:,jpk  ) = 0._wp
96      pv( :,:,jpk  ) = 0._wp
97      !
98      CALL lbc_lnk('usrdef_istate', pssh, 'T',  1. )            ! apply boundary conditions
99      CALL lbc_lnk('usrdef_istate',  pts, 'T',  1. )            ! apply boundary conditions
100      CALL lbc_lnk('usrdef_istate',   pu, 'U', -1. )            ! apply boundary conditions
101      CALL lbc_lnk('usrdef_istate',   pv, 'V', -1. )            ! apply boundary conditions
102     
103   END SUBROUTINE usr_def_istate
104
105
106   SUBROUTINE usr_def_ssh( ptmask, pssh )
107      !!----------------------------------------------------------------------
108      !!                   ***  ROUTINE usr_def_ssh  ***
109      !!
110      !! ** Purpose :   Initialization of ssh
111      !!                Here BENCH configuration
112      !!
113      !! ** Method  :   Set ssh
114      !!----------------------------------------------------------------------
115      REAL(wp), DIMENSION(jpi,jpj,jpk)     , INTENT(in   ) ::   ptmask  ! t-point ocean mask   [m]
116      REAL(wp), DIMENSION(jpi,jpj)         , INTENT(  out) ::   pssh    ! sea-surface height   [m]
117      !!----------------------------------------------------------------------
118      !
119      IF(lwp) WRITE(numout,*)
120      IF(lwp) WRITE(numout,*) 'usr_def_ssh : BENCH configuration, analytical definition of initial state'
121      !
122      pssh(:,:)   = 0._wp 
123      !
124   END SUBROUTINE usr_def_ssh
125   
126   !!======================================================================
127END MODULE usrdef_istate
Note: See TracBrowser for help on using the repository browser.