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 13540 for NEMO/branches/2020/r12377_ticket2386/tests/ICE_AGRIF/MY_SRC/usrdef_hgr.F90 – NEMO

Ignore:
Timestamp:
2020-09-29T12:41:06+02:00 (4 years ago)
Author:
andmirek
Message:

Ticket #2386: update to latest trunk

Location:
NEMO/branches/2020/r12377_ticket2386
Files:
2 edited

Legend:

Unmodified
Added
Removed
  • NEMO/branches/2020/r12377_ticket2386

    • Property svn:externals
      •  

        old new  
        33^/utils/build/mk@HEAD         mk 
        44^/utils/tools@HEAD            tools 
        5 ^/vendors/AGRIF/dev@HEAD      ext/AGRIF 
         5^/vendors/AGRIF/dev_r12970_AGRIF_CMEMS      ext/AGRIF 
        66^/vendors/FCM@HEAD            ext/FCM 
        77^/vendors/IOIPSL@HEAD         ext/IOIPSL 
        88 
        99# SETTE 
        10 ^/utils/CI/sette@HEAD         sette 
         10^/utils/CI/sette@13507        sette 
  • NEMO/branches/2020/r12377_ticket2386/tests/ICE_AGRIF/MY_SRC/usrdef_hgr.F90

    r10516 r13540  
    2626   PUBLIC   usr_def_hgr   ! called by domhgr.F90 
    2727 
     28   !! * Substitutions 
     29#  include "do_loop_substitute.h90" 
    2830   !!---------------------------------------------------------------------- 
    2931   !! NEMO/OCE 4.0 , NEMO Consortium (2018) 
     
    6264      REAL(wp), DIMENSION(:,:), INTENT(out) ::   pe1e2u, pe1e2v               ! u- & v-surfaces (if reduction in strait)   [m2] 
    6365      ! 
    64       INTEGER  ::   ji, jj   ! dummy loop indices 
     66      INTEGER  ::   ji, jj     ! dummy loop indices 
    6567      REAL(wp) ::   zphi0, zlam0, zbeta, zf0 
    66       REAL(wp) ::   zti, zui, ztj, zvj   ! local scalars 
     68      REAL(wp) ::   zti, ztj   ! local scalars 
    6769      !!------------------------------------------------------------------------------- 
    6870      ! 
     
    7476 
    7577      !                          ========== 
    76       zlam0 = -(jpiglo-1)/2 * 1.e-3 * rn_dx 
    77       zphi0 = -(jpjglo-1)/2 * 1.e-3 * rn_dy 
    78  
    7978#if defined key_agrif  
    80       IF( .NOT. Agrif_Root() ) THEN 
     79      IF( Agrif_Root() ) THEN 
     80#endif 
     81         ! Compatibility WITH old version:  
     82         ! jperio = 7 =>  Ni0glo = jpigo_old_version - 2 
     83         !            =>  jpiglo-1 replaced by Ni0glo+1 
     84         zlam0 = -REAL( (Ni0glo+1)/2, wp) * 1.e-3 * rn_dx 
     85         zphi0 = -REAL( (Nj0glo+1)/2, wp) * 1.e-3 * rn_dy   ! +1 for compatibility with old version --> to be replaced by -1 as before 
     86#if defined key_agrif  
     87      ELSE 
     88         ! ! let lower left longitude and latitude from parent 
    8189!clem         zlam0  = Agrif_Parent(zlam0) + (Agrif_ix())*Agrif_Parent(rn_dx) * 1.e-5 
    8290!clem         zphi0  = Agrif_Parent(zphi0) + (Agrif_iy())*Agrif_Parent(rn_dy) * 1.e-5 
    83          zlam0 = ( 0.5_wp - ( Agrif_parent(jpiglo) - 1 ) / 2 ) * 1.e-3 * Agrif_irhox() * rn_dx  & 
     91         ! Compatibility WITH old version:  
     92         ! jperio = 0 =>  Ni0glo = jpigo_old_version 
     93         !            =>  Agrif_parent(jpiglo)-1 replaced by  Agrif_parent(Ni0glo)-1 
     94         zlam0 = ( 0.5_wp - REAL( ( Agrif_parent(Ni0glo)-1 ) / 2, wp) ) * 1.e-3 * Agrif_irhox() * rn_dx  & 
    8495            &  + ( Agrif_Ix() + nbghostcells - 1 ) * Agrif_irhox() * rn_dx * 1.e-3 - ( 0.5_wp + nbghostcells ) * rn_dx * 1.e-3 
    85          zphi0 = ( 0.5_wp - ( Agrif_parent(jpjglo) - 1 ) / 2 ) * 1.e-3 * Agrif_irhoy() * rn_dy  & 
     96         zphi0 = ( 0.5_wp - REAL( ( Agrif_parent(Nj0glo)-1 ) / 2, wp) ) * 1.e-3 * Agrif_irhoy() * rn_dy  & 
    8697            &  + ( Agrif_Iy() + nbghostcells - 1 ) * Agrif_irhoy() * rn_dy * 1.e-3 - ( 0.5_wp + nbghostcells ) * rn_dy * 1.e-3 
    8798      ENDIF 
    8899#endif          
    89100 
    90       DO jj = 1, jpj 
    91          DO ji = 1, jpi 
    92             zti = FLOAT( ji - 1 + nimpp - 1 )          ;  ztj = FLOAT( jj - 1 + njmpp - 1 ) 
    93             zui = FLOAT( ji - 1 + nimpp - 1 ) + 0.5_wp ;  zvj = FLOAT( jj - 1 + njmpp - 1 ) + 0.5_wp 
    94  
    95             plamt(ji,jj) = zlam0 + rn_dx * 1.e-3 * zti 
    96             plamu(ji,jj) = zlam0 + rn_dx * 1.e-3 * zui 
    97             plamv(ji,jj) = plamt(ji,jj)  
    98             plamf(ji,jj) = plamu(ji,jj)  
    99     
    100             pphit(ji,jj) = zphi0 + rn_dy * 1.e-3 * ztj 
    101             pphiv(ji,jj) = zphi0 + rn_dy * 1.e-3 * zvj 
    102             pphiu(ji,jj) = pphit(ji,jj)  
    103             pphif(ji,jj) = pphiv(ji,jj)  
    104          END DO 
    105       END DO 
     101      DO_2D( 1, 1, 1, 1 ) 
     102         zti = REAL( mig0_oldcmp(ji) - 1, wp )   ! start at i=0 in the global grid without halos 
     103         ztj = REAL( mjg0_oldcmp(jj) - 1, wp )   ! start at j=0 in the global grid without halos 
     104          
     105         plamt(ji,jj) = zlam0 + rn_dx * 1.e-3 *   zti 
     106         plamu(ji,jj) = zlam0 + rn_dx * 1.e-3 * ( zti + 0.5_wp ) 
     107         plamv(ji,jj) = plamt(ji,jj)  
     108         plamf(ji,jj) = plamu(ji,jj)  
     109          
     110         pphit(ji,jj) = zphi0 + rn_dy * 1.e-3 *   ztj 
     111         pphiv(ji,jj) = zphi0 + rn_dy * 1.e-3 * ( ztj + 0.5_wp ) 
     112         pphiu(ji,jj) = pphit(ji,jj)  
     113         pphif(ji,jj) = pphiv(ji,jj)  
     114      END_2D 
    106115          
    107116         ! Horizontal scale factors (in meters) 
Note: See TracChangeset for help on using the changeset viewer.