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 9089 for branches/2017/dev_merge_2017/NEMOGCM/CONFIG/TEST_CASES/ISOMIP/MY_SRC/usrdef_hgr.F90 – NEMO

Ignore:
Timestamp:
2017-12-15T18:00:09+01:00 (6 years ago)
Author:
gm
Message:

dev_merge_2017: bug correction in zdfdrg + ISOMIP cfg

File:
1 edited

Legend:

Unmodified
Added
Removed
  • branches/2017/dev_merge_2017/NEMOGCM/CONFIG/TEST_CASES/ISOMIP/MY_SRC/usrdef_hgr.F90

    r9019 r9089  
    1717   USE par_oce         ! ocean space and time domain 
    1818   USE phycst          ! physical constants 
    19    USE usrdef_nam, ONLY: rn_lam0, rn_phi0, rn_e1deg, rn_e2deg   ! horizontal resolution in meters 
     19   USE usrdef_nam, ONLY: rn_e1deg, rn_e2deg   ! horizontal resolution in meters 
    2020   ! 
    2121   USE in_out_manager  ! I/O manager 
    2222   USE lib_mpp         ! MPP library 
    23    USE timing          ! Timing 
    2423    
    2524   IMPLICIT NONE 
     
    2928 
    3029   !!---------------------------------------------------------------------- 
    31    !! NEMO/OPA 4.0 , NEMO Consortium (2016) 
     30   !! NEMO/OPA 4.0 , NEMO Consortium (2017) 
    3231   !! $Id$  
    3332   !! Software governed by the CeCILL licence     (NEMOGCM/NEMO_CeCILL.txt) 
     
    6665      !!------------------------------------------------------------------------------- 
    6766      ! 
    68       IF( nn_timing == 1 )  CALL timing_start('usr_def_hgr') 
    69       ! 
    7067      IF(lwp) THEN 
    7168         WRITE(numout,*) 
     
    7976      !                       !==  grid point position  ==!   (in degrees) 
    8077      DO jj = 1, jpj 
     78         DO ji = 1, jpi             ! longitude   (west coast at lon=0°) 
     79            plamt(ji,jj) = rn_e1deg * (  - 0.5 + REAL( ji-1 + nimpp-1 , wp )  )   
     80            plamu(ji,jj) = rn_e1deg * (          REAL( ji-1 + nimpp-1 , wp )  ) 
     81            plamv(ji,jj) = plamt(ji,jj) 
     82            plamf(ji,jj) = plamu(ji,jj) 
     83            !                       ! latitude   (south coast at lat= 81°) 
     84            pphit(ji,jj) = rn_e2deg * (  - 0.5 + REAL( jj-1 + njmpp-1 , wp )  ) - 80._wp 
     85            pphiu(ji,jj) = pphit(ji,jj) 
     86            pphiv(ji,jj) = rn_e2deg * (          REAL( jj-1 + njmpp-1 , wp )  ) - 80_wp 
     87            pphif(ji,jj) = pphiv(ji,jj) 
     88         END DO 
     89      END DO 
     90      ! 
     91      !                       !==  Horizontal scale factors  ==!   (in meters) 
     92      DO jj = 1, jpj 
    8193         DO ji = 1, jpi 
    82             zti = FLOAT( ji - 1 + nimpp - 1 )         ;   ztj = FLOAT( jj - 1 + njmpp - 1 ) 
    83             zui = FLOAT( ji - 1 + nimpp - 1 ) + 0.5   ;   zuj = FLOAT( jj - 1 + njmpp - 1 ) 
    84             zvi = FLOAT( ji - 1 + nimpp - 1 )         ;   zvj = FLOAT( jj - 1 + njmpp - 1 ) + 0.5 
    85             zfi = FLOAT( ji - 1 + nimpp - 1 ) + 0.5   ;   zfj = FLOAT( jj - 1 + njmpp - 1 ) + 0.5 
    86      ! Longitude 
    87             plamt(ji,jj) = rn_lam0 + rn_e1deg * zti 
    88             plamu(ji,jj) = rn_lam0 + rn_e1deg * zui 
    89             plamv(ji,jj) = rn_lam0 + rn_e1deg * zvi 
    90             plamf(ji,jj) = rn_lam0 + rn_e1deg * zfi 
    91      ! Latitude 
    92             pphit(ji,jj) = rn_phi0 + rn_e2deg * ztj 
    93             pphiu(ji,jj) = rn_phi0 + rn_e2deg * zuj 
    94             pphiv(ji,jj) = rn_phi0 + rn_e2deg * zvj 
    95             pphif(ji,jj) = rn_phi0 + rn_e2deg * zfj 
    96              
    97      !                       !==  Horizontal scale factors  ==!   (in meters) 
    98      ! e1 
     94            !                       ! e1   (zonal) 
    9995            pe1t(ji,jj) = ra * rad * COS( rad * pphit(ji,jj) ) * rn_e1deg 
    10096            pe1u(ji,jj) = ra * rad * COS( rad * pphiu(ji,jj) ) * rn_e1deg 
    10197            pe1v(ji,jj) = ra * rad * COS( rad * pphiv(ji,jj) ) * rn_e1deg 
    10298            pe1f(ji,jj) = ra * rad * COS( rad * pphif(ji,jj) ) * rn_e1deg 
    103      ! e2 
     99            !                       ! e2   (meridional) 
    104100            pe2t(ji,jj) = ra * rad * rn_e2deg 
    105101            pe2u(ji,jj) = ra * rad * rn_e2deg 
     
    109105      END DO 
    110106      !                             ! NO reduction of grid size in some straits  
    111       ke1e2u_v = 0                  !    ==>> u_ & v_surfaces will be computed in dom_ghr routine 
     107      ke1e2u_v    = 0               !    ==>> u_ & v_surfaces will be computed in dom_ghr routine 
    112108      pe1e2u(:,:) = 0._wp           !    CAUTION: set to zero to avoid error with some compilers that 
    113109      pe1e2v(:,:) = 0._wp           !             require an initialization of INTENT(out) arguments 
     
    116112      !                       !==  Coriolis parameter  ==! 
    117113      kff = 0                       ! Coriolis parameter calculated on the sphere 
    118       ! 
    119       ! 
    120114      pff_f(:,:) = 0._wp            ! CAUTION: set to zero to avoid error with some compilers that 
    121115      pff_t(:,:) = 0._wp            !             require an initialization of INTENT(out) arguments 
    122       ! 
    123       IF( nn_timing == 1 )  CALL timing_stop('usr_def_hgr') 
    124116      ! 
    125117   END SUBROUTINE usr_def_hgr 
Note: See TracChangeset for help on using the changeset viewer.