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

source: branches/2015/dev_r5144_CMCC5_BDY_for_TOP/NEMOGCM/NEMO/OPA_SRC/BDY/bdy_oce.F90 @ 5160

Last change on this file since 5160 was 5160, checked in by lovato, 9 years ago

First implementation of BDY for TOP component, see #1441 (dev_r5144_CMCC5_BDY_for_TOP).

  • Property svn:keywords set to Id
File size: 10.3 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   !!            3.6  !  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(wp)   , POINTER, DIMENSION(:,:)   ::  nbw
31      REAL(wp)   , POINTER, DIMENSION(:,:)   ::  nbd
32      REAL(wp)   , POINTER, DIMENSION(:,:)   ::  nbdout
33      REAL(wp)   , POINTER, DIMENSION(:,:)   ::  flagu
34      REAL(wp)   , POINTER, DIMENSION(:,:)   ::  flagv
35   END TYPE OBC_INDEX
36
37   !! Logicals in OBC_DATA structure are true if the chosen algorithm requires this
38   !! field as external data. If true the data can come from external files
39   !! or model initial conditions. If false then no "external" data array
40   !! is required for this field.
41
42   TYPE, PUBLIC ::   OBC_DATA     !: Storage for external data
43      INTEGER,       DIMENSION(2)     ::  nread
44      LOGICAL                         ::  ll_ssh
45      LOGICAL                         ::  ll_u2d
46      LOGICAL                         ::  ll_v2d
47      LOGICAL                         ::  ll_u3d
48      LOGICAL                         ::  ll_v3d
49      LOGICAL                         ::  ll_tem
50      LOGICAL                         ::  ll_sal
51      REAL(wp), POINTER, DIMENSION(:)     ::  ssh
52      REAL(wp), POINTER, DIMENSION(:)     ::  u2d
53      REAL(wp), POINTER, DIMENSION(:)     ::  v2d
54      REAL(wp), POINTER, DIMENSION(:,:)   ::  u3d
55      REAL(wp), POINTER, DIMENSION(:,:)   ::  v3d
56      REAL(wp), POINTER, DIMENSION(:,:)   ::  tem
57      REAL(wp), POINTER, DIMENSION(:,:)   ::  sal
58#if defined key_lim2
59      LOGICAL                         ::  ll_frld
60      LOGICAL                         ::  ll_hicif
61      LOGICAL                         ::  ll_hsnif
62      REAL(wp), POINTER, DIMENSION(:)     ::  frld
63      REAL(wp), POINTER, DIMENSION(:)     ::  hicif
64      REAL(wp), POINTER, DIMENSION(:)     ::  hsnif
65#elif defined key_lim3
66      LOGICAL                         ::  ll_a_i
67      LOGICAL                         ::  ll_ht_i
68      LOGICAL                         ::  ll_ht_s
69      REAL, POINTER, DIMENSION(:,:)   ::  a_i   !: now ice leads fraction climatology
70      REAL, POINTER, DIMENSION(:,:)   ::  ht_i  !: Now ice  thickness climatology
71      REAL, POINTER, DIMENSION(:,:)   ::  ht_s  !: now snow thickness
72#endif
73#if defined key_top
74      CHARACTER(LEN=20)                   :: cn_obc  !: type of boundary condition to apply
75      REAL(wp)                            :: rn_fac  !: multiplicative scaling factor
76      REAL(wp), POINTER, DIMENSION(:,:)   :: trc     !: now field of the tracer
77      LOGICAL                             :: dmp     !: obc damping term
78#endif
79   END TYPE OBC_DATA
80
81   !!----------------------------------------------------------------------
82   !! Namelist variables
83   !!----------------------------------------------------------------------
84   CHARACTER(len=80), DIMENSION(jp_bdy) ::   cn_coords_file !: Name of bdy coordinates file
85   CHARACTER(len=80)                    ::   cn_mask_file   !: Name of bdy mask file
86   !
87   LOGICAL, DIMENSION(jp_bdy) ::   ln_coords_file           !: =T read bdy coordinates from file;
88   !                                                        !: =F read bdy coordinates from namelist
89   LOGICAL                    ::   ln_mask_file             !: =T read bdymask from file
90   LOGICAL                    ::   ln_vol                   !: =T volume correction             
91   !
92   INTEGER                    ::   nb_bdy                   !: number of open boundary sets
93   INTEGER, DIMENSION(jp_bdy) ::   nn_rimwidth              !: boundary rim width for Flow Relaxation Scheme
94   INTEGER                    ::   nn_volctl                !: = 0 the total volume will have the variability of the surface Flux E-P
95   !                                                        !  = 1 the volume will be constant during all the integration.
96   CHARACTER(len=20), DIMENSION(jp_bdy) ::   cn_dyn2d       ! Choice of boundary condition for barotropic variables (U,V,SSH)
97   INTEGER, DIMENSION(jp_bdy)           ::   nn_dyn2d_dta   !: = 0 use the initial state as bdy dta ;
98                                                            !: = 1 read it in a NetCDF file
99                                                            !: = 2 read tidal harmonic forcing from a NetCDF file
100                                                            !: = 3 read external data AND tidal harmonic forcing from NetCDF files
101   CHARACTER(len=20), DIMENSION(jp_bdy) ::   cn_dyn3d       ! Choice of boundary condition for baroclinic velocities
102   INTEGER, DIMENSION(jp_bdy)           ::   nn_dyn3d_dta   !: = 0 use the initial state as bdy dta ;
103                                                            !: = 1 read it in a NetCDF file
104   CHARACTER(len=20), DIMENSION(jp_bdy) ::   cn_tra         ! Choice of boundary condition for active tracers (T and S)
105   INTEGER, DIMENSION(jp_bdy)           ::   nn_tra_dta     !: = 0 use the initial state as bdy dta ;
106                                                            !: = 1 read it in a NetCDF file
107   LOGICAL, DIMENSION(jp_bdy) ::   ln_tra_dmp               !: =T Tracer damping
108   LOGICAL, DIMENSION(jp_bdy) ::   ln_dyn3d_dmp             !: =T Baroclinic velocity damping
109   REAL(wp),    DIMENSION(jp_bdy) ::   rn_time_dmp              !: Damping time scale in days
110   REAL(wp),    DIMENSION(jp_bdy) ::   rn_time_dmp_out          !: Damping time scale in days at radiation outflow points
111
112   CHARACTER(len=20), DIMENSION(jp_bdy) ::   cn_ice_lim       ! Choice of boundary condition for sea ice variables
113   INTEGER, DIMENSION(jp_bdy)           ::   nn_ice_lim_dta   !: = 0 use the initial state as bdy dta ;
114                                                              !: = 1 read it in a NetCDF file
115   REAL(wp),    DIMENSION(jp_bdy) ::   rn_ice_tem             !: choice of the temperature of incoming sea ice
116   REAL(wp),    DIMENSION(jp_bdy) ::   rn_ice_sal             !: choice of the salinity    of incoming sea ice
117   REAL(wp),    DIMENSION(jp_bdy) ::   rn_ice_age             !: choice of the age         of incoming sea ice
118   !
119   
120   !!----------------------------------------------------------------------
121   !! Global variables
122   !!----------------------------------------------------------------------
123   REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:,:), TARGET ::   bdytmask   !: Mask defining computational domain at T-points
124   REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:,:), TARGET ::   bdyumask   !: Mask defining computational domain at U-points
125   REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:,:), TARGET ::   bdyvmask   !: Mask defining computational domain at V-points
126
127   REAL(wp)                                    ::   bdysurftot !: Lateral surface of unstructured open boundary
128
129   !!----------------------------------------------------------------------
130   !! open boundary data variables
131   !!----------------------------------------------------------------------
132
133   INTEGER,  DIMENSION(jp_bdy)                     ::   nn_dta            !: =0 => *all* data is set to initial conditions
134                                                                          !: =1 => some data to be read in from data files
135   REAL(wp), ALLOCATABLE, DIMENSION(:,:,:), TARGET ::   dta_global        !: workspace for reading in global data arrays (unstr.  bdy)
136   REAL(wp), ALLOCATABLE, DIMENSION(:,:,:), TARGET ::   dta_global2       !: workspace for reading in global data arrays (struct. bdy)
137!$AGRIF_DO_NOT_TREAT
138   TYPE(OBC_INDEX), DIMENSION(jp_bdy), TARGET      ::   idx_bdy           !: bdy indices (local process)
139   TYPE(OBC_DATA) , DIMENSION(jp_bdy), TARGET      ::   dta_bdy           !: bdy external data (local process)
140!$AGRIF_END_DO_NOT_TREAT
141   !!----------------------------------------------------------------------
142   !! NEMO/OPA 4.0 , NEMO Consortium (2011)
143   !! $Id$
144   !! Software governed by the CeCILL licence     (NEMOGCM/NEMO_CeCILL.txt)
145   !!----------------------------------------------------------------------
146CONTAINS
147
148   FUNCTION bdy_oce_alloc()
149      !!----------------------------------------------------------------------
150      USE lib_mpp, ONLY: ctl_warn, mpp_sum
151      !
152      INTEGER :: bdy_oce_alloc
153      !!----------------------------------------------------------------------
154      !
155      ALLOCATE( bdytmask(jpi,jpj) , bdyumask(jpi,jpj), bdyvmask(jpi,jpj),     & 
156         &      STAT=bdy_oce_alloc )
157      !
158      ! Initialize masks
159      bdytmask(:,:) = 1._wp
160      bdyumask(:,:) = 1._wp
161      bdyvmask(:,:) = 1._wp
162      !
163      IF( lk_mpp             )   CALL mpp_sum ( bdy_oce_alloc )
164      IF( bdy_oce_alloc /= 0 )   CALL ctl_warn('bdy_oce_alloc: failed to allocate arrays.')
165      !
166   END FUNCTION bdy_oce_alloc
167
168#else
169   !!----------------------------------------------------------------------
170   !!   Dummy module                NO Unstructured Open Boundary Condition
171   !!----------------------------------------------------------------------
172   LOGICAL ::   ln_tides = .false.  !: =T apply tidal harmonic forcing along open boundaries
173#endif
174
175   !!======================================================================
176END MODULE bdy_oce
177
Note: See TracBrowser for help on using the repository browser.