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

source: NEMO/branches/2019/dev_r11943_MERGE_2019/src/OCE/BDY/bdy_oce.F90 @ 12340

Last change on this file since 12340 was 12340, checked in by acc, 4 years ago

Branch 2019/dev_r11943_MERGE_2019. This commit introduces basic do loop macro
substitution to the 2019 option 1, merge branch. These changes have been SETTE
tested. The only addition is the do_loop_substitute.h90 file in the OCE directory but
the macros defined therein are used throughout the code to replace identifiable, 2D-
and 3D- nested loop opening and closing statements with single-line alternatives. Code
indents are also adjusted accordingly.

The following explanation is taken from comments in the new header file:

This header file contains preprocessor definitions and macros used in the do-loop
substitutions introduced between version 4.0 and 4.2. The primary aim of these macros
is to assist in future applications of tiling to improve performance. This is expected
to be achieved by alternative versions of these macros in selected locations. The
initial introduction of these macros simply replaces all identifiable nested 2D- and
3D-loops with single line statements (and adjusts indenting accordingly). Do loops
are identifiable if they comform to either:

DO jk = ....

DO jj = .... DO jj = ...

DO ji = .... DO ji = ...
. OR .
. .

END DO END DO

END DO END DO

END DO

and white-space variants thereof.

Additionally, only loops with recognised jj and ji loops limits are treated; these are:
Lower limits of 1, 2 or fs_2
Upper limits of jpi, jpim1 or fs_jpim1 (for ji) or jpj, jpjm1 or fs_jpjm1 (for jj)

The macro naming convention takes the form: DO_2D_BT_LR where:

B is the Bottom offset from the PE's inner domain;
T is the Top offset from the PE's inner domain;
L is the Left offset from the PE's inner domain;
R is the Right offset from the PE's inner domain

So, given an inner domain of 2,jpim1 and 2,jpjm1, a typical example would replace:

DO jj = 2, jpj

DO ji = 1, jpim1
.
.

END DO

END DO

with:

DO_2D_01_10
.
.
END_2D

similar conventions apply to the 3D loops macros. jk loop limits are retained
through macro arguments and are not restricted. This includes the possibility of
strides for which an extra set of DO_3DS macros are defined.

In the example definition below the inner PE domain is defined by start indices of
(kIs, kJs) and end indices of (kIe, KJe)

#define DO_2D_00_00 DO jj = kJs, kJe ; DO ji = kIs, kIe
#define END_2D END DO ; END DO

TO DO:


Only conventional nested loops have been identified and replaced by this step. There are constructs such as:

DO jk = 2, jpkm1

z2d(:,:) = z2d(:,:) + e3w(:,:,jk,Kmm) * z3d(:,:,jk) * wmask(:,:,jk)

END DO

which may need to be considered.

  • Property svn:keywords set to Id
