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/2020/dev_r13327_KERNEL-06_2_techene_e3/src/OCE/BDY – NEMO

source: NEMO/branches/2020/dev_r13327_KERNEL-06_2_techene_e3/src/OCE/BDY/bdy_oce.F90 @ 13998

Last change on this file since 13998 was 13998, checked in by techene, 3 years ago

branch updated with trunk 13787

  • Property svn:keywords set to Id
File size: 11.0 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
[13998]65      REAL(wp), POINTER, DIMENSION(:,:) ::  hil    !: now ice  pond lid depth
[6140]66#if defined key_top
67      CHARACTER(LEN=20)                   :: cn_obc  !: type of boundary condition to apply
68      REAL(wp)                            :: rn_fac  !: multiplicative scaling factor
69      REAL(wp), POINTER, DIMENSION(:,:)   :: trc     !: now field of the tracer
70      LOGICAL                             :: dmp     !: obc damping term
71#endif
[3294]72   END TYPE OBC_DATA
73
[911]74   !!----------------------------------------------------------------------
75   !! Namelist variables
76   !!----------------------------------------------------------------------
[11536]77   !                                                   !!** nambdy **
[7646]78   LOGICAL, PUBLIC            ::   ln_bdy                   !: Unstructured Ocean Boundary Condition
79
[3294]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
[1125]82   !
[3294]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             
[1125]87   !
[3294]88   INTEGER                    ::   nb_bdy                   !: number of open boundary sets
89   INTEGER, DIMENSION(jp_bdy) ::   nn_rimwidth              !: boundary rim width for Flow Relaxation Scheme
90   INTEGER                    ::   nn_volctl                !: = 0 the total volume will have the variability of the surface Flux E-P
91   !                                                        !  = 1 the volume will be constant during all the integration.
[4292]92   CHARACTER(len=20), DIMENSION(jp_bdy) ::   cn_dyn2d       ! Choice of boundary condition for barotropic variables (U,V,SSH)
93   INTEGER, DIMENSION(jp_bdy)           ::   nn_dyn2d_dta   !: = 0 use the initial state as bdy dta ;
[3294]94                                                            !: = 1 read it in a NetCDF file
95                                                            !: = 2 read tidal harmonic forcing from a NetCDF file
96                                                            !: = 3 read external data AND tidal harmonic forcing from NetCDF files
[4292]97   CHARACTER(len=20), DIMENSION(jp_bdy) ::   cn_dyn3d       ! Choice of boundary condition for baroclinic velocities
98   INTEGER, DIMENSION(jp_bdy)           ::   nn_dyn3d_dta   !: = 0 use the initial state as bdy dta ;
[3294]99                                                            !: = 1 read it in a NetCDF file
[4292]100   CHARACTER(len=20), DIMENSION(jp_bdy) ::   cn_tra         ! Choice of boundary condition for active tracers (T and S)
101   INTEGER, DIMENSION(jp_bdy)           ::   nn_tra_dta     !: = 0 use the initial state as bdy dta ;
[3294]102                                                            !: = 1 read it in a NetCDF file
[5836]103   LOGICAL , DIMENSION(jp_bdy) ::   ln_tra_dmp              !: =T Tracer damping
104   LOGICAL , DIMENSION(jp_bdy) ::   ln_dyn3d_dmp            !: =T Baroclinic velocity damping
105   REAL(wp), DIMENSION(jp_bdy) ::   rn_time_dmp             !: Damping time scale in days
106   REAL(wp), DIMENSION(jp_bdy) ::   rn_time_dmp_out         !: Damping time scale in days at radiation outflow points
[3651]107
[9657]108   CHARACTER(len=20), DIMENSION(jp_bdy) ::   cn_ice         ! Choice of boundary condition for sea ice variables
109   INTEGER , DIMENSION(jp_bdy)          ::   nn_ice_dta     !: = 0 use the initial state as bdy dta ;
110                                                            !: = 1 read it in a NetCDF file
[11536]111   !
112   !                                                   !!** nambdy_dta **
113   REAL(wp), DIMENSION(jp_bdy) ::   rice_tem                !: temperature of incoming sea ice
114   REAL(wp), DIMENSION(jp_bdy) ::   rice_sal                !: salinity    of incoming sea ice
115   REAL(wp), DIMENSION(jp_bdy) ::   rice_age                !: age         of incoming sea ice
116   REAL(wp), DIMENSION(jp_bdy) ::   rice_apnd               !: pond conc.  of incoming sea ice
117   REAL(wp), DIMENSION(jp_bdy) ::   rice_hpnd               !: pond thick. of incoming sea ice
[13998]118   REAL(wp), DIMENSION(jp_bdy) ::   rice_hlid               !: pond lid thick. of incoming sea ice
[3294]119   !
[911]120   !!----------------------------------------------------------------------
121   !! Global variables
122   !!----------------------------------------------------------------------
[4292]123   REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:,:), TARGET ::   bdytmask   !: Mask defining computational domain at T-points
124   REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:,:), TARGET ::   bdyumask   !: Mask defining computational domain at U-points
125   REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:,:), TARGET ::   bdyvmask   !: Mask defining computational domain at V-points
[911]126
[3294]127   REAL(wp)                                    ::   bdysurftot !: Lateral surface of unstructured open boundary
128
[911]129   !!----------------------------------------------------------------------
[3294]130   !! open boundary data variables
[911]131   !!----------------------------------------------------------------------
132
[3294]133   INTEGER,  DIMENSION(jp_bdy)                     ::   nn_dta            !: =0 => *all* data is set to initial conditions
134                                                                          !: =1 => some data to be read in from data files
[4354]135!$AGRIF_DO_NOT_TREAT
[3294]136   TYPE(OBC_INDEX), DIMENSION(jp_bdy), TARGET      ::   idx_bdy           !: bdy indices (local process)
[4292]137   TYPE(OBC_DATA) , DIMENSION(jp_bdy), TARGET      ::   dta_bdy           !: bdy external data (local process)
[4354]138!$AGRIF_END_DO_NOT_TREAT
[11536]139   LOGICAL, ALLOCATABLE, DIMENSION(:,:,:,:) ::   lsend_bdy      !: mark needed communication for given boundary, grid and neighbour
140   LOGICAL, ALLOCATABLE, DIMENSION(:,:,:,:) ::   lrecv_bdy      !:  when searching in any direction
141   LOGICAL, ALLOCATABLE, DIMENSION(:,:,:,:) ::   lsend_bdyint   !: mark needed communication for given boundary, grid and neighbour
142   LOGICAL, ALLOCATABLE, DIMENSION(:,:,:,:) ::   lrecv_bdyint   !:  when searching towards the interior of the computational domain
143   LOGICAL, ALLOCATABLE, DIMENSION(:,:,:,:) ::   lsend_bdyext   !: mark needed communication for given boundary, grid and neighbour
144   LOGICAL, ALLOCATABLE, DIMENSION(:,:,:,:) ::   lrecv_bdyext   !:  when searching towards the exterior of the computational domain
[12377]145   !! * Substitutions
146#  include "do_loop_substitute.h90"
[2715]147   !!----------------------------------------------------------------------
[9598]148   !! NEMO/OCE 4.0 , NEMO Consortium (2018)
[2715]149   !! $Id$
[10068]150   !! Software governed by the CeCILL license (see ./LICENSE)
[2715]151   !!----------------------------------------------------------------------
152CONTAINS
153
154   FUNCTION bdy_oce_alloc()
155      !!----------------------------------------------------------------------
[10425]156      USE lib_mpp, ONLY: ctl_stop, mpp_sum
[2715]157      !
158      INTEGER :: bdy_oce_alloc
159      !!----------------------------------------------------------------------
160      !
[4292]161      ALLOCATE( bdytmask(jpi,jpj) , bdyumask(jpi,jpj), bdyvmask(jpi,jpj),     & 
[3294]162         &      STAT=bdy_oce_alloc )
[4354]163      !
164      ! Initialize masks
[7753]165      bdytmask(:,:) = 1._wp
166      bdyumask(:,:) = 1._wp
167      bdyvmask(:,:) = 1._wp
[4354]168      !
[10425]169      CALL mpp_sum ( 'bdy_oce', bdy_oce_alloc )
170      IF( bdy_oce_alloc /= 0 )   CALL ctl_stop( 'STOP', 'bdy_oce_alloc: failed to allocate arrays.' )
[2715]171      !
172   END FUNCTION bdy_oce_alloc
173
[911]174   !!======================================================================
175END MODULE bdy_oce
[3294]176
Note: See TracBrowser for help on using the repository browser.