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/2011/UKMO_MERCATOR_obc_bdy_merge/NEMOGCM/NEMO/OPA_SRC/DYN – NEMO

source: branches/2011/UKMO_MERCATOR_obc_bdy_merge/NEMOGCM/NEMO/OPA_SRC/DYN/dynspg_oce.F90 @ 2800

Last change on this file since 2800 was 2800, checked in by davestorkey, 13 years ago
  1. Application of boundary conditions to barotropic and baroclinic velocities clearly separated.
  2. Option to input full velocities in boundary data (default expects barotropic and baroclinic velocities separately).
  3. Option to use initial conditions as boundary conditions coded.
  • Property svn:keywords set to Id
File size: 3.4 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  ||  defined key_esopa
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   ||  defined key_esopa
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  ||  defined key_esopa
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
35  !                                                                         !!! Time splitting scheme (key_dynspg_ts)
36   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:), TARGET ::   sshn_e, ssha_e   ! sea surface heigth (now, after, average)
37   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:), TARGET ::   ua_e  , va_e     ! barotropic velocities (after)
38   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)         ::   hu_e  , hv_e     ! now ocean depth ( = Ho+sshn_e )
39   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:), TARGET ::   hur_e , hvr_e    ! inverse of hu_e and hv_e
40   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:), TARGET ::   sshn_b           ! before field without time-filter
41
42   !!----------------------------------------------------------------------
43   !! NEMO/OPA 4.0 , NEMO Consortium (2011)
44   !! $Id$
45   !! Software governed by the CeCILL licence     (NEMOGCM/NEMO_CeCILL.txt)
46   !!----------------------------------------------------------------------
47CONTAINS
48
49   INTEGER FUNCTION dynspg_oce_alloc()
50      !!----------------------------------------------------------------------
51      !!                  ***  routine dynspg_oce_alloc  ***
52      !!----------------------------------------------------------------------
53      ALLOCATE( sshn_e(jpi,jpj) , ua_e(jpi,jpj) , hu_e(jpi,jpj) , hur_e(jpi,jpj) ,      &
54         &      ssha_e(jpi,jpj) , va_e(jpi,jpj) , hv_e(jpi,jpj) , hvr_e(jpi,jpj) ,      &
55         &      sshn_b(jpi,jpj)                                                  , STAT = dynspg_oce_alloc )
56         !
57      IF( lk_mpp                )   CALL mpp_sum ( dynspg_oce_alloc )
58      IF( dynspg_oce_alloc /= 0 )   CALL ctl_warn('dynspg_oce_alloc: failed to allocate arrays')
59      !
60   END FUNCTION dynspg_oce_alloc
61
62   !!======================================================================
63END MODULE dynspg_oce
Note: See TracBrowser for help on using the repository browser.