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 NEMO/branches/UKMO/NEMO_4.0.4_CO9_wadcpl/src/OCE/BDY – NEMO

source: NEMO/branches/UKMO/NEMO_4.0.4_CO9_wadcpl/src/OCE/BDY/bdy_oce.F90 @ 15784

Last change on this file since 15784 was 15784, checked in by jmedwards01, 2 years ago

Added NEMO_4.0.4_CO9_package_tides. This is not consistent with tides in the RCS.
Fix this next.

File size: 11.2 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  !  2014-01  (C. Rousset) add ice boundary conditions for new model
11   !!            4.0  !  2018     (C. Rousset) SI3 compatibility
12   !!----------------------------------------------------------------------
13   USE par_oce         ! ocean parameters
14
15   IMPLICIT NONE
16   PUBLIC
17
18   INTEGER, PUBLIC, PARAMETER ::   jp_bdy  = 10       !: Maximum number of bdy sets
19   INTEGER, PUBLIC, PARAMETER ::   jpbgrd  = 3        !: Number of horizontal grid types used  (T, U, V)
20
21   TYPE, PUBLIC ::   OBC_INDEX    !: Indices and weights which define the open boundary
22      INTEGER ,          DIMENSION(jpbgrd) ::  nblen
23      INTEGER ,          DIMENSION(jpbgrd) ::  nblenrim
24      INTEGER ,          DIMENSION(jpbgrd) ::  nblenrim0
25      INTEGER , POINTER, DIMENSION(:,:)    ::  nbi
26      INTEGER , POINTER, DIMENSION(:,:)    ::  nbj
27      INTEGER , POINTER, DIMENSION(:,:)    ::  nbr
28      INTEGER , POINTER, DIMENSION(:,:)    ::  nbmap
29      INTEGER , POINTER, DIMENSION(:,:)    ::  ntreat
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                           ::  lneed_ssh
45      !--- davbyr
46      LOGICAL                           ::  lforced_ssh 
47     !--- END davbyr
48      LOGICAL                           ::  lneed_dyn2d
49      LOGICAL                           ::  lneed_dyn3d
50      LOGICAL                           ::  lneed_tra
51      LOGICAL                           ::  lneed_ice
52      REAL(wp), POINTER, DIMENSION(:)   ::  ssh
53      REAL(wp), POINTER, DIMENSION(:)   ::  u2d
54      REAL(wp), POINTER, DIMENSION(:)   ::  v2d
55      REAL(wp), POINTER, DIMENSION(:,:) ::  u3d
56      REAL(wp), POINTER, DIMENSION(:,:) ::  v3d
57      REAL(wp), POINTER, DIMENSION(:,:) ::  tem
58      REAL(wp), POINTER, DIMENSION(:,:) ::  sal
59      REAL(wp), POINTER, DIMENSION(:,:) ::  a_i    !: now ice leads fraction climatology
60      REAL(wp), POINTER, DIMENSION(:,:) ::  h_i    !: Now ice  thickness climatology
61      REAL(wp), POINTER, DIMENSION(:,:) ::  h_s    !: now snow thickness
62      REAL(wp), POINTER, DIMENSION(:,:) ::  t_i    !: now ice  temperature
63      REAL(wp), POINTER, DIMENSION(:,:) ::  t_s    !: now snow temperature
64      REAL(wp), POINTER, DIMENSION(:,:) ::  tsu    !: now surf temperature
65      REAL(wp), POINTER, DIMENSION(:,:) ::  s_i    !: now ice  salinity
66      REAL(wp), POINTER, DIMENSION(:,:) ::  aip    !: now ice  pond concentration
67      REAL(wp), POINTER, DIMENSION(:,:) ::  hip    !: now ice  pond depth
68      REAL(wp), POINTER, DIMENSION(:,:) ::  hil    !: now ice  pond lid depth
69#if defined key_top
70      CHARACTER(LEN=20)                   :: cn_obc  !: type of boundary condition to apply
71      REAL(wp)                            :: rn_fac  !: multiplicative scaling factor
72      REAL(wp), POINTER, DIMENSION(:,:)   :: trc     !: now field of the tracer
73      LOGICAL                             :: dmp     !: obc damping term
74#endif
75   END TYPE OBC_DATA
76
77   !!----------------------------------------------------------------------
78   !! Namelist variables
79   !!----------------------------------------------------------------------
80   !                                                   !!** nambdy **
81   LOGICAL, PUBLIC            ::   ln_bdy                   !: Unstructured Ocean Boundary Condition
82
83   CHARACTER(len=80), DIMENSION(jp_bdy) ::   cn_coords_file !: Name of bdy coordinates file
84   CHARACTER(len=80)                    ::   cn_mask_file   !: Name of bdy mask file
85   !
86   LOGICAL, DIMENSION(jp_bdy) ::   ln_coords_file           !: =T read bdy coordinates from file;
87   !                                                        !: =F read bdy coordinates from namelist
88   LOGICAL                    ::   ln_mask_file             !: =T read bdymask from file
89   LOGICAL                    ::   ln_vol                   !: =T volume correction             
90   !
91   INTEGER                    ::   nb_bdy                   !: number of open boundary sets
92   INTEGER, DIMENSION(jp_bdy) ::   nn_rimwidth              !: boundary rim width for Flow Relaxation Scheme
93   INTEGER                    ::   nn_volctl                !: = 0 the total volume will have the variability of the surface Flux E-P
94   !                                                        !  = 1 the volume will be constant during all the integration.
95   CHARACTER(len=20), DIMENSION(jp_bdy) ::   cn_dyn2d       ! Choice of boundary condition for barotropic variables (U,V,SSH)
96   INTEGER, DIMENSION(jp_bdy)           ::   nn_dyn2d_dta   !: = 0 use the initial state as bdy dta ;
97                                                            !: = 1 read it in a NetCDF file
98                                                            !: = 2 read tidal harmonic forcing from a NetCDF file
99                                                            !: = 3 read external data AND tidal harmonic forcing from NetCDF files
100   CHARACTER(len=20), DIMENSION(jp_bdy) ::   cn_dyn3d       ! Choice of boundary condition for baroclinic velocities
101   INTEGER, DIMENSION(jp_bdy)           ::   nn_dyn3d_dta   !: = 0 use the initial state as bdy dta ;
102                                                            !: = 1 read it in a NetCDF file
103   CHARACTER(len=20), DIMENSION(jp_bdy) ::   cn_tra         ! Choice of boundary condition for active tracers (T and S)
104   INTEGER, DIMENSION(jp_bdy)           ::   nn_tra_dta     !: = 0 use the initial state as bdy dta ;
105                                                            !: = 1 read it in a NetCDF file
106   LOGICAL , DIMENSION(jp_bdy) ::   ln_tra_dmp              !: =T Tracer damping
107   LOGICAL , DIMENSION(jp_bdy) ::   ln_dyn3d_dmp            !: =T Baroclinic velocity damping
108   REAL(wp), DIMENSION(jp_bdy) ::   rn_time_dmp             !: Damping time scale in days
109   REAL(wp), DIMENSION(jp_bdy) ::   rn_time_dmp_out         !: Damping time scale in days at radiation outflow points
110
111   CHARACTER(len=20), DIMENSION(jp_bdy) ::   cn_ice         ! Choice of boundary condition for sea ice variables
112   INTEGER , DIMENSION(jp_bdy)          ::   nn_ice_dta     !: = 0 use the initial state as bdy dta ;
113                                                            !: = 1 read it in a NetCDF file
114   !
115   !                                                   !!** nambdy_dta **
116   REAL(wp), DIMENSION(jp_bdy) ::   rice_tem                !: temperature of incoming sea ice
117   REAL(wp), DIMENSION(jp_bdy) ::   rice_sal                !: salinity    of incoming sea ice
118   REAL(wp), DIMENSION(jp_bdy) ::   rice_age                !: age         of incoming sea ice
119   REAL(wp), DIMENSION(jp_bdy) ::   rice_apnd               !: pond conc.  of incoming sea ice
120   REAL(wp), DIMENSION(jp_bdy) ::   rice_hpnd               !: pond thick. of incoming sea ice
121   REAL(wp), DIMENSION(jp_bdy) ::   rice_hlid               !: pond lid thick. of incoming sea ice
122   
123   !  davbyr
124   LOGICAL, DIMENSION(jp_bdy) ::   ln_ssh_bdy               !: =T USE SSH BDY - name list switch
125   REAL(wp), DIMENSION(jp_bdy) ::  rn_ssh_shift             !: =F SHIFT SSH AT A BORDER BY rn_ssh_shift m_
126   !  END davbyr
127   !
128   !!----------------------------------------------------------------------
129   !! Global variables
130   !!----------------------------------------------------------------------
131   REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:,:), TARGET ::   bdytmask   !: Mask defining computational domain at T-points
132   REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:,:), TARGET ::   bdyumask   !: Mask defining computational domain at U-points
133   REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:,:), TARGET ::   bdyvmask   !: Mask defining computational domain at V-points
134
135   REAL(wp)                                    ::   bdysurftot !: Lateral surface of unstructured open boundary
136
137   !!----------------------------------------------------------------------
138   !! open boundary data variables
139   !!----------------------------------------------------------------------
140
141   INTEGER,  DIMENSION(jp_bdy)                     ::   nn_dta            !: =0 => *all* data is set to initial conditions
142                                                                          !: =1 => some data to be read in from data files
143!$AGRIF_DO_NOT_TREAT
144   TYPE(OBC_INDEX), DIMENSION(jp_bdy), TARGET      ::   idx_bdy           !: bdy indices (local process)
145   TYPE(OBC_DATA) , DIMENSION(jp_bdy), TARGET      ::   dta_bdy           !: bdy external data (local process)
146!$AGRIF_END_DO_NOT_TREAT
147   LOGICAL, ALLOCATABLE, DIMENSION(:,:,:,:) ::   lsend_bdy      !: mark needed communication for given boundary, grid and neighbour
148   LOGICAL, ALLOCATABLE, DIMENSION(:,:,:,:) ::   lrecv_bdy      !:  when searching in any direction
149   LOGICAL, ALLOCATABLE, DIMENSION(:,:,:,:) ::   lsend_bdyint   !: mark needed communication for given boundary, grid and neighbour
150   LOGICAL, ALLOCATABLE, DIMENSION(:,:,:,:) ::   lrecv_bdyint   !:  when searching towards the interior of the computational domain
151   LOGICAL, ALLOCATABLE, DIMENSION(:,:,:,:) ::   lsend_bdyext   !: mark needed communication for given boundary, grid and neighbour
152   LOGICAL, ALLOCATABLE, DIMENSION(:,:,:,:) ::   lrecv_bdyext   !:  when searching towards the exterior of the computational domain
153   !!----------------------------------------------------------------------
154   !! NEMO/OCE 4.0 , NEMO Consortium (2018)
155   !! $Id$
156   !! Software governed by the CeCILL license (see ./LICENSE)
157   !!----------------------------------------------------------------------
158CONTAINS
159
160   FUNCTION bdy_oce_alloc()
161      !!----------------------------------------------------------------------
162      USE lib_mpp, ONLY: ctl_stop, mpp_sum
163      !
164      INTEGER :: bdy_oce_alloc
165      !!----------------------------------------------------------------------
166      !
167      ALLOCATE( bdytmask(jpi,jpj) , bdyumask(jpi,jpj), bdyvmask(jpi,jpj),     & 
168         &      STAT=bdy_oce_alloc )
169      !
170      ! Initialize masks
171      bdytmask(:,:) = 1._wp
172      bdyumask(:,:) = 1._wp
173      bdyvmask(:,:) = 1._wp
174      !
175      CALL mpp_sum ( 'bdy_oce', bdy_oce_alloc )
176      IF( bdy_oce_alloc /= 0 )   CALL ctl_stop( 'STOP', 'bdy_oce_alloc: failed to allocate arrays.' )
177      !
178   END FUNCTION bdy_oce_alloc
179
180   !!======================================================================
181END MODULE bdy_oce
182
Note: See TracBrowser for help on using the repository browser.