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 trunk/NEMOGCM/NEMO/OPA_SRC/BDY – NEMO

source: trunk/NEMOGCM/NEMO/OPA_SRC/BDY/bdy_oce.F90 @ 2715

Last change on this file since 2715 was 2715, checked in by rblod, 13 years ago

First attempt to put dynamic allocation on the trunk

  • Property svn:keywords set to Id
File size: 7.0 KB
RevLine 
[911]1MODULE bdy_oce
2   !!======================================================================
3   !!                       ***  MODULE bdy_oce   ***
4   !! Unstructured Open Boundary Cond. :   define related variables
5   !!======================================================================
[1125]6   !! History :  1.0  !  2001-05  (J. Chanut, A. Sellar)  Original code
7   !!            3.0  !  2008-04  (NEMO team)  add in the reference version     
[2528]8   !!            3.3  !  2010-09  (D. Storkey) add ice boundary conditions
[911]9   !!----------------------------------------------------------------------
[1125]10#if defined key_bdy 
[911]11   !!----------------------------------------------------------------------
[1125]12   !!   'key_bdy'                      Unstructured Open Boundary Condition
[911]13   !!----------------------------------------------------------------------
14   USE par_oce         ! ocean parameters
15   USE bdy_par         ! Unstructured boundary parameters
[2715]16   USE lib_mpp         ! distributed memory computing
[911]17
18   IMPLICIT NONE
19   PUBLIC
20
21   !!----------------------------------------------------------------------
22   !! Namelist variables
23   !!----------------------------------------------------------------------
[2528]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
[1125]31   !
[2528]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
[2715]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)
[2528]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)
[1125]41   !
[2715]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.
[911]46
47   !!----------------------------------------------------------------------
48   !! Global variables
49   !!----------------------------------------------------------------------
[2715]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
[911]53
54   !!----------------------------------------------------------------------
55   !! Unstructured open boundary data variables
56   !!----------------------------------------------------------------------
[2528]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
[911]60
[1125]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
[911]64   
[2715]65   REAL(wp) ::   bdysurftot                               !: Lateral surface of unstructured open boundary
[911]66
[1125]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
[911]69
[1125]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
[2715]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
[1125]74   REAL(wp), DIMENSION(jpbdim) ::   sshtide               !: Tidal boundary array : SSH
75   REAL(wp), DIMENSION(jpbdim) ::   utide, vtide          !: Tidal boundary array : U and V
[2528]76#if defined key_lim2
[2715]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
[2528]80#endif
[911]81
[2715]82   !!----------------------------------------------------------------------
83   !! NEMO/OPA 4.0 , NEMO Consortium (2011)
84   !! $Id$
85   !! Software governed by the CeCILL licence     (NEMOGCM/NEMO_CeCILL.txt)
86   !!----------------------------------------------------------------------
87CONTAINS
88
89   FUNCTION bdy_oce_alloc()
90      !!----------------------------------------------------------------------
91      USE lib_mpp, ONLY: ctl_warn, mpp_sum
92      !
93      INTEGER :: bdy_oce_alloc
94      !!----------------------------------------------------------------------
95      !
96      ALLOCATE( bdytmask(jpi,jpj) , tbdy(jpbdim,jpk) , sbdy(jpbdim,jpk) ,     &
97         &      bdyumask(jpi,jpj) , ubdy(jpbdim,jpk) ,                        &
98         &      bdyvmask(jpi,jpj) , vbdy(jpbdim,jpk) ,                    STAT=bdy_oce_alloc )
99         !
100      IF( lk_mpp             )   CALL mpp_sum ( bdy_oce_alloc )
101      IF( bdy_oce_alloc /= 0 )   CALL ctl_warn('bdy_oce_alloc: failed to allocate arrays.')
102      !
103   END FUNCTION bdy_oce_alloc
104
[911]105#else
106   !!----------------------------------------------------------------------
[1125]107   !!   Dummy module                NO Unstructured Open Boundary Condition
[911]108   !!----------------------------------------------------------------------
[2528]109   LOGICAL ::   ln_tides = .false.  !: =T apply tidal harmonic forcing along open boundaries
[911]110#endif
111
112   !!======================================================================
113END MODULE bdy_oce
Note: See TracBrowser for help on using the repository browser.