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_DYN_optimization/src/OCE/BDY – NEMO

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

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

dev_r10984_HPC-13 : adding extra halos in dyn_spg_ts is now possible, only works with a single halo when used with tide or bdy, see #2308

  • Property svn:keywords set to Id
File size: 14.8 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
19   INTEGER, PUBLIC, PARAMETER ::   jp_bdy  = 10       !: Maximum number of bdy sets
20   INTEGER, PUBLIC, PARAMETER ::   jpbgrd  = 3        !: Number of horizontal grid types used  (T, U, V)
21
22   TYPE, PUBLIC ::   OBC_INDEX    !: Indices and weights which define the open boundary
23      INTEGER ,          DIMENSION(jpbgrd) ::  nblen
24      INTEGER ,          DIMENSION(jpbgrd) ::  nblenrim
25      INTEGER ,          DIMENSION(jpbgrd) ::  nblenrim0
26      INTEGER , POINTER, DIMENSION(:,:)    ::  nbi
27      INTEGER , POINTER, DIMENSION(:,:)    ::  nbj
28      INTEGER , POINTER, DIMENSION(:,:)    ::  nbr
29      INTEGER , POINTER, DIMENSION(:,:)    ::  nbmap
30      INTEGER , POINTER, DIMENSION(:,:)    ::  ntreat
31      REAL(wp), POINTER, DIMENSION(:,:)    ::  nbw
32      REAL(wp), POINTER, DIMENSION(:,:)    ::  nbd
33      REAL(wp), POINTER, DIMENSION(:,:)    ::  nbdout
34      REAL(wp), POINTER, DIMENSION(:,:)    ::  flagu
35      REAL(wp), POINTER, DIMENSION(:,:)    ::  flagv
36   END TYPE OBC_INDEX
37
38   !! Logicals in OBC_DATA structure are true if the chosen algorithm requires this
39   !! field as external data. If true the data can come from external files
40   !! or model initial conditions. If false then no "external" data array
41   !! is required for this field.
42
43   TYPE, PUBLIC ::   OBC_DATA     !: Storage for external data
44      INTEGER          , DIMENSION(2)   ::  nread
45      LOGICAL                           ::  lneed_ssh
46      LOGICAL                           ::  lneed_dyn2d
47      LOGICAL                           ::  lneed_dyn3d
48      LOGICAL                           ::  lneed_tra
49      LOGICAL                           ::  lneed_ice
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      REAL(wp), POINTER, DIMENSION(:,:) ::  a_i    !: now ice leads fraction climatology
58      REAL(wp), POINTER, DIMENSION(:,:) ::  h_i    !: Now ice  thickness climatology
59      REAL(wp), POINTER, DIMENSION(:,:) ::  h_s    !: now snow thickness
60#if defined key_top
61      CHARACTER(LEN=20)                   :: cn_obc  !: type of boundary condition to apply
62      REAL(wp)                            :: rn_fac  !: multiplicative scaling factor
63      REAL(wp), POINTER, DIMENSION(:,:)   :: trc     !: now field of the tracer
64      LOGICAL                             :: dmp     !: obc damping term
65#endif
66   END TYPE OBC_DATA
67
68   !!----------------------------------------------------------------------
69   !! Namelist variables
70   !!----------------------------------------------------------------------
71   LOGICAL, PUBLIC            ::   ln_bdy                   !: Unstructured Ocean Boundary Condition
72
73   CHARACTER(len=80), DIMENSION(jp_bdy) ::   cn_coords_file !: Name of bdy coordinates file
74   CHARACTER(len=80)                    ::   cn_mask_file   !: Name of bdy mask file
75   !
76   LOGICAL, DIMENSION(jp_bdy) ::   ln_coords_file           !: =T read bdy coordinates from file;
77   !                                                        !: =F read bdy coordinates from namelist
78   LOGICAL                    ::   ln_mask_file             !: =T read bdymask from file
79   LOGICAL                    ::   ln_vol                   !: =T volume correction             
80   !
81   INTEGER                    ::   nb_bdy                   !: number of open boundary sets
82   INTEGER, DIMENSION(jp_bdy) ::   nn_rimwidth              !: boundary rim width for Flow Relaxation Scheme
83   INTEGER                    ::   nn_volctl                !: = 0 the total volume will have the variability of the surface Flux E-P
84   !                                                        !  = 1 the volume will be constant during all the integration.
85   CHARACTER(len=20), DIMENSION(jp_bdy) ::   cn_dyn2d       ! Choice of boundary condition for barotropic variables (U,V,SSH)
86   INTEGER, DIMENSION(jp_bdy)           ::   nn_dyn2d_dta   !: = 0 use the initial state as bdy dta ;
87                                                            !: = 1 read it in a NetCDF file
88                                                            !: = 2 read tidal harmonic forcing from a NetCDF file
89                                                            !: = 3 read external data AND tidal harmonic forcing from NetCDF files
90   CHARACTER(len=20), DIMENSION(jp_bdy) ::   cn_dyn3d       ! Choice of boundary condition for baroclinic velocities
91   INTEGER, DIMENSION(jp_bdy)           ::   nn_dyn3d_dta   !: = 0 use the initial state as bdy dta ;
92                                                            !: = 1 read it in a NetCDF file
93   CHARACTER(len=20), DIMENSION(jp_bdy) ::   cn_tra         ! Choice of boundary condition for active tracers (T and S)
94   INTEGER, DIMENSION(jp_bdy)           ::   nn_tra_dta     !: = 0 use the initial state as bdy dta ;
95                                                            !: = 1 read it in a NetCDF file
96   LOGICAL , DIMENSION(jp_bdy) ::   ln_tra_dmp              !: =T Tracer damping
97   LOGICAL , DIMENSION(jp_bdy) ::   ln_dyn3d_dmp            !: =T Baroclinic velocity damping
98   REAL(wp), DIMENSION(jp_bdy) ::   rn_time_dmp             !: Damping time scale in days
99   REAL(wp), DIMENSION(jp_bdy) ::   rn_time_dmp_out         !: Damping time scale in days at radiation outflow points
100
101   CHARACTER(len=20), DIMENSION(jp_bdy) ::   cn_ice         ! Choice of boundary condition for sea ice variables
102   INTEGER , DIMENSION(jp_bdy)          ::   nn_ice_dta     !: = 0 use the initial state as bdy dta ;
103                                                            !: = 1 read it in a NetCDF file
104   REAL(wp), DIMENSION(jp_bdy) ::   rn_ice_tem              !: choice of the temperature of incoming sea ice
105   REAL(wp), DIMENSION(jp_bdy) ::   rn_ice_sal              !: choice of the salinity    of incoming sea ice
106   REAL(wp), DIMENSION(jp_bdy) ::   rn_ice_age              !: choice of the age         of incoming sea ice
107   !
108   
109   !!----------------------------------------------------------------------
110   !! Global variables
111   !!----------------------------------------------------------------------
112   REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:,:), TARGET ::   bdytmask   !: Mask defining computational domain at T-points
113   REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:,:), TARGET ::   bdyumask   !: Mask defining computational domain at U-points
114   REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:,:), TARGET ::   bdyvmask   !: Mask defining computational domain at V-points
115
116   REAL(wp)                                    ::   bdysurftot !: Lateral surface of unstructured open boundary
117
118   !!----------------------------------------------------------------------
119   !! open boundary data variables
120   !!----------------------------------------------------------------------
121
122   INTEGER,  DIMENSION(jp_bdy)                     ::   nn_dta            !: =0 => *all* data is set to initial conditions
123                                                                          !: =1 => some data to be read in from data files
124!$AGRIF_DO_NOT_TREAT
125   ! regular :  interior domain + global halo || extended : interior domain + global halo + halo extension for time-splitting
126   TYPE(OBC_INDEX), DIMENSION(jp_bdy), TARGET      ::   idx_bdy_reg, idx_bdy_xtd    !: bdy indices (local process)
127   TYPE(OBC_DATA) , DIMENSION(jp_bdy), TARGET      ::   dta_bdy_reg, dta_bdy_xtd    !: bdy external data (local process)
128   ! pointers to switch between regular and extended, _save for the OBC_INDEX not currently used
129   TYPE(OBC_INDEX), DIMENSION(:)     , POINTER     ::   idx_bdy, idx_bdy_save       !: bdy indices (local process)
130   TYPE(OBC_DATA) , DIMENSION(:)     , POINTER     ::   dta_bdy, dta_bdy_save       !: bdy external data (local process)
131!$AGRIF_END_DO_NOT_TREAT
132   ! regular :  interior domain + global halo
133   LOGICAL, ALLOCATABLE, TARGET, DIMENSION(:,:,:,:) :: lsend_bdy_reg      !: mark com for given boundary, grid, neighbour and rim
134   LOGICAL, ALLOCATABLE, TARGET, DIMENSION(:,:,:,:) :: lrecv_bdy_reg      !:  when searching in any direction
135   LOGICAL, ALLOCATABLE, TARGET, DIMENSION(:,:,:,:) :: lsend_bdyint_reg   !: mark com for given boundary, grid, neighbour and rim
136   LOGICAL, ALLOCATABLE, TARGET, DIMENSION(:,:,:,:) :: lrecv_bdyint_reg   !:  when searching towards the interior of the domain
137   LOGICAL, ALLOCATABLE, TARGET, DIMENSION(:,:,:,:) :: lsend_bdyext_reg   !: mark com for given boundary, grid, neighbour and rim
138   LOGICAL, ALLOCATABLE, TARGET, DIMENSION(:,:,:,:) :: lrecv_bdyext_reg   !:  when searching towards the exterior of the domain
139   ! extended : interior domain + global halo + halo extension for time-splitting
140   LOGICAL, ALLOCATABLE, TARGET, DIMENSION(:,:,:,:) :: lsend_bdy_xtd      !: mark com for given boundary, grid, neighbour and rim
141   LOGICAL, ALLOCATABLE, TARGET, DIMENSION(:,:,:,:) :: lrecv_bdy_xtd      !:  when searching in any direction
142   LOGICAL, ALLOCATABLE, TARGET, DIMENSION(:,:,:,:) :: lsend_bdyint_xtd   !: mark com for given boundary, grid, neighbour and rim
143   LOGICAL, ALLOCATABLE, TARGET, DIMENSION(:,:,:,:) :: lrecv_bdyint_xtd   !:  when searching towards the interior of the domain
144   LOGICAL, ALLOCATABLE, TARGET, DIMENSION(:,:,:,:) :: lsend_bdyext_xtd   !: mark com for given boundary, grid, neighbour and rim
145   LOGICAL, ALLOCATABLE, TARGET, DIMENSION(:,:,:,:) :: lrecv_bdyext_xtd   !:  when searching towards the exterior of the domain
146   ! pointers to switch between regular and extended, _save for the logical array not currently used
147   LOGICAL,             POINTER, DIMENSION(:,:,:,:) :: lsend_bdy   , lsend_bdy_save
148   LOGICAL,             POINTER, DIMENSION(:,:,:,:) :: lrecv_bdy   , lrecv_bdy_save
149   LOGICAL,             POINTER, DIMENSION(:,:,:,:) :: lsend_bdyint, lsend_bdyint_save
150   LOGICAL,             POINTER, DIMENSION(:,:,:,:) :: lrecv_bdyint, lrecv_bdyint_save
151   LOGICAL,             POINTER, DIMENSION(:,:,:,:) :: lsend_bdyext, lsend_bdyext_save
152   LOGICAL,             POINTER, DIMENSION(:,:,:,:) :: lrecv_bdyext, lrecv_bdyext_save
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
181   SUBROUTINE swap_bdyptr
182      !!----------------------------------------------------------------------
183      !!                 ***  ROUTINE  swap_bdyptr  ***
184      !!         
185      !! ** Purpose :   swap all pointers for bdy treatment
186      !!----------------------------------------------------------------------
187      CALL swap_obciptr(idx_bdy     , idx_bdy_save     )
188      CALL swap_obcdptr(dta_bdy     , dta_bdy_save     )
189      CALL swap_lptr   (lsend_bdy   , lsend_bdy_save   )
190      CALL swap_lptr   (lrecv_bdy   , lrecv_bdy_save   )
191      CALL swap_lptr   (lsend_bdyint, lsend_bdyint_save)
192      CALL swap_lptr   (lrecv_bdyint, lrecv_bdyint_save)
193      CALL swap_lptr   (lsend_bdyext, lsend_bdyext_save)
194      CALL swap_lptr   (lrecv_bdyext, lrecv_bdyext_save)
195      !
196   END SUBROUTINE swap_bdyptr
197
198
199   SUBROUTINE swap_lptr( ptr1, ptr2 )
200      !!----------------------------------------------------------------------
201      !!                 ***  ROUTINE swap_lptr  ***
202      !!         
203      !! ** Purpose :   swap logical pointers
204      !! ** Method  :   use temporary pointer to save the target
205      !!----------------------------------------------------------------------     
206      LOGICAL, DIMENSION(:,:,:,:), POINTER, INTENT(inout)   :: ptr1, ptr2
207      LOGICAL, DIMENSION(:,:,:,:), POINTER                  :: ptrtmp
208      !!----------------------------------------------------------------------
209      ptrtmp => ptr1
210      ptr1 => ptr2
211      ptr2 => ptrtmp
212   END SUBROUTINE swap_lptr
213
214
215   SUBROUTINE swap_obciptr( ptr1, ptr2 )
216      !!----------------------------------------------------------------------
217      !!                 ***  ROUTINE swap_obciptr  ***
218      !!         
219      !! ** Purpose :   swap pointers on OBC_INDEX types
220      !! ** Method  :   use temporary pointer to save the target
221      !!----------------------------------------------------------------------     
222      TYPE(OBC_INDEX), DIMENSION(:), POINTER, INTENT(inout)   :: ptr1, ptr2
223      TYPE(OBC_INDEX), DIMENSION(:), POINTER                  :: ptrtmp
224      !!----------------------------------------------------------------------
225      ptrtmp => ptr1
226      ptr1 => ptr2
227      ptr2 => ptrtmp
228   END SUBROUTINE swap_obciptr
229
230
231   SUBROUTINE swap_obcdptr( ptr1, ptr2 )
232      !!----------------------------------------------------------------------
233      !!                 ***  ROUTINE swap_obcdptr  ***
234      !!         
235      !! ** Purpose :   swap pointers on OBC_DATA types
236      !! ** Method  :   use temporary pointer to save the target
237      !!----------------------------------------------------------------------     
238      TYPE(OBC_DATA), DIMENSION(:), POINTER, INTENT(inout)   :: ptr1, ptr2
239      TYPE(OBC_DATA), DIMENSION(:), POINTER                  :: ptrtmp
240      !!----------------------------------------------------------------------
241      ptrtmp => ptr1
242      ptr1 => ptr2
243      ptr2 => ptrtmp
244   END SUBROUTINE swap_obcdptr
245
246   !!======================================================================
247END MODULE bdy_oce
248
Note: See TracBrowser for help on using the repository browser.