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.
Changeset 3294 for trunk/NEMOGCM/NEMO/OPA_SRC/BDY/bdy_oce.F90 – NEMO

Ignore:
Timestamp:
2012-01-28T17:44:18+01:00 (12 years ago)
Author:
rblod
Message:

Merge of 3.4beta into the trunk

File:
1 edited

Legend:

Unmodified
Added
Removed
  • trunk/NEMOGCM/NEMO/OPA_SRC/BDY/bdy_oce.F90

    r2715 r3294  
    77   !!            3.0  !  2008-04  (NEMO team)  add in the reference version      
    88   !!            3.3  !  2010-09  (D. Storkey) add ice boundary conditions 
     9   !!            3.4  !  2011     (D. Storkey) rewrite in preparation for OBC-BDY merge 
    910   !!---------------------------------------------------------------------- 
    1011#if defined key_bdy  
     
    1920   PUBLIC 
    2021 
     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 
    2149   !!---------------------------------------------------------------------- 
    2250   !! Namelist variables 
    2351   !!---------------------------------------------------------------------- 
    24    CHARACTER(len=80) ::   cn_mask        !: Name of unstruct. bdy mask file 
    25    CHARACTER(len=80) ::   cn_dta_frs_T   !: Name of unstruct. bdy data file at T points for FRS conditions 
    26    CHARACTER(len=80) ::   cn_dta_frs_U   !: Name of unstruct. bdy data file at U points for FRS conditions 
    27    CHARACTER(len=80) ::   cn_dta_frs_V   !: Name of unstruct. bdy data file at V points for FRS conditions 
    28    CHARACTER(len=80) ::   cn_dta_fla_T   !: Name of unstruct. bdy data file at T points for Flather scheme 
    29    CHARACTER(len=80) ::   cn_dta_fla_U   !: Name of unstruct. bdy data file at U points for Flather scheme 
    30    CHARACTER(len=80) ::   cn_dta_fla_V   !: Name of unstruct. bdy data file at V points for Flather scheme 
     52   CHARACTER(len=80), DIMENSION(jp_bdy) ::   cn_coords_file !: Name of bdy coordinates file 
     53   CHARACTER(len=80)                    ::   cn_mask_file   !: Name of bdy mask file 
    3154   ! 
    32    LOGICAL ::   ln_tides = .false.    !: =T apply tidal harmonic forcing along open boundaries 
    33    LOGICAL ::   ln_vol  = .false.     !: =T volume correction              
    34    LOGICAL ::   ln_mask = .false.     !: =T read bdymask from file 
    35    LOGICAL ::   ln_clim = .false.     !: =T bdy data files contain  1 time dump  (-->bdy forcing will be constant)  
    36    !                                  !                         or 12 months     (-->bdy forcing will be cyclic)  
    37    LOGICAL ::   ln_dyn_fla  = .false. !: =T Flather boundary conditions on barotropic velocities 
    38    LOGICAL ::   ln_dyn_frs  = .false. !: =T FRS boundary conditions on velocities 
    39    LOGICAL ::   ln_tra_frs  = .false. !: =T FRS boundary conditions on tracers (T and S) 
    40    LOGICAL ::   ln_ice_frs  = .false. !: =T FRS boundary conditions on seaice (leads fraction, ice depth, snow depth) 
     55   LOGICAL, DIMENSION(jp_bdy) ::   ln_coords_file           !: =T read bdy coordinates from file;  
     56   !                                                        !: =F read bdy coordinates from namelist 
     57   LOGICAL                    ::   ln_mask_file             !: =T read bdymask from file 
     58   LOGICAL                    ::   ln_vol                   !: =T volume correction              
    4159   ! 
    42    INTEGER ::   nn_rimwidth = 7       !: boundary rim width 
    43    INTEGER ::   nn_dtactl   = 1       !: = 0 use the initial state as bdy dta ; = 1 read it in a NetCDF file 
    44    INTEGER ::   nn_volctl   = 1       !: = 0 the total volume will have the variability of the surface Flux E-P  
    45    !                                  !  = 1 the volume will be constant during all the integration. 
    46  
     60   INTEGER                    ::   nb_bdy                   !: number of open boundary sets 
     61   INTEGER, DIMENSION(jp_bdy) ::   nn_rimwidth              !: boundary rim width for Flow Relaxation Scheme 
     62   INTEGER                    ::   nn_volctl                !: = 0 the total volume will have the variability of the surface Flux E-P  
     63   !                                                        !  = 1 the volume will be constant during all the integration. 
     64   INTEGER, DIMENSION(jp_bdy) ::   nn_dyn2d                 ! Choice of boundary condition for barotropic variables (U,V,SSH) 
     65   INTEGER, DIMENSION(jp_bdy) ::   nn_dyn2d_dta           !: = 0 use the initial state as bdy dta ;  
     66                                                            !: = 1 read it in a NetCDF file 
     67                                                            !: = 2 read tidal harmonic forcing from a NetCDF file 
     68                                                            !: = 3 read external data AND tidal harmonic forcing from NetCDF files 
     69   INTEGER, DIMENSION(jp_bdy) ::   nn_dyn3d                 ! Choice of boundary condition for baroclinic velocities  
     70   INTEGER, DIMENSION(jp_bdy) ::   nn_dyn3d_dta           !: = 0 use the initial state as bdy dta ;  
     71                                                            !: = 1 read it in a NetCDF file 
     72   INTEGER, DIMENSION(jp_bdy) ::   nn_tra                   ! Choice of boundary condition for active tracers (T and S) 
     73   INTEGER, DIMENSION(jp_bdy) ::   nn_tra_dta             !: = 0 use the initial state as bdy dta ;  
     74                                                            !: = 1 read it in a NetCDF file 
     75#if defined key_lim2 
     76   INTEGER, DIMENSION(jp_bdy) ::   nn_ice_lim2              ! Choice of boundary condition for sea ice variables  
     77   INTEGER, DIMENSION(jp_bdy) ::   nn_ice_lim2_dta          !: = 0 use the initial state as bdy dta ;  
     78                                                            !: = 1 read it in a NetCDF file 
     79#endif 
     80   ! 
     81    
    4782   !!---------------------------------------------------------------------- 
    4883   !! Global variables 
     
    5287   REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:,:) ::   bdyvmask   !: Mask defining computational domain at V-points 
    5388 
     89   REAL(wp)                                    ::   bdysurftot !: Lateral surface of unstructured open boundary 
     90 
     91   REAL(wp), POINTER, DIMENSION(:,:)           ::   pssh       !:  
     92   REAL(wp), POINTER, DIMENSION(:,:)           ::   phur       !:  
     93   REAL(wp), POINTER, DIMENSION(:,:)           ::   phvr       !: Pointers for barotropic fields  
     94   REAL(wp), POINTER, DIMENSION(:,:)           ::   pu2d       !:  
     95   REAL(wp), POINTER, DIMENSION(:,:)           ::   pv2d       !:  
     96 
    5497   !!---------------------------------------------------------------------- 
    55    !! Unstructured open boundary data variables 
     98   !! open boundary data variables 
    5699   !!---------------------------------------------------------------------- 
    57    INTEGER, DIMENSION(jpbgrd) ::   nblen    = 0           !: Size of bdy data on a proc for each grid type 
    58    INTEGER, DIMENSION(jpbgrd) ::   nblenrim = 0           !: Size of bdy data on a proc for first rim ind 
    59    INTEGER, DIMENSION(jpbgrd) ::   nblendta = 0           !: Size of bdy data in file 
    60100 
    61    INTEGER, DIMENSION(jpbdim,jpbgrd) ::   nbi, nbj        !: i and j indices of bdy dta 
    62    INTEGER, DIMENSION(jpbdim,jpbgrd) ::   nbr             !: Discrete distance from rim points 
    63    INTEGER, DIMENSION(jpbdim,jpbgrd) ::   nbmap           !: Indices of data in file for data in memory  
    64      
    65    REAL(wp) ::   bdysurftot                               !: Lateral surface of unstructured open boundary 
    66  
    67    REAL(wp), DIMENSION(jpbdim)        ::   flagu, flagv   !: Flag for normal velocity compnt for velocity components 
    68    REAL(wp), DIMENSION(jpbdim,jpbgrd) ::   nbw            !: Rim weights of bdy data 
    69  
    70    REAL(wp), DIMENSION(jpbdim)     ::   sshbdy            !: Now clim of bdy sea surface height (Flather) 
    71    REAL(wp), DIMENSION(jpbdim)     ::   ubtbdy, vbtbdy    !: Now clim of bdy barotropic velocity components 
    72    REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:,:) ::   tbdy  , sbdy      !: Now clim of bdy temperature and salinity   
    73    REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:,:) ::   ubdy  , vbdy    !: Now clim of bdy velocity components 
    74    REAL(wp), DIMENSION(jpbdim) ::   sshtide               !: Tidal boundary array : SSH 
    75    REAL(wp), DIMENSION(jpbdim) ::   utide, vtide          !: Tidal boundary array : U and V 
    76 #if defined key_lim2 
    77    REAL(wp), DIMENSION(jpbdim) ::   frld_bdy    !: now ice leads fraction climatology    
    78    REAL(wp), DIMENSION(jpbdim) ::   hicif_bdy   !: Now ice  thickness climatology 
    79    REAL(wp), DIMENSION(jpbdim) ::   hsnif_bdy   !: now snow thickness 
    80 #endif 
     101   INTEGER,  DIMENSION(jp_bdy)                     ::   nn_dta            !: =0 => *all* data is set to initial conditions 
     102                                                                          !: =1 => some data to be read in from data files 
     103   REAL(wp), ALLOCATABLE, DIMENSION(:,:,:), TARGET ::   dta_global        !: workspace for reading in global data arrays 
     104   TYPE(OBC_INDEX), DIMENSION(jp_bdy), TARGET      ::   idx_bdy           !: bdy indices (local process) 
     105   TYPE(OBC_DATA) , DIMENSION(jp_bdy)              ::   dta_bdy           !: bdy external data (local process) 
    81106 
    82107   !!---------------------------------------------------------------------- 
     
    94119      !!---------------------------------------------------------------------- 
    95120      ! 
    96       ALLOCATE( bdytmask(jpi,jpj) , tbdy(jpbdim,jpk) , sbdy(jpbdim,jpk) ,     & 
    97          &      bdyumask(jpi,jpj) , ubdy(jpbdim,jpk) ,                        & 
    98          &      bdyvmask(jpi,jpj) , vbdy(jpbdim,jpk) ,                    STAT=bdy_oce_alloc ) 
     121      ALLOCATE( bdytmask(jpi,jpj) , bdyumask(jpi,jpj), bdyvmask(jpi,jpj),                    &   
     122         &      STAT=bdy_oce_alloc ) 
    99123         ! 
    100124      IF( lk_mpp             )   CALL mpp_sum ( bdy_oce_alloc ) 
     
    112136   !!====================================================================== 
    113137END MODULE bdy_oce 
     138 
Note: See TracChangeset for help on using the changeset viewer.