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

source: branches/2013/dev_r3987_METO1_MERCATOR6_OBC_BDY_merge/NEMOGCM/NEMO/OPA_SRC/BDY/bdy_oce.F90 @ 3991

Last change on this file since 3991 was 3991, checked in by davestorkey, 11 years ago

New branch from later branch point on trunk so you can do a clean
diff of all the changes. Copy in changes from dev_r3891_METO1_MERCATOR6_OBC_BDY_merge.

  • Property svn:keywords set to Id
File size: 9.5 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
[3294]9   !!            3.4  !  2011     (D. Storkey) rewrite in preparation for OBC-BDY merge
[911]10   !!----------------------------------------------------------------------
[1125]11#if defined key_bdy 
[911]12   !!----------------------------------------------------------------------
[1125]13   !!   'key_bdy'                      Unstructured Open Boundary Condition
[911]14   !!----------------------------------------------------------------------
15   USE par_oce         ! ocean parameters
16   USE bdy_par         ! Unstructured boundary parameters
[2715]17   USE lib_mpp         ! distributed memory computing
[911]18
19   IMPLICIT NONE
20   PUBLIC
21
[3294]22   TYPE, PUBLIC ::   OBC_INDEX    !: Indices and weights which define the open boundary
23      INTEGER,          DIMENSION(jpbgrd) ::  nblen
24      INTEGER,          DIMENSION(jpbgrd) ::  nblenrim
25      INTEGER, POINTER, DIMENSION(:,:)   ::  nbi
26      INTEGER, POINTER, DIMENSION(:,:)   ::  nbj
27      INTEGER, POINTER, DIMENSION(:,:)   ::  nbr
28      INTEGER, POINTER, DIMENSION(:,:)   ::  nbmap
29      REAL   , POINTER, DIMENSION(:,:)   ::  nbw
[3651]30      REAL   , POINTER, DIMENSION(:,:)   ::  nbd
[3991]31      REAL   , POINTER, DIMENSION(:,:)   ::  nbdout
32      REAL   , POINTER, DIMENSION(:,:)   ::  flagu
33      REAL   , POINTER, DIMENSION(:,:)   ::  flagv
[3294]34   END TYPE OBC_INDEX
35
[3991]36   !! Logicals in OBC_DATA structure are true if the chosen algorithm requires this
37   !! field as external data. If true the data can come from external files
38   !! or model initial conditions. If false then no "external" data array
39   !! is required for this field.
40
[3294]41   TYPE, PUBLIC ::   OBC_DATA     !: Storage for external data
[3991]42      INTEGER,       DIMENSION(2)     ::  nread
43      LOGICAL                         ::  ll_ssh
44      LOGICAL                         ::  ll_u2d
45      LOGICAL                         ::  ll_v2d
46      LOGICAL                         ::  ll_u3d
47      LOGICAL                         ::  ll_v3d
48      LOGICAL                         ::  ll_tem
49      LOGICAL                         ::  ll_sal
[3294]50      REAL, POINTER, DIMENSION(:)     ::  ssh
51      REAL, POINTER, DIMENSION(:)     ::  u2d
52      REAL, POINTER, DIMENSION(:)     ::  v2d
53      REAL, POINTER, DIMENSION(:,:)   ::  u3d
54      REAL, POINTER, DIMENSION(:,:)   ::  v3d
55      REAL, POINTER, DIMENSION(:,:)   ::  tem
56      REAL, POINTER, DIMENSION(:,:)   ::  sal
57#if defined key_lim2
[3991]58      LOGICAL                         ::  ll_frld
59      LOGICAL                         ::  ll_hicif
60      LOGICAL                         ::  ll_hsnif
[3294]61      REAL, POINTER, DIMENSION(:)     ::  frld
62      REAL, POINTER, DIMENSION(:)     ::  hicif
63      REAL, POINTER, DIMENSION(:)     ::  hsnif
64#endif
65   END TYPE OBC_DATA
66
[911]67   !!----------------------------------------------------------------------
68   !! Namelist variables
69   !!----------------------------------------------------------------------
[3294]70   CHARACTER(len=80), DIMENSION(jp_bdy) ::   cn_coords_file !: Name of bdy coordinates file
71   CHARACTER(len=80)                    ::   cn_mask_file   !: Name of bdy mask file
[1125]72   !
[3294]73   LOGICAL, DIMENSION(jp_bdy) ::   ln_coords_file           !: =T read bdy coordinates from file;
74   !                                                        !: =F read bdy coordinates from namelist
75   LOGICAL                    ::   ln_mask_file             !: =T read bdymask from file
76   LOGICAL                    ::   ln_vol                   !: =T volume correction             
[1125]77   !
[3294]78   INTEGER                    ::   nb_bdy                   !: number of open boundary sets
79   INTEGER, DIMENSION(jp_bdy) ::   nn_rimwidth              !: boundary rim width for Flow Relaxation Scheme
80   INTEGER                    ::   nn_volctl                !: = 0 the total volume will have the variability of the surface Flux E-P
81   !                                                        !  = 1 the volume will be constant during all the integration.
[3991]82   CHARACTER(len=20), DIMENSION(jp_bdy) ::   cn_dyn2d       ! Choice of boundary condition for barotropic variables (U,V,SSH)
83   INTEGER, DIMENSION(jp_bdy)           ::   nn_dyn2d_dta   !: = 0 use the initial state as bdy dta ;
[3294]84                                                            !: = 1 read it in a NetCDF file
85                                                            !: = 2 read tidal harmonic forcing from a NetCDF file
86                                                            !: = 3 read external data AND tidal harmonic forcing from NetCDF files
[3991]87   CHARACTER(len=20), DIMENSION(jp_bdy) ::   cn_dyn3d       ! Choice of boundary condition for baroclinic velocities
88   INTEGER, DIMENSION(jp_bdy)           ::   nn_dyn3d_dta   !: = 0 use the initial state as bdy dta ;
[3294]89                                                            !: = 1 read it in a NetCDF file
[3991]90   CHARACTER(len=20), DIMENSION(jp_bdy) ::   cn_tra         ! Choice of boundary condition for active tracers (T and S)
91   INTEGER, DIMENSION(jp_bdy)           ::   nn_tra_dta     !: = 0 use the initial state as bdy dta ;
[3294]92                                                            !: = 1 read it in a NetCDF file
[3651]93   LOGICAL, DIMENSION(jp_bdy) ::   ln_tra_dmp               !: =T Tracer damping
94   LOGICAL, DIMENSION(jp_bdy) ::   ln_dyn3d_dmp             !: =T Baroclinic velocity damping
95   REAL,    DIMENSION(jp_bdy) ::   rn_time_dmp              !: Damping time scale in days
[3991]96   REAL,    DIMENSION(jp_bdy) ::   rn_time_dmp_out          !: Damping time scale in days at radiation outflow points
[3651]97
[3294]98#if defined key_lim2
[3991]99   CHARACTER(len=20), DIMENSION(jp_bdy) ::   nn_ice_lim2      ! Choice of boundary condition for sea ice variables
100   INTEGER, DIMENSION(jp_bdy)           ::   nn_ice_lim2_dta  !: = 0 use the initial state as bdy dta ;
101                                                              !: = 1 read it in a NetCDF file
[3294]102#endif
103   !
104   
[911]105   !!----------------------------------------------------------------------
106   !! Global variables
107   !!----------------------------------------------------------------------
[3991]108   REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:,:), TARGET ::   bdytmask   !: Mask defining computational domain at T-points
109   REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:,:), TARGET ::   bdyumask   !: Mask defining computational domain at U-points
110   REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:,:), TARGET ::   bdyvmask   !: Mask defining computational domain at V-points
111   REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:,:), TARGET ::   bdyfmask   !: Mask defining computational domain at F-points
[911]112
[3294]113   REAL(wp)                                    ::   bdysurftot !: Lateral surface of unstructured open boundary
114
[3991]115   REAL(wp), POINTER, DIMENSION(:,:)           ::   pssh                  !:
116   REAL(wp), POINTER, DIMENSION(:,:)           ::   phur                  !:
117   REAL(wp), POINTER, DIMENSION(:,:)           ::   phvr                  !: Pointers for barotropic fields
118   REAL(wp), POINTER, DIMENSION(:,:)           ::   pub2d, pun2d, pua2d   !:
119   REAL(wp), POINTER, DIMENSION(:,:)           ::   pvb2d, pvn2d, pva2d   !:
[3294]120
[911]121   !!----------------------------------------------------------------------
[3294]122   !! open boundary data variables
[911]123   !!----------------------------------------------------------------------
124
[3294]125   INTEGER,  DIMENSION(jp_bdy)                     ::   nn_dta            !: =0 => *all* data is set to initial conditions
126                                                                          !: =1 => some data to be read in from data files
[3651]127   REAL(wp), ALLOCATABLE, DIMENSION(:,:,:), TARGET ::   dta_global        !: workspace for reading in global data arrays (unstr.  bdy)
128   REAL(wp), ALLOCATABLE, DIMENSION(:,:,:), TARGET ::   dta_global2       !: workspace for reading in global data arrays (struct. bdy)
[3294]129   TYPE(OBC_INDEX), DIMENSION(jp_bdy), TARGET      ::   idx_bdy           !: bdy indices (local process)
[3991]130   TYPE(OBC_DATA) , DIMENSION(jp_bdy), TARGET      ::   dta_bdy           !: bdy external data (local process)
[911]131
[2715]132   !!----------------------------------------------------------------------
133   !! NEMO/OPA 4.0 , NEMO Consortium (2011)
134   !! $Id$
135   !! Software governed by the CeCILL licence     (NEMOGCM/NEMO_CeCILL.txt)
136   !!----------------------------------------------------------------------
137CONTAINS
138
139   FUNCTION bdy_oce_alloc()
140      !!----------------------------------------------------------------------
141      USE lib_mpp, ONLY: ctl_warn, mpp_sum
142      !
143      INTEGER :: bdy_oce_alloc
144      !!----------------------------------------------------------------------
145      !
[3991]146      ALLOCATE( bdytmask(jpi,jpj) , bdyumask(jpi,jpj), bdyvmask(jpi,jpj), bdyfmask(jpi,jpj),     & 
[3294]147         &      STAT=bdy_oce_alloc )
[2715]148         !
149      IF( lk_mpp             )   CALL mpp_sum ( bdy_oce_alloc )
150      IF( bdy_oce_alloc /= 0 )   CALL ctl_warn('bdy_oce_alloc: failed to allocate arrays.')
151      !
152   END FUNCTION bdy_oce_alloc
153
[911]154#else
155   !!----------------------------------------------------------------------
[1125]156   !!   Dummy module                NO Unstructured Open Boundary Condition
[911]157   !!----------------------------------------------------------------------
[2528]158   LOGICAL ::   ln_tides = .false.  !: =T apply tidal harmonic forcing along open boundaries
[911]159#endif
160
161   !!======================================================================
162END MODULE bdy_oce
[3294]163
Note: See TracBrowser for help on using the repository browser.