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 9763 for NEMO/trunk/tests – NEMO

Changeset 9763 for NEMO/trunk/tests


Ignore:
Timestamp:
2018-06-07T17:36:49+02:00 (6 years ago)
Author:
clem
Message:

repair broken reproducibility in SAS_BIPER

Location:
NEMO/trunk/tests/SAS_BIPER
Files:
4 edited

Legend:

Unmodified
Added
Removed
  • NEMO/trunk/tests/SAS_BIPER/EXPREF/1_namelist_cfg

    r9718 r9763  
    2222   rn_dx       =    1000.   ! horizontal resolution in meters 
    2323   rn_dy       =    1000.   ! horizontal resolution in meters 
     24   rn_ppgphi0  =     70.    ! Reference latitude [degrees] 
    2425/ 
    2526!----------------------------------------------------------------------- 
  • NEMO/trunk/tests/SAS_BIPER/EXPREF/namelist_cfg

    r9743 r9763  
    2222   rn_dx       =    3000.   ! horizontal resolution in meters 
    2323   rn_dy       =    3000.   ! horizontal resolution in meters 
     24   rn_ppgphi0  =     70.    ! Reference latitude [degrees] 
    2425/ 
    2526!----------------------------------------------------------------------- 
  • NEMO/trunk/tests/SAS_BIPER/MY_SRC/usrdef_hgr.F90

    r9154 r9763  
    1616   USE par_oce         ! ocean space and time domain 
    1717   USE phycst          ! physical constants 
    18    USE usrdef_nam, ONLY: rn_dx, rn_dy   ! horizontal resolution in meters 
    19    ! 
     18   USE usrdef_nam, ONLY: rn_dx, rn_dy, rn_ppgphi0   ! horizontal resolution in meters 
     19   !                                                  and reference latitude 
    2020   USE in_out_manager  ! I/O manager 
    2121   USE lib_mpp         ! MPP library 
     
    6464      INTEGER  ::   ji, jj   ! dummy loop indices 
    6565      REAL(wp) ::   zphi0, zlam0, zbeta, zf0 
    66       REAL(wp) ::   zti, zui, zvi, zfi   ! local scalars 
    67       REAL(wp) ::   ztj, zuj, zvj, zfj   !   -      - 
     66      REAL(wp) ::   zti, zui, ztj, zvj   ! local scalars 
    6867      !!------------------------------------------------------------------------------- 
    6968      ! 
     
    7574 
    7675      !                          ========== 
    77 !clem      zlam0 = 0._wp 
    78 !clem      zphi0 = 0._wp 
    7976      zlam0 = -(jpiglo-1)/2 * 1.e-3 * rn_dx 
    8077      zphi0 = -(jpjglo-1)/2 * 1.e-3 * rn_dy 
     
    8885         zphi0 = ( 0.5_wp - ( Agrif_parent(jpjglo) - 1 ) / 2 ) * 1.e-3 * Agrif_irhoy() * rn_dy  & 
    8986            &  + ( Agrif_Iy() + nbghostcells - 1 ) * Agrif_irhoy() * rn_dy * 1.e-3 - ( 0.5_wp + nbghostcells ) * rn_dy * 1.e-3 
    90          rn_dx = Agrif_Parent(rn_dx)/Agrif_Rhox() 
    91          rn_dy = Agrif_Parent(rn_dy)/Agrif_Rhoy()           
    9287      ENDIF 
    9388#endif          
     
    9590      DO jj = 1, jpj 
    9691         DO ji = 1, jpi 
    97             zti = FLOAT( ji - 1 + nimpp - 1 )         ;   ztj = FLOAT( jj - 1 + njmpp - 1 ) 
    98             zui = FLOAT( ji - 1 + nimpp - 1 ) + 0.5   ;   zuj = FLOAT( jj - 1 + njmpp - 1 ) 
    99             zvi = FLOAT( ji - 1 + nimpp - 1 )         ;   zvj = FLOAT( jj - 1 + njmpp - 1 ) + 0.5 
    100             zfi = FLOAT( ji - 1 + nimpp - 1 ) + 0.5   ;   zfj = FLOAT( jj - 1 + njmpp - 1 ) + 0.5 
     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 
    10194 
    102             plamt(ji,jj) = zlam0 + rn_dx * 1.e-5 * zti 
    103             plamu(ji,jj) = zlam0 + rn_dx * 1.e-5 * zui 
    104             plamv(ji,jj) = zlam0 + rn_dx * 1.e-5 * zvi 
    105             plamf(ji,jj) = zlam0 + rn_dx * 1.e-5 * zfi 
     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)  
    10699    
    107             pphit(ji,jj) = zphi0 + rn_dy * 1.e-5 * ztj 
    108             pphiu(ji,jj) = zphi0 + rn_dy * 1.e-5 * zuj 
    109             pphiv(ji,jj) = zphi0 + rn_dy * 1.e-5 * zvj 
    110             pphif(ji,jj) = zphi0 + rn_dy * 1.e-5 * zfj 
     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)  
    111104         END DO 
    112105      END DO 
     
    115108         !                              ====== 
    116109!! ==> EITHER 1) variable scale factors 
    117          DO jj = 1, jpj 
    118             DO ji = 1, jpi 
    119                !!pe1t(ji,jj) = rn_dx * EXP( -0.8/REAL(jpiglo**2) * (mi0(ji)-REAL(jpiglo+1)*0.5)**2 )  ! gaussian shape 
    120                !!pe2t(ji,jj) = rn_dy * EXP( -0.8/REAL(jpjglo**2) * (mj0(jj)-REAL(jpjglo+1)*0.5)**2 )  ! gaussian shape 
    121                pe1t(ji,jj) = rn_dx * ( 1. -0.1 * ABS(REAL(mi0(ji))-REAL(jpiglo+1)*0.5) / (1.-REAL(jpiglo+1)*0.5) ) ! linear shape 
    122                pe2t(ji,jj) = rn_dy * ( 1. -0.1 * ABS(REAL(mj0(jj))-REAL(jpjglo+1)*0.5) / (1.-REAL(jpjglo+1)*0.5) ) ! linear shape 
    123             END DO 
    124          END DO 
    125 #if defined key_agrif  
    126          IF( .NOT. Agrif_Root() ) THEN ! only works if the zoom is positioned at the center of the parent grid 
    127             DO jj = 1, jpj 
    128                DO ji = 1, jpi 
    129                   pe1t(ji,jj) = rn_dx * ( 1. -0.1 * ABS(REAL(mi0(ji))-REAL(jpiglo+1)*0.5) / (1.-REAL(jpiglo+1)*0.5)  & 
    130                      &                            * REAL(jpiglo) / REAL(Agrif_Parent(jpiglo) * Agrif_Rhox()) )       ! factor to match parent grid 
    131                   pe2t(ji,jj) = rn_dy * ( 1. -0.1 * ABS(REAL(mj0(jj))-REAL(jpjglo+1)*0.5) / (1.-REAL(jpjglo+1)*0.5)  & 
    132                      &                            * REAL(jpjglo) / REAL(Agrif_Parent(jpjglo) * Agrif_Rhoy()) )       ! factor to match parent grid 
    133                END DO 
    134             END DO 
    135          ENDIF 
    136 #endif 
     110!! clem: This can be used with a 1proc simulation but I think it breaks repro when >1procs are used       
     111!!         DO jj = 1, jpj 
     112!!            DO ji = 1, jpi 
     113!!               !!pe1t(ji,jj) = rn_dx * EXP( -0.8/REAL(jpiglo**2) * (mi0(ji)-REAL(jpiglo+1)*0.5)**2 )  ! gaussian shape 
     114!!               !!pe2t(ji,jj) = rn_dy * EXP( -0.8/REAL(jpjglo**2) * (mj0(jj)-REAL(jpjglo+1)*0.5)**2 )  ! gaussian shape 
     115!!               pe1t(ji,jj) = rn_dx * ( 1. -0.1 * ABS(REAL(mi0(ji))-REAL(jpiglo+1)*0.5) / (1.-REAL(jpiglo+1)*0.5) ) ! linear shape 
     116!!               pe2t(ji,jj) = rn_dy * ( 1. -0.1 * ABS(REAL(mj0(jj))-REAL(jpjglo+1)*0.5) / (1.-REAL(jpjglo+1)*0.5) ) ! linear shape 
     117!!            END DO 
     118!!         END DO 
     119!!#if defined key_agrif  
     120!!         IF( .NOT. Agrif_Root() ) THEN ! only works if the zoom is positioned at the center of the parent grid 
     121!!            DO jj = 1, jpj 
     122!!               DO ji = 1, jpi 
     123!!                  pe1t(ji,jj) = rn_dx * ( 1. -0.1 * ABS(REAL(mi0(ji))-REAL(jpiglo+1)*0.5) / (1.-REAL(jpiglo+1)*0.5)  & 
     124!!                     &                            * REAL(jpiglo) / REAL(Agrif_Parent(jpiglo) * Agrif_Rhox()) )       ! factor to match parent grid 
     125!!                  pe2t(ji,jj) = rn_dy * ( 1. -0.1 * ABS(REAL(mj0(jj))-REAL(jpjglo+1)*0.5) / (1.-REAL(jpjglo+1)*0.5)  & 
     126!!                     &                            * REAL(jpjglo) / REAL(Agrif_Parent(jpjglo) * Agrif_Rhoy()) )       ! factor to match parent grid 
     127!!               END DO 
     128!!            END DO 
     129!!         ENDIF 
     130!!#endif 
    137131!! ==> OR 2) constant scale factors 
    138 !!         pe1t(:,:) = rn_dx 
    139 !!         pe2t(:,:) = rn_dy 
     132         pe1t(:,:) = rn_dx 
     133         pe2t(:,:) = rn_dy 
     134!! ==> END 
    140135          
    141          pe1u(:,:) = pe1t(:,:)      ;      pe2u(:,:) = pe2t(:,:) 
    142          pe1v(:,:) = pe1t(:,:)      ;      pe2v(:,:) = pe2t(:,:) 
    143          pe1f(:,:) = pe1t(:,:)      ;      pe2f(:,:) = pe2t(:,:) 
     136      pe1u(:,:) = pe1t(:,:)      ;      pe2u(:,:) = pe2t(:,:) 
     137      pe1v(:,:) = pe1t(:,:)      ;      pe2v(:,:) = pe2t(:,:) 
     138      pe1f(:,:) = pe1t(:,:)      ;      pe2f(:,:) = pe2t(:,:) 
    144139 
    145140      !                             ! NO reduction of grid size in some straits  
     
    152147      kff = 1                       !  indicate not to compute Coriolis parameter afterward 
    153148      ! 
    154 !!jerome      zbeta = 2._wp * omega * COS( rad * rn_ppgphi0 ) / ra 
    155 !!      zf0   = 2._wp * omega * SIN( rad * rn_ppgphi0 ) 
    156 !!      pff_f(:,:) = zf0 + zbeta * pphif(:,:) * 1.e+3 
    157 !!jerome      pff_t(:,:) = zf0 + zbeta * pphit(:,:) * 1.e+3 
    158       pff_f(:,:) = 0._wp            ! here No earth rotation: f=0 
    159       pff_t(:,:) = 0._wp 
     149      zbeta = 2._wp * omega * COS( rad * rn_ppgphi0 ) / ra 
     150      zf0   = 2._wp * omega * SIN( rad * rn_ppgphi0 ) 
     151      pff_f(:,:) = zf0 + zbeta * pphif(:,:) * 1.e+3 
     152      pff_t(:,:) = zf0 + zbeta * pphit(:,:) * 1.e+3 
    160153      ! 
    161154   END SUBROUTINE usr_def_hgr 
  • NEMO/trunk/tests/SAS_BIPER/MY_SRC/usrdef_nam.F90

    r9460 r9763  
    1515   !!---------------------------------------------------------------------- 
    1616   USE dom_oce  , ONLY: nimpp , njmpp            ! i- & j-indices of the local domain 
    17    USE dom_oce  , ONLY: ln_zco, ln_zps, ln_sco   ! flag of type of coordinate 
    1817   USE par_oce        ! ocean space and time domain 
    1918   USE phycst         ! physical constants 
     
    2827   PUBLIC   usr_def_nam   ! called by nemogcm.F90 
    2928 
    30    !                              !!* namusr_def namelist *!! 
    31    REAL(wp), PUBLIC ::   rn_dx     ! resolution in meters defining the horizontal domain size 
    32    REAL(wp), PUBLIC ::   rn_dy     ! resolution in meters defining the horizontal domain size 
     29   !                               !!* namusr_def namelist *!! 
     30   REAL(wp), PUBLIC ::   rn_dx      ! resolution in meters defining the horizontal domain size 
     31   REAL(wp), PUBLIC ::   rn_dy      ! resolution in meters defining the horizontal domain size 
     32   REAL(wp), PUBLIC ::   rn_ppgphi0 ! reference latitude for beta-plane  
    3333 
    3434   !!---------------------------------------------------------------------- 
     
    5858      ! 
    5959      INTEGER ::   ios, ii   ! Local integer 
     60      REAL(wp)::   zlx, zly  ! Local scalars 
    6061      !! 
    61       NAMELIST/namusr_def/ ln_zco, rn_dx, rn_dy 
     62      NAMELIST/namusr_def/ ln_zco, rn_dx, rn_dy, rn_ppgphi0 
    6263      !!---------------------------------------------------------------------- 
    6364      ! 
     
    6768      READ  ( numnam_cfg, namusr_def, IOSTAT = ios, ERR = 902 ) 
    6869902   IF( ios /= 0 )   CALL ctl_nam ( ios , 'namusr_def in configuration namelist', .TRUE. ) 
     70      ! 
     71#if defined key_agrif  
     72      ! Domain parameters are taken from parent: 
     73      IF( .NOT. Agrif_Root() ) THEN 
     74         rn_dx = Agrif_Parent(rn_dx)/Agrif_Rhox() 
     75         rn_dy = Agrif_Parent(rn_dy)/Agrif_Rhoy() 
     76         rn_ppgphi0 = Agrif_Parent(rn_ppgphi0) 
     77      ENDIF 
     78#endif 
    6979      ! 
    7080      WRITE( ldnam(:), namusr_def ) 
     
    8494      kpk = 1 
    8595      ! 
     96!!      zlx = (kpi-2)*rn_dx*1.e-3 
     97!!      zly = (kpj-2)*rn_dy*1.e-3 
     98      zlx = kpi*rn_dx*1.e-3 
     99      zly = kpj*rn_dy*1.e-3 
    86100      !                             ! control print 
    87101      WRITE(ldtxt(ii),*) '   '                                                                          ;   ii = ii + 1 
     
    89103      WRITE(ldtxt(ii),*) '~~~~~~~~~~~ '                                                                 ;   ii = ii + 1 
    90104      WRITE(ldtxt(ii),*) '   Namelist namusr_def : SAS_BIPER test case'                                 ;   ii = ii + 1 
    91       WRITE(ldtxt(ii),*) '      type of vertical coordinate : '                                         ;   ii = ii + 1 
    92       WRITE(ldtxt(ii),*) '         z-coordinate flag                     ln_zco = ', ln_zco             ;   ii = ii + 1 
    93       WRITE(ldtxt(ii),*) '         z-partial-step coordinate flag        ln_zps = ', ln_zps             ;   ii = ii + 1 
    94       WRITE(ldtxt(ii),*) '         s-coordinate flag                     ln_sco = ', ln_sco             ;   ii = ii + 1 
    95105      WRITE(ldtxt(ii),*) '      horizontal resolution                    rn_dx  = ', rn_dx, ' meters'   ;   ii = ii + 1 
    96106      WRITE(ldtxt(ii),*) '      horizontal resolution                    rn_dy  = ', rn_dy, ' meters'   ;   ii = ii + 1 
    97107      WRITE(ldtxt(ii),*) '      SAS_BIPER domain = 300 km x 300Km x 1 grid-point '                      ;   ii = ii + 1 
     108      WRITE(ldtxt(ii),*) '         LX [km]: ', zlx                                                      ;   ii = ii + 1 
     109      WRITE(ldtxt(ii),*) '         LY [km]: ', zly                                                      ;   ii = ii + 1 
    98110      WRITE(ldtxt(ii),*) '         resulting global domain size :        jpiglo = ', kpi                ;   ii = ii + 1 
    99111      WRITE(ldtxt(ii),*) '                                               jpjglo = ', kpj                ;   ii = ii + 1 
Note: See TracChangeset for help on using the changeset viewer.