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/ROMS_WAD_7832/NEMOGCM/CONFIG/CS15mini/MY_SRC – NEMO

source: branches/UKMO/ROMS_WAD_7832/NEMOGCM/CONFIG/CS15mini/MY_SRC/usrdef_istate.F90 @ 8544

Last change on this file since 8544 was 8544, checked in by deazer, 7 years ago

Added reference level (above all potential wet points) to avoid negative depth bathymetry as a work around.
Require reference level to be emedded into the domain configuration file
uses ht_0 instead of ht_wd. This si still in the code but should be removed in time.

File size: 5.2 KB
Line 
1MODULE usrdef_istate
2   !!======================================================================
3   !!                   ***  MODULE  usrdef_istate   ***
4   !!
5   !!                     ===  GYRE 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        ! ocean space and time domain
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   
23   IMPLICIT NONE
24   PRIVATE
25
26   PUBLIC   usr_def_istate   ! called in istate.F90
27
28   !!----------------------------------------------------------------------
29   !! NEMO/OPA 4.0 , NEMO Consortium (2016)
30   !! $Id$
31   !! Software governed by the CeCILL licence     (NEMOGCM/NEMO_CeCILL.txt)
32   !!----------------------------------------------------------------------
33CONTAINS
34 
35   SUBROUTINE usr_def_istate( pdept, ptmask, pts, pu, pv, pssh )
36      !!----------------------------------------------------------------------
37      !!                   ***  ROUTINE usr_def_istate  ***
38      !!
39      !! ** Purpose :   Initialization of the dynamics and tracers
40      !!                Here GYRE configuration example : (double gyre with rotated domain)
41      !!
42      !! ** Method  : - set temprature field
43      !!              - set salinity   field
44      !!----------------------------------------------------------------------
45      REAL(wp), DIMENSION(jpi,jpj,jpk)     , INTENT(in   ) ::   pdept   ! depth of t-point               [m]
46      REAL(wp), DIMENSION(jpi,jpj,jpk)     , INTENT(in   ) ::   ptmask  ! t-point ocean mask             [m]
47      REAL(wp), DIMENSION(jpi,jpj,jpk,jpts), INTENT(  out) ::   pts     ! T & S fields      [Celsius ; g/kg]
48      REAL(wp), DIMENSION(jpi,jpj,jpk)     , INTENT(  out) ::   pu      ! i-component of the velocity  [m/s]
49      REAL(wp), DIMENSION(jpi,jpj,jpk)     , INTENT(  out) ::   pv      ! j-component of the velocity  [m/s]
50      REAL(wp), DIMENSION(jpi,jpj)         , INTENT(  out) ::   pssh    ! sea-surface height
51      !
52      INTEGER :: ji, jj, jk  ! dummy loop indices
53      !!----------------------------------------------------------------------
54      !
55      IF(lwp) WRITE(numout,*)
56      IF(lwp) WRITE(numout,*) 'usr_def_istate : analytical definition of initial state '
57      IF(lwp) WRITE(numout,*) '~~~~~~~~~~~~~~   Ocean at rest, with an horizontally uniform T and S profiles'
58      !
59      pu  (:,:,:) = 0._wp        ! ocean at rest
60      pv  (:,:,:) = 0._wp
61      pssh(:,:)   = 0._wp
62      !
63      DO jk = 1, jpk             ! horizontally uniform T & S profiles
64         DO jj = 1, jpj
65            DO ji = 1, jpi
66               pts(ji,jj,jk,jp_tem) =  (  (  16. - 12. * TANH( (pdept(ji,jj,jk) - 400) / 700 ) )   &
67                    &           * (-TANH( (500. - pdept(ji,jj,jk)) / 150. ) + 1.) / 2.             &
68                    &           + ( 15. * ( 1. - TANH( (pdept(ji,jj,jk)-50.) / 1500.) )            &
69                    &           - 1.4 * TANH((pdept(ji,jj,jk)-100.) / 100.)                        &
70                    &           + 7.  * (1500. - pdept(ji,jj,jk) ) / 1500.)                        &
71                    &           * (-TANH( (pdept(ji,jj,jk) - 500.) / 150.) + 1.) / 2.  ) * ptmask(ji,jj,jk)
72
73               pts(ji,jj,jk,jp_sal) =  (  (  36.25 - 1.13 * TANH( (pdept(ji,jj,jk) - 305) / 460 ) )  &
74                    &         * (-TANH((500. - pdept(ji,jj,jk)) / 150.) + 1.) / 2                  &
75                    &         + ( 35.55 + 1.25 * (5000. - pdept(ji,jj,jk)) / 5000.                 &
76                    &         - 1.62 * TANH( (pdept(ji,jj,jk) - 60.  ) / 650. )                    &
77                    &         + 0.2  * TANH( (pdept(ji,jj,jk) - 35.  ) / 100. )                    &
78                    &         + 0.2  * TANH( (pdept(ji,jj,jk) - 1000.) / 5000.) )                  &
79                    &         * (-TANH( (pdept(ji,jj,jk) - 500.) / 150.) + 1.) / 2  ) * ptmask(ji,jj,jk)
80               pts(ji,jj,jk,jp_tem) = 10. * ptmask(ji,jj,jk) ! slwa constant temperature ic
81               pts(ji,jj,jk,jp_sal) = 35. * ptmask(ji,jj,jk) ! slwa constant salinity ic
82            END DO
83         END DO
84      END DO
85      !   
86
87! subtract the height of z=0 above the geoid (this allows z = 0 to be higher than all points that may become wet)   
88      pssh(:,:) =  -rn_ssh_ref
89
90      !
91      ! Apply minimum wetdepth criterion
92      !
93      do jj = 1,jpj
94         do ji = 1,jpi
95            IF( ht_0(ji,jj) + pssh(ji,jj)  < rn_wdmin1 ) THEN
96               pssh(ji,jj) = ptmask(ji,jj,1)*( rn_wdmin1 - (ht_0(ji,jj)) )
97            ENDIF
98         end do
99      end do
100     !
101   END SUBROUTINE usr_def_istate
102
103   !!======================================================================
104END MODULE usrdef_istate
Note: See TracBrowser for help on using the repository browser.