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 branches/UKMO/CO6_shelfclimate/NEMOGCM/NEMO/OPA_SRC/BDY – NEMO

source: branches/UKMO/CO6_shelfclimate/NEMOGCM/NEMO/OPA_SRC/BDY/bdy_oce.F90 @ 15473

Last change on this file since 15473 was 7567, checked in by hadjt, 7 years ago

CO6 version adapted for shelf seas climate projections, including added diagnostics

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
[4292]10   !!            3.6  !  2012-01  (C. Rousset) add ice boundary conditions for lim3
[911]11   !!----------------------------------------------------------------------
[1125]12#if defined key_bdy 
[911]13   !!----------------------------------------------------------------------
[1125]14   !!   'key_bdy'                      Unstructured Open Boundary Condition
[911]15   !!----------------------------------------------------------------------
16   USE par_oce         ! ocean parameters
17   USE bdy_par         ! Unstructured boundary parameters
[2715]18   USE lib_mpp         ! distributed memory computing
[911]19
20   IMPLICIT NONE
21   PUBLIC
22
[3294]23   TYPE, PUBLIC ::   OBC_INDEX    !: Indices and weights which define the open boundary
24      INTEGER,          DIMENSION(jpbgrd) ::  nblen
25      INTEGER,          DIMENSION(jpbgrd) ::  nblenrim
26      INTEGER, POINTER, DIMENSION(:,:)   ::  nbi
27      INTEGER, POINTER, DIMENSION(:,:)   ::  nbj
28      INTEGER, POINTER, DIMENSION(:,:)   ::  nbr
29      INTEGER, POINTER, DIMENSION(:,:)   ::  nbmap
[4292]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
[4292]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      REAL(wp), POINTER, DIMENSION(:)     ::  ssh
52      REAL(wp), POINTER, DIMENSION(:)     ::  u2d
53      REAL(wp), POINTER, DIMENSION(:)     ::  v2d
54      REAL(wp), POINTER, DIMENSION(:,:)   ::  u3d
55      REAL(wp), POINTER, DIMENSION(:,:)   ::  v3d
56      REAL(wp), POINTER, DIMENSION(:,:)   ::  tem
57      REAL(wp), POINTER, DIMENSION(:,:)   ::  sal
[3294]58#if defined key_lim2
[4292]59      LOGICAL                         ::  ll_frld
60      LOGICAL                         ::  ll_hicif
61      LOGICAL                         ::  ll_hsnif
62      REAL(wp), POINTER, DIMENSION(:)     ::  frld
63      REAL(wp), POINTER, DIMENSION(:)     ::  hicif
64      REAL(wp), POINTER, DIMENSION(:)     ::  hsnif
65#elif defined key_lim3
66      LOGICAL                         ::  ll_a_i
67      LOGICAL                         ::  ll_ht_i
68      LOGICAL                         ::  ll_ht_s
69      REAL, POINTER, DIMENSION(:,:)   ::  a_i   !: now ice leads fraction climatology
70      REAL, POINTER, DIMENSION(:,:)   ::  ht_i  !: Now ice  thickness climatology
71      REAL, POINTER, DIMENSION(:,:)   ::  ht_s  !: now snow thickness
[3294]72#endif
[7567]73#if defined key_top
74      CHARACTER(LEN=20)                   :: cn_obc  !: type of boundary condition to apply
75      REAL(wp)                            :: rn_fac  !: multiplicative scaling factor
76      REAL(wp), POINTER, DIMENSION(:,:)   :: trc     !: now field of the tracer
77      LOGICAL                             :: dmp     !: obc damping term
78#endif
79
[3294]80   END TYPE OBC_DATA
81
[911]82   !!----------------------------------------------------------------------
83   !! Namelist variables
84   !!----------------------------------------------------------------------
[3294]85   CHARACTER(len=80), DIMENSION(jp_bdy) ::   cn_coords_file !: Name of bdy coordinates file
86   CHARACTER(len=80)                    ::   cn_mask_file   !: Name of bdy mask file
[1125]87   !
[3294]88   LOGICAL, DIMENSION(jp_bdy) ::   ln_coords_file           !: =T read bdy coordinates from file;
89   !                                                        !: =F read bdy coordinates from namelist
90   LOGICAL                    ::   ln_mask_file             !: =T read bdymask from file
91   LOGICAL                    ::   ln_vol                   !: =T volume correction             
[7567]92   !JT
93   LOGICAL, DIMENSION(jp_bdy) ::   ln_sponge                !: =T use sponge layer
94   !JT
[1125]95   !
[3294]96   INTEGER                    ::   nb_bdy                   !: number of open boundary sets
97   INTEGER, DIMENSION(jp_bdy) ::   nn_rimwidth              !: boundary rim width for Flow Relaxation Scheme
98   INTEGER                    ::   nn_volctl                !: = 0 the total volume will have the variability of the surface Flux E-P
99   !                                                        !  = 1 the volume will be constant during all the integration.
[4292]100   CHARACTER(len=20), DIMENSION(jp_bdy) ::   cn_dyn2d       ! Choice of boundary condition for barotropic variables (U,V,SSH)
101   INTEGER, DIMENSION(jp_bdy)           ::   nn_dyn2d_dta   !: = 0 use the initial state as bdy dta ;
[3294]102                                                            !: = 1 read it in a NetCDF file
103                                                            !: = 2 read tidal harmonic forcing from a NetCDF file
104                                                            !: = 3 read external data AND tidal harmonic forcing from NetCDF files
[4292]105   CHARACTER(len=20), DIMENSION(jp_bdy) ::   cn_dyn3d       ! Choice of boundary condition for baroclinic velocities
106   INTEGER, DIMENSION(jp_bdy)           ::   nn_dyn3d_dta   !: = 0 use the initial state as bdy dta ;
[3294]107                                                            !: = 1 read it in a NetCDF file
[4292]108   CHARACTER(len=20), DIMENSION(jp_bdy) ::   cn_tra         ! Choice of boundary condition for active tracers (T and S)
109   INTEGER, DIMENSION(jp_bdy)           ::   nn_tra_dta     !: = 0 use the initial state as bdy dta ;
[3294]110                                                            !: = 1 read it in a NetCDF file
[3651]111   LOGICAL, DIMENSION(jp_bdy) ::   ln_tra_dmp               !: =T Tracer damping
112   LOGICAL, DIMENSION(jp_bdy) ::   ln_dyn3d_dmp             !: =T Baroclinic velocity damping
[7567]113   
114!   !JT
115   LOGICAL, DIMENSION(jp_bdy) ::   ln_ssh_bdy               !: =T USE SSH BDY - name list switch
116!   !JT
117   
[4292]118   REAL(wp),    DIMENSION(jp_bdy) ::   rn_time_dmp              !: Damping time scale in days
119   REAL(wp),    DIMENSION(jp_bdy) ::   rn_time_dmp_out          !: Damping time scale in days at radiation outflow points
[7567]120   !JT
121   REAL(wp)                   ::   rn_sponge                  !: multiplier of diffusion for sponge layer
122   !JT
[3651]123
[4608]124   CHARACTER(len=20), DIMENSION(jp_bdy) ::   cn_ice_lim       ! Choice of boundary condition for sea ice variables
[4333]125   INTEGER, DIMENSION(jp_bdy)           ::   nn_ice_lim_dta   !: = 0 use the initial state as bdy dta ;
[4292]126                                                              !: = 1 read it in a NetCDF file
[4699]127   REAL(wp),    DIMENSION(jp_bdy) ::   rn_ice_tem             !: choice of the temperature of incoming sea ice
128   REAL(wp),    DIMENSION(jp_bdy) ::   rn_ice_sal             !: choice of the salinity    of incoming sea ice
129   REAL(wp),    DIMENSION(jp_bdy) ::   rn_ice_age             !: choice of the age         of incoming sea ice
[3294]130   !
131   
[911]132   !!----------------------------------------------------------------------
133   !! Global variables
134   !!----------------------------------------------------------------------
[4292]135   REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:,:), TARGET ::   bdytmask   !: Mask defining computational domain at T-points
136   REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:,:), TARGET ::   bdyumask   !: Mask defining computational domain at U-points
137   REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:,:), TARGET ::   bdyvmask   !: Mask defining computational domain at V-points
[7567]138   !JT
139   REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:,:) ::   sponge_factor !: Multiplier for diffusion for sponge layer
140   !JT
[911]141
[3294]142   REAL(wp)                                    ::   bdysurftot !: Lateral surface of unstructured open boundary
143
[911]144   !!----------------------------------------------------------------------
[3294]145   !! open boundary data variables
[911]146   !!----------------------------------------------------------------------
147
[3294]148   INTEGER,  DIMENSION(jp_bdy)                     ::   nn_dta            !: =0 => *all* data is set to initial conditions
149                                                                          !: =1 => some data to be read in from data files
[3651]150   REAL(wp), ALLOCATABLE, DIMENSION(:,:,:), TARGET ::   dta_global        !: workspace for reading in global data arrays (unstr.  bdy)
151   REAL(wp), ALLOCATABLE, DIMENSION(:,:,:), TARGET ::   dta_global2       !: workspace for reading in global data arrays (struct. bdy)
[4354]152!$AGRIF_DO_NOT_TREAT
[3294]153   TYPE(OBC_INDEX), DIMENSION(jp_bdy), TARGET      ::   idx_bdy           !: bdy indices (local process)
[4292]154   TYPE(OBC_DATA) , DIMENSION(jp_bdy), TARGET      ::   dta_bdy           !: bdy external data (local process)
[4354]155!$AGRIF_END_DO_NOT_TREAT
[2715]156   !!----------------------------------------------------------------------
157   !! NEMO/OPA 4.0 , NEMO Consortium (2011)
[7566]158   !! $Id$
[2715]159   !! Software governed by the CeCILL licence     (NEMOGCM/NEMO_CeCILL.txt)
160   !!----------------------------------------------------------------------
161CONTAINS
162
163   FUNCTION bdy_oce_alloc()
164      !!----------------------------------------------------------------------
165      USE lib_mpp, ONLY: ctl_warn, mpp_sum
166      !
167      INTEGER :: bdy_oce_alloc
168      !!----------------------------------------------------------------------
169      !
[7567]170      !JT ALLOCATE( bdytmask(jpi,jpj) , bdyumask(jpi,jpj), bdyvmask(jpi,jpj),     & 
171      ALLOCATE( bdytmask(jpi,jpj) , bdyumask(jpi,jpj), bdyvmask(jpi,jpj),sponge_factor(jpi,jpj),     &     
[3294]172         &      STAT=bdy_oce_alloc )
[4354]173      !
174      ! Initialize masks
175      bdytmask(:,:) = 1._wp
176      bdyumask(:,:) = 1._wp
177      bdyvmask(:,:) = 1._wp
[7567]178      !JT
179      sponge_factor(:,:) = 1._wp
180      !JT
[4354]181      !
[2715]182      IF( lk_mpp             )   CALL mpp_sum ( bdy_oce_alloc )
183      IF( bdy_oce_alloc /= 0 )   CALL ctl_warn('bdy_oce_alloc: failed to allocate arrays.')
184      !
185   END FUNCTION bdy_oce_alloc
186
[911]187#else
188   !!----------------------------------------------------------------------
[1125]189   !!   Dummy module                NO Unstructured Open Boundary Condition
[911]190   !!----------------------------------------------------------------------
[2528]191   LOGICAL ::   ln_tides = .false.  !: =T apply tidal harmonic forcing along open boundaries
[911]192#endif
193
194   !!======================================================================
195END MODULE bdy_oce
[3294]196
Note: See TracBrowser for help on using the repository browser.