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.
obc_oce.F90 in branches/2011/UKMO_MERCATOR_obc_bdy_merge/NEMOGCM/NEMO/OPA_SRC/OBC – NEMO

source: branches/2011/UKMO_MERCATOR_obc_bdy_merge/NEMOGCM/NEMO/OPA_SRC/OBC/obc_oce.F90 @ 2814

Last change on this file since 2814 was 2814, checked in by davestorkey, 13 years ago
  1. Implement tidal harmonics forcing (UKMO version) in new structure.
  2. Other bug fixes and updates.
  • Property svn:keywords set to Id
File size: 7.8 KB
Line 
1MODULE obc_oce
2   !!======================================================================
3   !!                       ***  MODULE obc_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, J. Chanut) OBC-BDY merge
10   !!----------------------------------------------------------------------
11#if defined key_obc 
12   !!----------------------------------------------------------------------
13   !!   'key_obc'                      Unstructured Open Boundary Condition
14   !!----------------------------------------------------------------------
15   USE par_oce         ! ocean parameters
16   USE obc_par         ! Unstructured boundary parameters
17   USE lib_mpp         ! distributed memory computing
18
19   IMPLICIT NONE
20   PUBLIC
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, POINTER, DIMENSION(:,:)   ::  nbi
26      INTEGER, POINTER, DIMENSION(:,:)   ::  nbj
27      INTEGER, POINTER, DIMENSION(:,:)   ::  nbr
28      INTEGER, POINTER, DIMENSION(:,:)   ::  nbmap
29      REAL   , POINTER, DIMENSION(:,:)   ::  nbw
30      REAL   , POINTER, DIMENSION(:)     ::  flagu
31      REAL   , POINTER, DIMENSION(:)     ::  flagv
32   END TYPE OBC_INDEX
33
34   TYPE, PUBLIC ::   OBC_DATA     !: Storage for external data
35      REAL, POINTER, DIMENSION(:)     ::  ssh
36      REAL, POINTER, DIMENSION(:)     ::  u2d
37      REAL, POINTER, DIMENSION(:)     ::  v2d
38      REAL, POINTER, DIMENSION(:,:)   ::  u3d
39      REAL, POINTER, DIMENSION(:,:)   ::  v3d
40      REAL, POINTER, DIMENSION(:,:)   ::  tem
41      REAL, POINTER, DIMENSION(:,:)   ::  sal
42#if defined key_lim2
43      REAL, POINTER, DIMENSION(:)     ::  frld
44      REAL, POINTER, DIMENSION(:)     ::  hicif
45      REAL, POINTER, DIMENSION(:)     ::  hsnif
46#endif
47   END TYPE OBC_DATA
48
49   !!----------------------------------------------------------------------
50   !! Namelist variables
51   !!----------------------------------------------------------------------
52   CHARACTER(len=80), DIMENSION(jp_obc) ::   cn_coords_file !: Name of obc coordinates file
53   CHARACTER(len=80)                    ::   cn_mask_file   !: Name of obc mask file
54   !
55   LOGICAL, DIMENSION(jp_obc) ::   ln_coords_file           !: =T read obc coordinates from file;
56   !                                                        !: =F read obc coordinates from namelist
57   LOGICAL                    ::   ln_mask_file             !: =T read obcmask from file
58   LOGICAL                    ::   ln_vol                   !: =T volume correction             
59   LOGICAL, DIMENSION(jp_obc) ::   ln_clim                  !: =T obc data files contain climatological data (time-cyclic)
60   !
61   INTEGER                    ::   nb_obc                   !: number of open boundary sets
62   INTEGER, DIMENSION(jp_obc) ::   nn_rimwidth              !: boundary rim width
63   INTEGER, DIMENSION(jp_obc) ::   nn_dtactl           !: = 0 use the initial state as obc dta ;
64                                                            !: = 1 read it in a NetCDF file
65   INTEGER, DIMENSION(jp_obc) ::   nn_tides                 !: = 0 no tidal harmonic forcing
66                                                            !: = 1 apply ONLY tidal harmonic forcing for barotropic solution
67                                                            !: = 2 ADD tidal harmonic forcing to other barotropic boundary data
68   INTEGER                    ::   nn_volctl                !: = 0 the total volume will have the variability of the surface Flux E-P
69   !                                                        !  = 1 the volume will be constant during all the integration.
70   INTEGER, DIMENSION(jp_obc) ::   nn_dyn2d                 ! Choice of boundary condition for barotropic variables (U,V,SSH)
71   INTEGER, DIMENSION(jp_obc) ::   nn_dyn3d                 ! Choice of boundary condition for baroclinic velocities
72   INTEGER, DIMENSION(jp_obc) ::   nn_tra                   ! Choice of boundary condition for active tracers (T and S)
73#if defined key_lim2
74   INTEGER, DIMENSION(jp_obc) ::   nn_ice_lim2              ! Choice of boundary condition for sea ice variables
75#endif
76   !
77   INTEGER, DIMENSION(jp_obc) ::   nn_dmp2d_in              ! Damping timescale (days) for 2D solution for inward radiation or FRS
78   INTEGER, DIMENSION(jp_obc) ::   nn_dmp2d_out             ! Damping timescale (days) for 2D solution for outward radiation
79   INTEGER, DIMENSION(jp_obc) ::   nn_dmp3d_in              ! Damping timescale (days) for 3D solution for inward radiation or FRS
80   INTEGER, DIMENSION(jp_obc) ::   nn_dmp3d_out             ! Damping timescale (days) for 3D solution for outward radiation
81
82   
83   !!----------------------------------------------------------------------
84   !! Global variables
85   !!----------------------------------------------------------------------
86   REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:,:) ::   obctmask   !: Mask defining computational domain at T-points
87   REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:,:) ::   obcumask   !: Mask defining computational domain at U-points
88   REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:,:) ::   obcvmask   !: Mask defining computational domain at V-points
89
90   REAL(wp)                                    ::   obcsurftot !: Lateral surface of unstructured open boundary
91
92   REAL(wp), POINTER, DIMENSION(:,:)           ::   pssh       !:
93   REAL(wp), POINTER, DIMENSION(:,:)           ::   phur       !:
94   REAL(wp), POINTER, DIMENSION(:,:)           ::   phvr       !: Pointers for barotropic fields
95   REAL(wp), POINTER, DIMENSION(:,:)           ::   pu2d       !:
96   REAL(wp), POINTER, DIMENSION(:,:)           ::   pv2d       !:
97
98   !!----------------------------------------------------------------------
99   !! open boundary data variables
100   !!----------------------------------------------------------------------
101
102   REAL(wp), ALLOCATABLE, DIMENSION(:,:,:), TARGET ::   dta_global        !: workspace for reading in global data arrays
103   TYPE(OBC_INDEX), DIMENSION(jp_obc), TARGET      ::   idx_obc           !: obc indices (local process)
104   TYPE(OBC_DATA) , DIMENSION(jp_obc)              ::   dta_obc           !: obc external data (local process)
105
106   !!----------------------------------------------------------------------
107   !! NEMO/OPA 4.0 , NEMO Consortium (2011)
108   !! $Id$
109   !! Software governed by the CeCILL licence     (NEMOGCM/NEMO_CeCILL.txt)
110   !!----------------------------------------------------------------------
111CONTAINS
112
113   FUNCTION obc_oce_alloc()
114      !!----------------------------------------------------------------------
115      USE lib_mpp, ONLY: ctl_warn, mpp_sum
116      !
117      INTEGER :: obc_oce_alloc
118      !!----------------------------------------------------------------------
119      !
120      ALLOCATE( obctmask(jpi,jpj) , obcumask(jpi,jpj), obcvmask(jpi,jpj),                    & 
121         &      STAT=obc_oce_alloc )
122         !
123      IF( lk_mpp             )   CALL mpp_sum ( obc_oce_alloc )
124      IF( obc_oce_alloc /= 0 )   CALL ctl_warn('obc_oce_alloc: failed to allocate arrays.')
125      !
126   END FUNCTION obc_oce_alloc
127
128#else
129   !!----------------------------------------------------------------------
130   !!   Dummy module                NO Unstructured Open Boundary Condition
131   !!----------------------------------------------------------------------
132   LOGICAL ::   ln_tides = .false.  !: =T apply tidal harmonic forcing along open boundaries
133#endif
134
135   !!======================================================================
136END MODULE obc_oce
137
Note: See TracBrowser for help on using the repository browser.