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.
dynspg_oce.F90 in branches/2015/dev_r5803_NOC_WAD/NEMOGCM/NEMO/OPA_SRC/DYN – NEMO

source: branches/2015/dev_r5803_NOC_WAD/NEMOGCM/NEMO/OPA_SRC/DYN/dynspg_oce.F90 @ 6137

Last change on this file since 6137 was 5870, checked in by acc, 9 years ago

Branch 2015/dev_r5803_NOC_WAD. Merge in trunk changes from 5803 to 5869 in preparation for merge. Also tidied and reorganised some wetting and drying code. Renamed wadlmt.F90 to wetdry.F90. Wetting drying code changes restricted to domzgr.F90, domvvl.F90 nemogcm.F90 sshwzv.F90, dynspg_ts.F90, wetdry.F90 and dynhpg.F90. Code passes full SETTE tests with ln_wd=.false.. Still awaiting test case for checking with ln_wd=.false.

  • Property svn:keywords set to Id
File size: 3.7 KB
Line 
1MODULE dynspg_oce
2   !!======================================================================
3   !!                       ***  MODULE dynspg_oce  ***
4   !!       
5   !! Ocean dynamics: Define in memory some surface pressure gradient variables
6   !!======================================================================
7   !! History :  1.0  ! 2005-12  (C. Talandier, G. Madec)  Original code
8   !!            3.2  ! 2009-07  (R. Benshila) Suppression of rigid-lid option
9   !!----------------------------------------------------------------------
10   USE par_oce        ! ocean parameters
11   USE lib_mpp        ! MPP library
12
13   IMPLICIT NONE
14   PUBLIC           
15
16   PUBLIC   dynspg_oce_alloc   ! called in dynspg.F90
17   
18   !                                                       !!! Surface pressure gradient logicals
19#if   defined key_dynspg_exp
20   LOGICAL, PUBLIC, PARAMETER ::   lk_dynspg_exp = .TRUE.   !: Explicit free surface flag
21#else
22   LOGICAL, PUBLIC, PARAMETER ::   lk_dynspg_exp = .FALSE.  !: Explicit free surface flag
23#endif
24#if   defined key_dynspg_ts
25   LOGICAL, PUBLIC, PARAMETER ::   lk_dynspg_ts  = .TRUE.   !: Free surface with time splitting flag
26#else
27   LOGICAL, PUBLIC, PARAMETER ::   lk_dynspg_ts  = .FALSE.  !: Free surface with time splitting flag
28#endif
29#if   defined key_dynspg_flt
30   LOGICAL, PUBLIC, PARAMETER ::   lk_dynspg_flt = .TRUE.   !: Filtered free surface cst volume flag
31#else
32   LOGICAL, PUBLIC, PARAMETER ::   lk_dynspg_flt = .FALSE.  !: Filtered free surface cst volume flag
33#endif
34  !                                                                         !!! Time splitting scheme (key_dynspg_ts)
35   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   sshn_e, ssha_e   ! sea surface heigth (now, after)
36   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   ua_e  , va_e     ! barotropic velocities (after)
37   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   hu_e  , hv_e     ! now ocean depth ( = Ho+sshn_e )
38   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   hur_e , hvr_e    ! inverse of hu_e and hv_e
39   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   un_adv, vn_adv   ! Advection vel. at "now" barocl. step
40   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   ub2_b,  vb2_b    ! Half step fluxes (ln_bt_fw=T)
41#if defined key_agrif
42   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   ub2_i_b,  vb2_i_b! Half step time integrated fluxes
43#endif
44
45   !!----------------------------------------------------------------------
46   !! NEMO/OPA 4.0 , NEMO Consortium (2011)
47   !! $Id$
48   !! Software governed by the CeCILL licence     (NEMOGCM/NEMO_CeCILL.txt)
49   !!----------------------------------------------------------------------
50CONTAINS
51
52   INTEGER FUNCTION dynspg_oce_alloc()
53      !!----------------------------------------------------------------------
54      !!                  ***  routine dynspg_oce_alloc  ***
55      !!----------------------------------------------------------------------
56      ALLOCATE( sshn_e(jpi,jpj) , ua_e(jpi,jpj) , hu_e(jpi,jpj) , hur_e(jpi,jpj) ,      &
57         &      ssha_e(jpi,jpj) , va_e(jpi,jpj) , hv_e(jpi,jpj) , hvr_e(jpi,jpj) ,      &
58         &      ub2_b(jpi,jpj)  , vb2_b(jpi,jpj)                                 ,      &
59#if defined key_agrif
60         &      ub2_i_b(jpi,jpj), vb2_i_b(jpi,jpj)                               ,      &
61#endif
62         &      un_adv(jpi,jpj) , vn_adv(jpi,jpj)                                , STAT = dynspg_oce_alloc )
63         !
64      IF( lk_mpp                )   CALL mpp_sum ( dynspg_oce_alloc )
65      IF( dynspg_oce_alloc /= 0 )   CALL ctl_warn('dynspg_oce_alloc: failed to allocate arrays')
66      !
67   END FUNCTION dynspg_oce_alloc
68
69   !!======================================================================
70END MODULE dynspg_oce
Note: See TracBrowser for help on using the repository browser.