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 utils/tools_AGRIF_CMEMS_2020/DOMAINcfg/src – NEMO

source: utils/tools_AGRIF_CMEMS_2020/DOMAINcfg/src/bdy_oce.F90 @ 10727

Last change on this file since 10727 was 10727, checked in by rblod, 5 years ago

new nesting tools (attempt) and brutal cleaning of DOMAINcfg, see ticket #2129

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