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/2018/dev_r9759_HPC09_ESIWACE/tests/BENCH/MY_SRC – NEMO

source: NEMO/branches/2018/dev_r9759_HPC09_ESIWACE/tests/BENCH/MY_SRC/usrdef_istate.F90 @ 10102

Last change on this file since 10102 was 10102, checked in by smasson, 6 years ago

dev_r9759_HPC09_ESIWACE: update usrdef_istate.F90 to define unique value on each point

File size: 3.9 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
30   !!----------------------------------------------------------------------
31   !! NEMO/OPA 4.0 , NEMO Consortium (2016)
32   !! $Id$
33   !! Software governed by the CeCILL licence     (NEMOGCM/NEMO_CeCILL.txt)
34   !!----------------------------------------------------------------------
35CONTAINS
36 
37   SUBROUTINE usr_def_istate( pdept, ptmask, pts, pu, pv, pssh )
38      !!----------------------------------------------------------------------
39      !!                   ***  ROUTINE usr_def_istate  ***
40      !!
41      !! ** Purpose :   Initialization of the dynamics and tracers
42      !!                Here BENCH configuration
43      !!
44      !! ** Method  :   Set a gaussian anomaly of pressure and associated
45      !!                geostrophic velocities
46      !!----------------------------------------------------------------------
47      REAL(wp), DIMENSION(jpi,jpj,jpk)     , INTENT(in   ) ::   pdept   ! depth of t-point               [m]
48      REAL(wp), DIMENSION(jpi,jpj,jpk)     , INTENT(in   ) ::   ptmask  ! t-point ocean mask             [m]
49      REAL(wp), DIMENSION(jpi,jpj,jpk,jpts), INTENT(  out) ::   pts     ! T & S fields      [Celsius ; g/kg]
50      REAL(wp), DIMENSION(jpi,jpj,jpk)     , INTENT(  out) ::   pu      ! i-component of the velocity  [m/s]
51      REAL(wp), DIMENSION(jpi,jpj,jpk)     , INTENT(  out) ::   pv      ! j-component of the velocity  [m/s]
52      REAL(wp), DIMENSION(jpi,jpj)         , INTENT(  out) ::   pssh    ! sea-surface height
53      !
54      REAL(wp), DIMENSION(jpi,jpj) ::   z2d   ! 2D workspace
55      INTEGER :: ji, jj, jk
56      !!----------------------------------------------------------------------
57      !
58      IF(lwp) WRITE(numout,*)
59      IF(lwp) WRITE(numout,*) 'usr_def_istate : BENCH configuration, analytical definition of initial state'
60      IF(lwp) WRITE(numout,*) '~~~~~~~~~~~~~~   '
61      !
62      ! define unique value on each point
63      DO jj = 1, jpj
64         DO ji = 1, jpi
65            z2d(ji,jj) = ( 0.5_wp - REAL( nimpp + ji - 1 + ( njmpp + jj - 2 ) * jpiglo) / REAL ( jpiglo * jpjglo ) ) * 0.1_wp
66         ENDDO
67      ENDDO
68      !
69      ! sea level:
70      pssh(:,:) = z2d(:,:)
71      !
72      DO jk = 1, jpk
73         ! temperature:
74         pts(:,:,jk,jp_tem) = 10._wp + z2d(:,:) * 2._wp
75         ! salinity: 
76         pts(:,:,jk,jp_sal) = 35._wp + z2d(:,:)
77         ! velocities:
78         pu(:,:,jk) = z2d(:,:) * 0.1_wp
79         pv(:,:,jk) = z2d(:,:) * 0.01_wp
80      ENDDO
81      !
82      CALL lbc_lnk("usr_def_istate", pssh, 'T',  1. )            ! apply boundary conditions
83      CALL lbc_lnk("usr_def_istate",  pts, 'T',  1. )            ! apply boundary conditions
84      CALL lbc_lnk("usr_def_istate",   pu, 'U', -1. )            ! apply boundary conditions
85      CALL lbc_lnk("usr_def_istate",   pv, 'V', -1. )            ! apply boundary conditions
86     
87   END SUBROUTINE usr_def_istate
88
89   !!======================================================================
90END MODULE usrdef_istate
Note: See TracBrowser for help on using the repository browser.