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.4_idealised_ovf/src/OCE/USR – NEMO

source: NEMO/branches/UKMO/NEMO_4.0.4_idealised_ovf/src/OCE/USR/usrdef_istate.F90 @ 15156

Last change on this file since 15156 was 15156, checked in by dbruciaferri, 3 years ago

adding initial condition for Denmark Strait

File size: 4.8 KB
Line 
1MODULE usrdef_istate
2   !!======================================================================
3   !!                   ***  MODULE  usrdef_istate   ***
4   !!
5   !!          ===  NORTH ATALNTIC ORCA025 IDEALISED OVERFLOWS  ===
6   !!
7   !! User defined : set the initial state of a user configuration
8   !!======================================================================
9   !! History :  4.0    ! 2016-03  (S. Flavoni) Original code
10   !!            4.0.4  ! 2021-07  (D. Bruciaferri) Overflows code
11   !!----------------------------------------------------------------------
12
13   !!----------------------------------------------------------------------
14   !!  usr_def_istate : initial state in Temperature and salinity
15   !!----------------------------------------------------------------------
16   USE par_oce        ! ocean space and time domain
17   USE phycst         ! physical constants
18   USE dom_oce
19   USE dtatsd     
20   !
21   USE in_out_manager ! I/O manager
22   USE lib_mpp        ! MPP library
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$
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      !!                North Atlantic idealised overflows
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      !
53      INTEGER                                              ::   ji, jj, kk, num_pnt, ierr0, ierr1
54      INTEGER, ALLOCATABLE                 , DIMENSION(:)  ::   ovf_ji, ovf_jj ! arrays for overflow
55      !!----------------------------------------------------------------------
56      !
57      IF(lwp) WRITE(numout,*)
58      IF(lwp) WRITE(numout,*) 'usr_def_istate : analytical definition of initial state '
59      IF(lwp) WRITE(numout,*) '~~~~~~~~~~~~~~   Ocean at rest, with a 3D uniform T and S'
60      IF(lwp) WRITE(numout,*) '                 and cold dense blobs in the DS and/or IFR'
61      !
62      pu  (:,:,:) = 0._wp        ! ocean at rest
63      pv  (:,:,:) = 0._wp
64      pssh(:,:)   = 0._wp
65      !
66      ! 3D uniform T & S profiles
67      pts(:, :, :, jp_tem) = rn_tem_env
68      pts(:, :, :, jp_sal) = rn_sal_env
69      !
70      SELECT CASE(nn_ovf_loc)
71
72         CASE(0) ! Denmark Strait
73            num_pnt = 17
74            ALLOCATE( ovf_ji(num_pnt), STAT=ierr0 )
75            ALLOCATE( ovf_jj(num_pnt), STAT=ierr1 )
76            IF( ierr0 + ierr1 > 0 ) THEN
77               CALL ctl_stop( 'dta_tsd : unable to allocate T & S data arrays' );   RETURN
78            ENDIF
79            ovf_ji = (/ &
80                        &       1045, 1046, &
81                        & 1044, 1045, 1046, &
82                        & 1043, 1044, 1045, &
83                        & 1042, 1043, 1044, &
84                        & 1041, 1042, 1043, &
85                        & 1040, 1041, 1042  &
86                        & /)
87            ovf_jj = (/ &
88                        &       1020, 1020, &
89                        & 1019, 1019, 1019, &
90                        & 1018, 1018, 1018, &
91                        & 1017, 1017, 1017, &
92                        & 1016, 1016, 1016, &
93                        & 1015, 1015, 1015  &
94                        & /)
95      END SELECT
96      !
97      IF( lk_mpp ) CALL mppsync
98      DO kk = 1, num_pnt
99         ji = ovf_ji(kk)
100         jj = ovf_jj(kk)
101         IF ((mi0(ji)>1 .AND. mi0(ji)<jpi) .AND. (mj0(jj)>1 .AND. mj0(jj)<jpj)) THEN
102            pts(mi0(ji), mj0(jj), :, jp_tem) = rn_tem_ovf
103            pts(mi0(ji), mj0(jj), :, jp_sal) = rn_sal_ovf
104         ENDIF
105      END DO           
106      !   
107   END SUBROUTINE usr_def_istate
108
109   !!======================================================================
110END MODULE usrdef_istate
Note: See TracBrowser for help on using the repository browser.