File size: 10.8 KB
RevLine 
[911]1MODULE bdy_oce
2   !!======================================================================
3   !!                       ***  MODULE bdy_oce   ***
4   !! Unstructured Open Boundary Cond. :   define related variables
5   !!======================================================================
[1125]6   !! History :  1.0  !  2001-05  (J. Chanut, A. Sellar)  Original code
7   !!            3.0  !  2008-04  (NEMO team)  add in the reference version     
[2528]8   !!            3.3  !  2010-09  (D. Storkey) add ice boundary conditions
[3294]9   !!            3.4  !  2011     (D. Storkey) rewrite in preparation for OBC-BDY merge
[9656]10   !!            3.6  !  2014-01  (C. Rousset) add ice boundary conditions for new model
11   !!            4.0  !  2018     (C. Rousset) SI3 compatibility
[911]12   !!----------------------------------------------------------------------
13   USE par_oce         ! ocean parameters
14
15   IMPLICIT NONE
16   PUBLIC
17
[7646]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
[3294]21   TYPE, PUBLIC ::   OBC_INDEX    !: Indices and weights which define the open boundary
[5836]22      INTEGER ,          DIMENSION(jpbgrd) ::  nblen
23      INTEGER ,          DIMENSION(jpbgrd) ::  nblenrim
[11536]24      INTEGER ,          DIMENSION(jpbgrd) ::  nblenrim0
[5836]25      INTEGER , POINTER, DIMENSION(:,:)    ::  nbi
26      INTEGER , POINTER, DIMENSION(:,:)    ::  nbj
27      INTEGER , POINTER, DIMENSION(:,:)    ::  nbr
28      INTEGER , POINTER, DIMENSION(:,:)    ::  nbmap
[11536]29      INTEGER , POINTER, DIMENSION(:,:)    ::  ntreat
[5836]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
[3294]35   END TYPE OBC_INDEX
36
[4292]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
[3294]42   TYPE, PUBLIC ::   OBC_DATA     !: Storage for external data
[5836]43      INTEGER          , DIMENSION(2)   ::  nread
[11536]44      LOGICAL                           ::  lneed_ssh
45      LOGICAL                           ::  lneed_dyn2d
46      LOGICAL                           ::  lneed_dyn3d
47      LOGICAL                           ::  lneed_tra
48      LOGICAL                           ::  lneed_ice
[5836]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
[11536]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      REAL(wp), POINTER, DIMENSION(:,:) ::  t_i    !: now ice  temperature
60      REAL(wp), POINTER, DIMENSION(:,:) ::  t_s    !: now snow temperature
61      REAL(wp), POINTER, DIMENSION(:,:) ::  tsu    !: now surf temperature
62      REAL(wp), POINTER, DIMENSION(:,:) ::  s_i    !: now ice  salinity
63      REAL(wp), POINTER, DIMENSION(:,:) ::  aip    !: now ice  pond concentration
64      REAL(wp), POINTER, DIMENSION(:,:) ::  hip    !: now ice  pond depth
[6140]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
[3294]71   END TYPE OBC_DATA
72
[911]73   !!----------------------------------------------------------------------
74   !! Namelist variables
75   !!----------------------------------------------------------------------
[11536]76   !                                                   !!** nambdy **
[7646]77   LOGICAL, PUBLIC            ::   ln_bdy                   !: Unstructured Ocean Boundary Condition
78
[3294]79   CHARACTER(len=80), DIMENSION(jp_bdy) ::   cn_coords_file !: Name of bdy coordinates file
80   CHARACTER(len=80)                    ::   cn_mask_file   !: Name of bdy mask file
[1125]81   !
[3294]82   LOGICAL, DIMENSION(jp_bdy) ::   ln_coords_file           !: =T read bdy coordinates from file;
83   !                                                        !: =F read bdy coordinates from namelist
84   LOGICAL                    ::   ln_mask_file             !: =T read bdymask from file
85   LOGICAL                    ::   ln_vol                   !: =T volume correction             
[1125]86   !
[3294]87   INTEGER                    ::   nb_bdy                   !: number of open boundary sets
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.
[4292]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 ;
[3294]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
[4292]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 ;
[3294]98                                                            !: = 1 read it in a NetCDF file
[4292]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 ;
[3294]101                                                            !: = 1 read it in a NetCDF file
[5836]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
[3651]106
[9657]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
[11536]110   !
111   !                                                   !!** nambdy_dta **
112   REAL(wp), DIMENSION(jp_bdy) ::   rice_tem                !: temperature of incoming sea ice
113   REAL(wp), DIMENSION(jp_bdy) ::   rice_sal                !: salinity    of incoming sea ice
114   REAL(wp), DIMENSION(jp_bdy) ::   rice_age                !: age         of incoming sea ice
115   REAL(wp), DIMENSION(jp_bdy) ::   rice_apnd               !: pond conc.  of incoming sea ice
116   REAL(wp), DIMENSION(jp_bdy) ::   rice_hpnd               !: pond thick. of incoming sea ice
[3294]117   !
[911]118   !!----------------------------------------------------------------------
119   !! Global variables
120   !!----------------------------------------------------------------------
[4292]121   REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:,:), TARGET ::   bdytmask   !: Mask defining computational domain at T-points
122   REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:,:), TARGET ::   bdyumask   !: Mask defining computational domain at U-points
123   REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:,:), TARGET ::   bdyvmask   !: Mask defining computational domain at V-points
[911]124
[3294]125   REAL(wp)                                    ::   bdysurftot !: Lateral surface of unstructured open boundary
126
[911]127   !!----------------------------------------------------------------------
[3294]128   !! open boundary data variables
[911]129   !!----------------------------------------------------------------------
130
[3294]131   INTEGER,  DIMENSION(jp_bdy)                     ::   nn_dta            !: =0 => *all* data is set to initial conditions
132                                                                          !: =1 => some data to be read in from data files
[4354]133!$AGRIF_DO_NOT_TREAT
[3294]134   TYPE(OBC_INDEX), DIMENSION(jp_bdy), TARGET      ::   idx_bdy           !: bdy indices (local process)
[4292]135   TYPE(OBC_DATA) , DIMENSION(jp_bdy), TARGET      ::   dta_bdy           !: bdy external data (local process)
[4354]136!$AGRIF_END_DO_NOT_TREAT
[11536]137   LOGICAL, ALLOCATABLE, DIMENSION(:,:,:,:) ::   lsend_bdy      !: mark needed communication for given boundary, grid and neighbour
138   LOGICAL, ALLOCATABLE, DIMENSION(:,:,:,:) ::   lrecv_bdy      !:  when searching in any direction
139   LOGICAL, ALLOCATABLE, DIMENSION(:,:,:,:) ::   lsend_bdyint   !: mark needed communication for given boundary, grid and neighbour
140   LOGICAL, ALLOCATABLE, DIMENSION(:,:,:,:) ::   lrecv_bdyint   !:  when searching towards the interior of the computational domain
141   LOGICAL, ALLOCATABLE, DIMENSION(:,:,:,:) ::   lsend_bdyext   !: mark needed communication for given boundary, grid and neighbour
142   LOGICAL, ALLOCATABLE, DIMENSION(:,:,:,:) ::   lrecv_bdyext   !:  when searching towards the exterior of the computational domain
[12340]143   !! * Substitutions
144#  include "do_loop_substitute.h90"
[2715]145   !!----------------------------------------------------------------------
[9598]146   !! NEMO/OCE 4.0 , NEMO Consortium (2018)
[2715]147   !! $Id$
[10068]148   !! Software governed by the CeCILL license (see ./LICENSE)
[2715]149   !!----------------------------------------------------------------------
150CONTAINS
151
152   FUNCTION bdy_oce_alloc()
153      !!----------------------------------------------------------------------
[10425]154      USE lib_mpp, ONLY: ctl_stop, mpp_sum
[2715]155      !
156      INTEGER :: bdy_oce_alloc
157      !!----------------------------------------------------------------------
158      !
[4292]159      ALLOCATE( bdytmask(jpi,jpj) , bdyumask(jpi,jpj), bdyvmask(jpi,jpj),     & 
[3294]160         &      STAT=bdy_oce_alloc )
[4354]161      !
162      ! Initialize masks
[7753]163      bdytmask(:,:) = 1._wp
164      bdyumask(:,:) = 1._wp
165      bdyvmask(:,:) = 1._wp
[4354]166      !
[10425]167      CALL mpp_sum ( 'bdy_oce', bdy_oce_alloc )
168      IF( bdy_oce_alloc /= 0 )   CALL ctl_stop( 'STOP', 'bdy_oce_alloc: failed to allocate arrays.' )
[2715]169      !
170   END FUNCTION bdy_oce_alloc
171
[911]172   !!======================================================================
173END MODULE bdy_oce
[3294]174
Note: See TracBrowser for help on using the repository browser.