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 @ 11223

Last change on this file since 11223 was 11223, checked in by smasson, 5 years ago

dev_r10984_HPC-13 : cleaning of rewriting of bdydta, see #2285

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