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.
bdy_oce.F90 in branches/2011/DEV_r2739_STFC_dCSE/NEMOGCM/NEMO/OPA_SRC/BDY – NEMO

source: branches/2011/DEV_r2739_STFC_dCSE/NEMOGCM/NEMO/OPA_SRC/BDY/bdy_oce.F90 @ 4428

Last change on this file since 4428 was 3211, checked in by spickles2, 12 years ago

Stephen Pickles, 11 Dec 2011

Commit to bring the rest of the DCSE NEMO development branch
in line with the latest development version. This includes
array index re-ordering of all OPA_SRC/.

  • Property svn:keywords set to Id
File size: 7.1 KB
Line 
1MODULE bdy_oce
2   !!======================================================================
3   !!                       ***  MODULE bdy_oce   ***
4   !! Unstructured Open Boundary Cond. :   define related variables
5   !!======================================================================
6   !! History :  1.0  !  2001-05  (J. Chanut, A. Sellar)  Original code
7   !!            3.0  !  2008-04  (NEMO team)  add in the reference version     
8   !!            3.3  !  2010-09  (D. Storkey) add ice boundary conditions
9   !!----------------------------------------------------------------------
10#if defined key_bdy 
11   !!----------------------------------------------------------------------
12   !!   'key_bdy'                      Unstructured Open Boundary Condition
13   !!----------------------------------------------------------------------
14   USE par_oce         ! ocean parameters
15   USE bdy_par         ! Unstructured boundary parameters
16   USE lib_mpp         ! distributed memory computing
17
18   IMPLICIT NONE
19   PUBLIC
20
21   !!----------------------------------------------------------------------
22   !! Namelist variables
23   !!----------------------------------------------------------------------
24   CHARACTER(len=80) ::   cn_mask        !: Name of unstruct. bdy mask file
25   CHARACTER(len=80) ::   cn_dta_frs_T   !: Name of unstruct. bdy data file at T points for FRS conditions
26   CHARACTER(len=80) ::   cn_dta_frs_U   !: Name of unstruct. bdy data file at U points for FRS conditions
27   CHARACTER(len=80) ::   cn_dta_frs_V   !: Name of unstruct. bdy data file at V points for FRS conditions
28   CHARACTER(len=80) ::   cn_dta_fla_T   !: Name of unstruct. bdy data file at T points for Flather scheme
29   CHARACTER(len=80) ::   cn_dta_fla_U   !: Name of unstruct. bdy data file at U points for Flather scheme
30   CHARACTER(len=80) ::   cn_dta_fla_V   !: Name of unstruct. bdy data file at V points for Flather scheme
31   !
32   LOGICAL ::   ln_tides = .false.    !: =T apply tidal harmonic forcing along open boundaries
33   LOGICAL ::   ln_vol  = .false.     !: =T volume correction             
34   LOGICAL ::   ln_mask = .false.     !: =T read bdymask from file
35   LOGICAL ::   ln_clim = .false.     !: =T bdy data files contain  1 time dump  (-->bdy forcing will be constant)
36   !                                  !                         or 12 months     (-->bdy forcing will be cyclic)
37   LOGICAL ::   ln_dyn_fla  = .false. !: =T Flather boundary conditions on barotropic velocities
38   LOGICAL ::   ln_dyn_frs  = .false. !: =T FRS boundary conditions on velocities
39   LOGICAL ::   ln_tra_frs  = .false. !: =T FRS boundary conditions on tracers (T and S)
40   LOGICAL ::   ln_ice_frs  = .false. !: =T FRS boundary conditions on seaice (leads fraction, ice depth, snow depth)
41   !
42   INTEGER ::   nn_rimwidth = 7       !: boundary rim width
43   INTEGER ::   nn_dtactl   = 1       !: = 0 use the initial state as bdy dta ; = 1 read it in a NetCDF file
44   INTEGER ::   nn_volctl   = 1       !: = 0 the total volume will have the variability of the surface Flux E-P
45   !                                  !  = 1 the volume will be constant during all the integration.
46
47   !!----------------------------------------------------------------------
48   !! Global variables
49   !!----------------------------------------------------------------------
50   REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:,:) ::   bdytmask   !: Mask defining computational domain at T-points
51   REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:,:) ::   bdyumask   !: Mask defining computational domain at U-points
52   REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:,:) ::   bdyvmask   !: Mask defining computational domain at V-points
53
54   !!----------------------------------------------------------------------
55   !! Unstructured open boundary data variables
56   !!----------------------------------------------------------------------
57   INTEGER, DIMENSION(jpbgrd) ::   nblen    = 0           !: Size of bdy data on a proc for each grid type
58   INTEGER, DIMENSION(jpbgrd) ::   nblenrim = 0           !: Size of bdy data on a proc for first rim ind
59   INTEGER, DIMENSION(jpbgrd) ::   nblendta = 0           !: Size of bdy data in file
60
61   INTEGER, DIMENSION(jpbdim,jpbgrd) ::   nbi, nbj        !: i and j indices of bdy dta
62   INTEGER, DIMENSION(jpbdim,jpbgrd) ::   nbr             !: Discrete distance from rim points
63   INTEGER, DIMENSION(jpbdim,jpbgrd) ::   nbmap           !: Indices of data in file for data in memory
64   
65   REAL(wp) ::   bdysurftot                               !: Lateral surface of unstructured open boundary
66
67   REAL(wp), DIMENSION(jpbdim)        ::   flagu, flagv   !: Flag for normal velocity compnt for velocity components
68   REAL(wp), DIMENSION(jpbdim,jpbgrd) ::   nbw            !: Rim weights of bdy data
69
70   REAL(wp), DIMENSION(jpbdim)     ::   sshbdy            !: Now clim of bdy sea surface height (Flather)
71   REAL(wp), DIMENSION(jpbdim)     ::   ubtbdy, vbtbdy    !: Now clim of bdy barotropic velocity components
72   REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:,:) ::   tbdy  , sbdy      !: Now clim of bdy temperature and salinity 
73   REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:,:) ::   ubdy  , vbdy      !: Now clim of bdy velocity components
74   REAL(wp), DIMENSION(jpbdim) ::   sshtide               !: Tidal boundary array : SSH
75   REAL(wp), DIMENSION(jpbdim) ::   utide, vtide          !: Tidal boundary array : U and V
76#if defined key_lim2
77   REAL(wp), DIMENSION(jpbdim) ::   frld_bdy    !: now ice leads fraction climatology   
78   REAL(wp), DIMENSION(jpbdim) ::   hicif_bdy   !: Now ice  thickness climatology
79   REAL(wp), DIMENSION(jpbdim) ::   hsnif_bdy   !: now snow thickness
80#endif
81
82   !! * Control permutation of array indices
83   !!   We do not permute indices of boundary condition arrays!
84
85   !!----------------------------------------------------------------------
86   !! NEMO/OPA 4.0 , NEMO Consortium (2011)
87   !! $Id$
88   !! Software governed by the CeCILL licence     (NEMOGCM/NEMO_CeCILL.txt)
89   !!----------------------------------------------------------------------
90CONTAINS
91
92   FUNCTION bdy_oce_alloc()
93      !!----------------------------------------------------------------------
94      USE lib_mpp, ONLY: ctl_warn, mpp_sum
95      !
96      INTEGER :: bdy_oce_alloc
97      !!----------------------------------------------------------------------
98      !
99      ALLOCATE( bdytmask(jpi,jpj) , tbdy(jpbdim,jpk) , sbdy(jpbdim,jpk) ,     &
100         &      bdyumask(jpi,jpj) , ubdy(jpbdim,jpk) ,                        &
101         &      bdyvmask(jpi,jpj) , vbdy(jpbdim,jpk) ,                    STAT=bdy_oce_alloc )
102         !
103      IF( lk_mpp             )   CALL mpp_sum ( bdy_oce_alloc )
104      IF( bdy_oce_alloc /= 0 )   CALL ctl_warn('bdy_oce_alloc: failed to allocate arrays.')
105      !
106   END FUNCTION bdy_oce_alloc
107
108#else
109   !!----------------------------------------------------------------------
110   !!   Dummy module                NO Unstructured Open Boundary Condition
111   !!----------------------------------------------------------------------
112   LOGICAL ::   ln_tides = .false.  !: =T apply tidal harmonic forcing along open boundaries
113#endif
114
115   !!======================================================================
116END MODULE bdy_oce
Note: See TracBrowser for help on using the repository browser.