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

source: branches/2013/dev_r4028_CNRS_LIM3/NEMOGCM/NEMO/OPA_SRC/BDY/bdy_oce.F90 @ 4332

Last change on this file since 4332 was 4332, checked in by clem, 10 years ago

update LIM3 to fix remaining bugs. Now working in global and regional config.

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