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 5845 for branches/2015/dev_r5836_NOC3_vvl_by_default/NEMOGCM/NEMO/OPA_SRC/CRS/crsdom.F90 – NEMO

Ignore:
Timestamp:
2015-10-31T08:40:45+01:00 (8 years ago)
Author:
gm
Message:

#1613: vvl by default: suppression of domzgr_substitute.h90

File:
1 edited

Legend:

Unmodified
Added
Removed
  • branches/2015/dev_r5836_NOC3_vvl_by_default/NEMOGCM/NEMO/OPA_SRC/CRS/crsdom.F90

    r5302 r5845  
    3030   !!       Original.   May 2012.  (J. Simeon, C. Calone, G. Madec, C. Ethe) 
    3131   !!=================================================================== 
    32  
    3332   USE dom_oce        ! ocean space and time domain and to get jperio 
    34    USE wrk_nemo       ! work arrays 
    3533   USE crs            ! domain for coarse grid 
     34   ! 
    3635   USE in_out_manager  
    3736   USE par_kind 
    3837   USE crslbclnk 
     38   USE wrk_nemo       ! work arrays 
    3939   USE lib_mpp 
    40     
    4140 
    4241   IMPLICIT NONE 
     
    5453   REAL(wp) :: r_inf = 1e+36 
    5554 
    56    !! Substitutions 
    57 #  include "domzgr_substitute.h90" 
    58     
     55   !!---------------------------------------------------------------------- 
     56   !! NEMO/OPA 3.3 , NEMO Consortium (2010) 
    5957   !! $Id$ 
     58   !! Software governed by the CeCILL licence     (NEMOGCM/NEMO_CeCILL.txt) 
     59   !!---------------------------------------------------------------------- 
    6060CONTAINS 
    61  
    6261 
    6362   SUBROUTINE crs_dom_msk 
     
    133132   END SUBROUTINE crs_dom_msk 
    134133 
     134 
    135135   SUBROUTINE crs_dom_coordinates( p_gphi, p_glam, cd_type, p_gphi_crs, p_glam_crs ) 
    136136      !!---------------------------------------------------------------- 
     
    334334      !!              cd_type     = grid type (T,U,V,F) for scale factors; for velocities (U or V) 
    335335      !!              cd_op       = applied operation (SUM, VOL, WGT) 
    336       !!              p_fse3      = (Optional) parent grid vertical level thickness (fse3u or fse3v) 
     336      !!              p_e3      = (Optional) parent grid vertical level thickness (e3u or e3v) 
    337337      !! ** Outputs : p_cfield2d_1 = (Optional) 2D field on coarse grid 
    338338      !!              p_cfield2d_2 = (Optional) 2D field on coarse grid 
     
    348348      REAL(wp), DIMENSION(jpi,jpj)            , INTENT(in)  :: p_e1     ! Parent grid U,V scale factors (e1) 
    349349      REAL(wp), DIMENSION(jpi,jpj)            , INTENT(in)  :: p_e2     ! Parent grid U,V scale factors (e2) 
    350       REAL(wp), DIMENSION(jpi,jpj,jpk)        , INTENT(in)  :: p_e3     ! Parent grid vertical level thickness (fse3u, fse3v) 
     350      REAL(wp), DIMENSION(jpi,jpj,jpk)        , INTENT(in)  :: p_e3     ! Parent grid vertical level thickness (e3u, e3v) 
    351351 
    352352      REAL(wp), DIMENSION(jpi_crs,jpj_crs,jpk), INTENT(out) :: p_fld1_crs ! Coarse grid box 3D quantity  
     
    469469      !!              p_pmask     = parent grid mask (T,U,V,F) for scale factors;  
    470470      !!                                       for velocities (U or V) 
    471       !!              p_fse3      = parent grid vertical level thickness (fse3u or fse3v) 
     471      !!              p_e3      = parent grid vertical level thickness (e3u or e3v) 
    472472      !!              p_pfield    = U or V on the parent grid 
    473473      !!              p_surf_crs  = (Optional) Coarse grid weight for averaging 
     
    478478      !!            5 Jun.  Streamline for area-weighted average only ; separate scale factor and weights. 
    479479      !!---------------------------------------------------------------- 
    480       !!  
    481       !!  Arguments 
    482480      REAL(wp), DIMENSION(jpi,jpj,jpk),         INTENT(in)           :: p_fld   ! T, U, V or W on parent grid 
    483481      CHARACTER(len=3),                         INTENT(in)           :: cd_op    ! Operation SUM, MAX or MIN 
     
    485483      REAL(wp), DIMENSION(jpi,jpj,jpk),         INTENT(in)           :: p_mask    ! Parent grid T,U,V mask 
    486484      REAL(wp), DIMENSION(jpi,jpj),             INTENT(in), OPTIONAL :: p_e12    ! Parent grid T,U,V scale factors (e1 or e2) 
    487       REAL(wp), DIMENSION(jpi,jpj,jpk),         INTENT(in), OPTIONAL :: p_e3     ! Parent grid vertical level thickness (fse3u, fse3v) 
     485      REAL(wp), DIMENSION(jpi,jpj,jpk),         INTENT(in), OPTIONAL :: p_e3     ! Parent grid vertical level thickness (e3u, e3v) 
    488486      REAL(wp), DIMENSION(jpi_crs,jpj_crs,jpk), INTENT(in), OPTIONAL :: p_surf_crs ! Coarse grid area-weighting denominator     
    489487      REAL(wp), DIMENSION(jpi_crs,jpj_crs,jpk), INTENT(in), OPTIONAL :: p_mask_crs    ! Coarse grid T,U,V maska 
    490488      REAL(wp),                                 INTENT(in)           :: psgn    ! sign  
    491  
    492  
    493       REAL(wp), DIMENSION(jpi_crs,jpj_crs,jpk), INTENT(out)          :: p_fld_crs ! Coarse grid box 3D quantity  
    494  
    495       !! Local variables 
     489      REAL(wp), DIMENSION(jpi_crs,jpj_crs,jpk), INTENT(  out)        :: p_fld_crs ! Coarse grid box 3D quantity  
     490      ! 
    496491      INTEGER  :: ji, jj, jk  
    497492      INTEGER  :: ii, ij, ijie, ijje, je_2 
     
    499494      REAL(wp), DIMENSION(:,:,:), POINTER :: zsurf, zsurfmsk, zmask   
    500495      !!----------------------------------------------------------------   
    501     
    502       p_fld_crs(:,:,:) = 0.0 
    503  
     496      ! 
     497      p_fld_crs(:,:,:) = 0._wp 
     498      ! 
    504499      SELECT CASE ( cd_op ) 
    505500       
     
    11361131      !!              p_pmask     = parent grid mask (T,U,V,F) for scale factors;  
    11371132      !!                                       for velocities (U or V) 
    1138       !!              p_fse3      = parent grid vertical level thickness (fse3u or fse3v) 
     1133      !!              p_e3      = parent grid vertical level thickness (e3u or e3v) 
    11391134      !!              p_pfield    = U or V on the parent grid 
    11401135      !!              p_surf_crs  = (Optional) Coarse grid weight for averaging 
     
    11521147      REAL(wp), DIMENSION(jpi,jpj,jpk),         INTENT(in)           :: p_mask    ! Parent grid T,U,V mask 
    11531148      REAL(wp), DIMENSION(jpi,jpj),             INTENT(in), OPTIONAL :: p_e12    ! Parent grid T,U,V scale factors (e1 or e2) 
    1154       REAL(wp), DIMENSION(jpi,jpj,jpk),         INTENT(in), OPTIONAL :: p_e3     ! Parent grid vertical level thickness (fse3u, fse3v) 
     1149      REAL(wp), DIMENSION(jpi,jpj,jpk),         INTENT(in), OPTIONAL :: p_e3     ! Parent grid vertical level thickness (e3u, e3v) 
    11551150      REAL(wp), DIMENSION(jpi_crs,jpj_crs)    , INTENT(in), OPTIONAL :: p_surf_crs ! Coarse grid area-weighting denominator     
    11561151      REAL(wp), DIMENSION(jpi_crs,jpj_crs,jpk), INTENT(in), OPTIONAL :: p_mask_crs    ! Coarse grid T,U,V mask 
Note: See TracChangeset for help on using the changeset viewer.