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/2019/dev_r10984_HPC-13_IRRMANN_BDY_optimization/src/OCE/BDY – NEMO

source: NEMO/branches/2019/dev_r10984_HPC-13_IRRMANN_BDY_optimization/src/OCE/BDY/bdy_oce.F90 @ 11191

Last change on this file since 11191 was 11191, checked in by girrmann, 5 years ago

dev_r10984_HPC-13 : bdy treatment can now handel a rim 0 and a rim 1, results are unchanged when only rim 1 is provided, see #2288 and #2285

  • Property svn:keywords set to Id
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                           ::  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      LOGICAL                           ::  ll_fvl
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#if defined key_si3
60      LOGICAL                           ::   ll_a_i
61      LOGICAL                           ::   ll_h_i
62      LOGICAL                           ::   ll_h_s
63      REAL(wp), POINTER, DIMENSION(:,:) ::   a_i    !: now ice leads fraction climatology
64      REAL(wp), POINTER, DIMENSION(:,:) ::   h_i    !: Now ice  thickness climatology
65      REAL(wp), POINTER, DIMENSION(:,:) ::   h_s    !: now snow thickness
66#endif
67#if defined key_top
68      CHARACTER(LEN=20)                   :: cn_obc  !: type of boundary condition to apply
69      REAL(wp)                            :: rn_fac  !: multiplicative scaling factor
70      REAL(wp), POINTER, DIMENSION(:,:)   :: trc     !: now field of the tracer
71      LOGICAL                             :: dmp     !: obc damping term
72#endif
73   END TYPE OBC_DATA
74
75   !!----------------------------------------------------------------------
76   !! Namelist variables
77   !!----------------------------------------------------------------------
78   LOGICAL, PUBLIC            ::   ln_bdy                   !: Unstructured Ocean Boundary Condition
79
80   CHARACTER(len=80), DIMENSION(jp_bdy) ::   cn_coords_file !: Name of bdy coordinates file
81   CHARACTER(len=80)                    ::   cn_mask_file   !: Name of bdy mask file
82   !
83   LOGICAL, DIMENSION(jp_bdy) ::   ln_coords_file           !: =T read bdy coordinates from file;
84   !                                                        !: =F read bdy coordinates from namelist
85   LOGICAL                    ::   ln_mask_file             !: =T read bdymask from file
86   LOGICAL                    ::   ln_vol                   !: =T volume correction             
87   !
88   INTEGER                    ::   nb_bdy                   !: number of open boundary sets
89   INTEGER, DIMENSION(jp_bdy) ::   nb_jpk_bdy               !: number of levels in the bdy data (set < 0 if consistent with planned run)
90   INTEGER, DIMENSION(jp_bdy) ::   nn_rimwidth              !: boundary rim width for Flow Relaxation Scheme
91   INTEGER                    ::   nn_volctl                !: = 0 the total volume will have the variability of the surface Flux E-P
92   !                                                        !  = 1 the volume will be constant during all the integration.
93   CHARACTER(len=20), DIMENSION(jp_bdy) ::   cn_dyn2d       ! Choice of boundary condition for barotropic variables (U,V,SSH)
94   INTEGER, DIMENSION(jp_bdy)           ::   nn_dyn2d_dta   !: = 0 use the initial state as bdy dta ;
95                                                            !: = 1 read it in a NetCDF file
96                                                            !: = 2 read tidal harmonic forcing from a NetCDF file
97                                                            !: = 3 read external data AND tidal harmonic forcing from NetCDF files
98   CHARACTER(len=20), DIMENSION(jp_bdy) ::   cn_dyn3d       ! Choice of boundary condition for baroclinic velocities
99   INTEGER, DIMENSION(jp_bdy)           ::   nn_dyn3d_dta   !: = 0 use the initial state as bdy dta ;
100                                                            !: = 1 read it in a NetCDF file
101   CHARACTER(len=20), DIMENSION(jp_bdy) ::   cn_tra         ! Choice of boundary condition for active tracers (T and S)
102   INTEGER, DIMENSION(jp_bdy)           ::   nn_tra_dta     !: = 0 use the initial state as bdy dta ;
103                                                            !: = 1 read it in a NetCDF file
104   LOGICAL , DIMENSION(jp_bdy) ::   ln_tra_dmp              !: =T Tracer damping
105   LOGICAL , DIMENSION(jp_bdy) ::   ln_dyn3d_dmp            !: =T Baroclinic velocity damping
106   REAL(wp), DIMENSION(jp_bdy) ::   rn_time_dmp             !: Damping time scale in days
107   REAL(wp), DIMENSION(jp_bdy) ::   rn_time_dmp_out         !: Damping time scale in days at radiation outflow points
108
109   CHARACTER(len=20), DIMENSION(jp_bdy) ::   cn_ice         ! Choice of boundary condition for sea ice variables
110   INTEGER , DIMENSION(jp_bdy)          ::   nn_ice_dta     !: = 0 use the initial state as bdy dta ;
111                                                            !: = 1 read it in a NetCDF file
112   REAL(wp), DIMENSION(jp_bdy) ::   rn_ice_tem              !: choice of the temperature of incoming sea ice
113   REAL(wp), DIMENSION(jp_bdy) ::   rn_ice_sal              !: choice of the salinity    of incoming sea ice
114   REAL(wp), DIMENSION(jp_bdy) ::   rn_ice_age              !: choice of the age         of incoming sea ice
115   !
116   
117   !!----------------------------------------------------------------------
118   !! Global variables
119   !!----------------------------------------------------------------------
120   REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:,:), TARGET ::   bdytmask   !: Mask defining computational domain at T-points
121   REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:,:), TARGET ::   bdyumask   !: Mask defining computational domain at U-points
122   REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:,:), TARGET ::   bdyvmask   !: Mask defining computational domain at V-points
123
124   REAL(wp)                                    ::   bdysurftot !: Lateral surface of unstructured open boundary
125
126   !!----------------------------------------------------------------------
127   !! open boundary data variables
128   !!----------------------------------------------------------------------
129
130   INTEGER,  DIMENSION(jp_bdy)                     ::   nn_dta            !: =0 => *all* data is set to initial conditions
131                                                                          !: =1 => some data to be read in from data files
132   REAL(wp), ALLOCATABLE, DIMENSION(:,:,:), TARGET ::   dta_global        !: workspace for reading in global data arrays (unstr.  bdy)
133   REAL(wp), ALLOCATABLE, DIMENSION(:,:,:), TARGET ::   dta_global_z      !: workspace for reading in global depth arrays (unstr.  bdy)
134   REAL(wp), ALLOCATABLE, DIMENSION(:,:,:), TARGET ::   dta_global_dz     !: workspace for reading in global depth arrays (unstr.  bdy)
135   REAL(wp), ALLOCATABLE, DIMENSION(:,:,:), TARGET ::   dta_global2       !: workspace for reading in global data arrays (struct. bdy)
136   REAL(wp), ALLOCATABLE, DIMENSION(:,:,:), TARGET ::   dta_global2_z     !: workspace for reading in global depth arrays (struct. bdy)
137   REAL(wp), ALLOCATABLE, DIMENSION(:,:,:), TARGET ::   dta_global2_dz    !: workspace for reading in global depth arrays (struct. bdy)
138!$AGRIF_DO_NOT_TREAT
139   TYPE(OBC_INDEX), DIMENSION(jp_bdy), TARGET      ::   idx_bdy           !: bdy indices (local process)
140   TYPE(OBC_DATA) , DIMENSION(jp_bdy), TARGET      ::   dta_bdy           !: bdy external data (local process)
141!$AGRIF_END_DO_NOT_TREAT
142   LOGICAL, ALLOCATABLE, DIMENSION(:,:,:,:) ::   lsend_bdy      !: mark needed communication for given boundary, grid and neighbour
143   LOGICAL, ALLOCATABLE, DIMENSION(:,:,:,:) ::   lrecv_bdy      !:  when searching in any direction
144   LOGICAL, ALLOCATABLE, DIMENSION(:,:,:,:) ::   lsend_bdyint   !: mark needed communication for given boundary, grid and neighbour
145   LOGICAL, ALLOCATABLE, DIMENSION(:,:,:,:) ::   lrecv_bdyint   !:  when searching towards the interior of the computational domain
146   LOGICAL, ALLOCATABLE, DIMENSION(:,:,:,:) ::   lsend_bdyext   !: mark needed communication for given boundary, grid and neighbour
147   LOGICAL, ALLOCATABLE, DIMENSION(:,:,:,:) ::   lrecv_bdyext   !:  when searching towards the exterior of the computational domain
148   !!----------------------------------------------------------------------
149   !! NEMO/OCE 4.0 , NEMO Consortium (2018)
150   !! $Id$
151   !! Software governed by the CeCILL license (see ./LICENSE)
152   !!----------------------------------------------------------------------
153CONTAINS
154
155   FUNCTION bdy_oce_alloc()
156      !!----------------------------------------------------------------------
157      USE lib_mpp, ONLY: ctl_stop, mpp_sum
158      !
159      INTEGER :: bdy_oce_alloc
160      !!----------------------------------------------------------------------
161      !
162      ALLOCATE( bdytmask(jpi,jpj) , bdyumask(jpi,jpj), bdyvmask(jpi,jpj),     & 
163         &      STAT=bdy_oce_alloc )
164      !
165      ! Initialize masks
166      bdytmask(:,:) = 1._wp
167      bdyumask(:,:) = 1._wp
168      bdyvmask(:,:) = 1._wp
169      !
170      CALL mpp_sum ( 'bdy_oce', bdy_oce_alloc )
171      IF( bdy_oce_alloc /= 0 )   CALL ctl_stop( 'STOP', 'bdy_oce_alloc: failed to allocate arrays.' )
172      !
173   END FUNCTION bdy_oce_alloc
174
175   !!======================================================================
176END MODULE bdy_oce
177
Note: See TracBrowser for help on using the repository browser.