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

Changeset 13546 for NEMO/trunk


Ignore:
Timestamp:
2020-09-30T10:47:59+02:00 (3 years ago)
Author:
smasson
Message:

trunk: supress the use of undefined values, see #2535

Location:
NEMO/trunk/src
Files:
11 edited

Legend:

Unmodified
Added
Removed
  • NEMO/trunk/src/ICE/icestp.F90

    r13472 r13546  
    257257      END WHERE 
    258258      ! 
     259      CALL diag_set0                   ! set diag of mass, heat and salt fluxes to 0: needed for Agrif child grids 
     260      ! 
    259261      CALL ice_itd_init                ! ice thickness distribution initialization 
    260262      ! 
  • NEMO/trunk/src/NST/agrif_user.F90

    r13472 r13546  
    405405         use_sign_north = .TRUE. 
    406406         sign_north = -1. 
     407         CALL Agrif_Bc_variable(ub2b_interp_id,calledweight=1.,procname=interpub2b)   ! must be called before unb_id to define ubdy 
     408         CALL Agrif_Bc_variable(vb2b_interp_id,calledweight=1.,procname=interpvb2b)   ! must be called before vnb_id to define vbdy 
    407409         CALL Agrif_Bc_variable(        unb_id,calledweight=1.,procname=interpunb ) 
    408410         CALL Agrif_Bc_variable(        vnb_id,calledweight=1.,procname=interpvnb ) 
    409          CALL Agrif_Bc_variable(ub2b_interp_id,calledweight=1.,procname=interpub2b) 
    410          CALL Agrif_Bc_variable(vb2b_interp_id,calledweight=1.,procname=interpvb2b) 
    411411         use_sign_north = .FALSE. 
    412412         ubdy(:,:) = 0._wp 
  • NEMO/trunk/src/OCE/DYN/dynspg_ts.F90

    r13497 r13546  
    917917               CALL iom_get( numror, jpdom_auto, 'ub2_i_b'  , ub2_i_b(:,:), cd_type = 'U', psgn = -1._wp, ldxios = lrxios )    
    918918               CALL iom_get( numror, jpdom_auto, 'vb2_i_b'  , vb2_i_b(:,:), cd_type = 'V', psgn = -1._wp, ldxios = lrxios ) 
     919            ELSE 
     920               ub2_i_b(:,:) = 0._wp   ;   vb2_i_b(:,:) = 0._wp   ! used in the 1st update of agrif 
    919921            ENDIF 
    920922#endif 
     
    922924            IF(lwp) WRITE(numout,*) 
    923925            IF(lwp) WRITE(numout,*) '   ==>>>   start from rest: set barotropic values to 0' 
    924             ub2_b (:,:) = 0._wp   ;   vb2_b (:,:) = 0._wp   ! used in the 1st interpol of agrif 
    925             un_adv(:,:) = 0._wp   ;   vn_adv(:,:) = 0._wp   ! used in the 1st interpol of agrif 
    926             un_bf (:,:) = 0._wp   ;   vn_bf (:,:) = 0._wp   ! used in the 1st update   of agrif 
     926            ub2_b  (:,:) = 0._wp   ;   vb2_b (:,:) = 0._wp   ! used in the 1st interpol of agrif 
     927            un_adv (:,:) = 0._wp   ;   vn_adv (:,:) = 0._wp   ! used in the 1st interpol of agrif 
     928            un_bf  (:,:) = 0._wp   ;   vn_bf (:,:) = 0._wp   ! used in the 1st update   of agrif 
    927929#if defined key_agrif 
    928             IF ( .NOT.Agrif_Root() ) THEN 
    929                ub2_i_b(:,:) = 0._wp   ;   vb2_i_b(:,:) = 0._wp   ! used in the 1st update of agrif 
    930             ENDIF 
     930            ub2_i_b(:,:) = 0._wp   ;   vb2_i_b(:,:) = 0._wp   ! used in the 1st update of agrif 
    931931#endif 
    932932         ENDIF 
  • NEMO/trunk/src/OCE/DYN/dynvor.F90

    r13497 r13546  
    217217      INTEGER  ::   ji, jj, jk           ! dummy loop indices 
    218218      REAL(wp) ::   zx1, zy1, zx2, zy2   ! local scalars 
    219       REAL(wp), DIMENSION(jpi,jpj)     ::   zwx, zwy, zwt   ! 2D workspace 
    220       REAL(wp), DIMENSION(jpi,jpj,jpk) ::   zwz             ! 3D workspace 
     219      REAL(wp), DIMENSION(jpi,jpj)       ::   zwx, zwy, zwt   ! 2D workspace 
     220      REAL(wp), DIMENSION(jpi,jpj,jpkm1) ::   zwz             ! 3D workspace, jpkm1 -> avoid lbc_lnk on jpk that is not defined 
    221221      !!---------------------------------------------------------------------- 
    222222      ! 
     
    533533      REAL(wp) ::   zua, zva     ! local scalars 
    534534      REAL(wp) ::   zmsk, ze3f   ! local scalars 
    535       REAL(wp), DIMENSION(jpi,jpj)     ::   zwx , zwy , z1_e3f 
    536       REAL(wp), DIMENSION(jpi,jpj)     ::   ztnw, ztne, ztsw, ztse 
    537       REAL(wp), DIMENSION(jpi,jpj,jpk) ::   zwz 
     535      REAL(wp), DIMENSION(jpi,jpj)       ::   zwx , zwy , z1_e3f 
     536      REAL(wp), DIMENSION(jpi,jpj)       ::   ztnw, ztne, ztsw, ztse 
     537      REAL(wp), DIMENSION(jpi,jpj,jpkm1) ::   zwz   ! 3D workspace, jpkm1 -> jpkm1 -> avoid lbc_lnk on jpk that is not defined 
    538538      !!---------------------------------------------------------------------- 
    539539      ! 
     
    677677      REAL(wp) ::   zua, zva       ! local scalars 
    678678      REAL(wp) ::   zmsk, z1_e3t   ! local scalars 
    679       REAL(wp), DIMENSION(jpi,jpj)     ::   zwx , zwy  
    680       REAL(wp), DIMENSION(jpi,jpj)     ::   ztnw, ztne, ztsw, ztse 
    681       REAL(wp), DIMENSION(jpi,jpj,jpk) ::   zwz 
     679      REAL(wp), DIMENSION(jpi,jpj)       ::   zwx , zwy  
     680      REAL(wp), DIMENSION(jpi,jpj)       ::   ztnw, ztne, ztsw, ztse 
     681      REAL(wp), DIMENSION(jpi,jpj,jpkm1) ::   zwz   ! 3D workspace, avoid lbc_lnk on jpk that is not defined 
    682682      !!---------------------------------------------------------------------- 
    683683      ! 
  • NEMO/trunk/src/OCE/SBC/fldread.F90

    r13295 r13546  
    216216                  WRITE(numout, clfmt)  TRIM( sd(jf)%clvar ), kt, REAL(isecsbc,wp)/rday, nyear, nmonth, nday,   &             
    217217                     & sd(jf)%nrec(1,ibb), sd(jf)%nrec(1,iaa), REAL(sd(jf)%nrec(2,ibb),wp)/rday, REAL(sd(jf)%nrec(2,iaa),wp)/rday 
    218                   WRITE(numout, *) '      zt_offset is : ',zt_offset 
     218                  IF( zt_offset /= 0._wp )   WRITE(numout, *) '      zt_offset is : ', zt_offset 
    219219               ENDIF 
    220220               ! temporal interpolation weights 
  • NEMO/trunk/src/OCE/SBC/sbcmod.F90

    r13477 r13546  
    252252      sfx   (:,:) = 0._wp           !* salt flux due to freezing/melting 
    253253      fmmflx(:,:) = 0._wp           !* freezing minus melting flux 
     254      cloud_fra(:,:) = pp_cldf      !* cloud fraction over sea ice (used in si3) 
    254255 
    255256      taum(:,:) = 0._wp             !* wind stress module (needed in GLS in case of reduced restart) 
     
    336337      IF( l_sbc_clo   )   CALL sbc_clo_init              ! closed sea surface initialisation 
    337338      ! 
    338       IF( ln_blk      )   CALL sbc_blk_init            ! bulk formulae initialization 
    339  
    340       IF( ln_abl      )   CALL sbc_abl_init            ! Atmospheric Boundary Layer (ABL) 
    341  
    342       IF( ln_ssr      )   CALL sbc_ssr_init            ! Sea-Surface Restoring initialization 
     339      IF( ln_blk      )   CALL sbc_blk_init              ! bulk formulae initialization 
     340 
     341      IF( ln_abl      )   CALL sbc_abl_init              ! Atmospheric Boundary Layer (ABL) 
     342 
     343      IF( ln_ssr      )   CALL sbc_ssr_init              ! Sea-Surface Restoring initialization 
    343344      ! 
    344345      ! 
  • NEMO/trunk/src/OCE/SBC/sbcwave.F90

    r13497 r13546  
    106106      !!--------------------------------------------------------------------- 
    107107      ! 
    108       ALLOCATE( ze3divh(jpi,jpj,jpk) ) 
     108      ALLOCATE( ze3divh(jpi,jpj,jpkm1) )   ! jpkm1 -> avoid lbc_lnk on jpk that is not defined 
    109109      ALLOCATE( zk_t(jpi,jpj), zk_u(jpi,jpj), zk_v(jpi,jpj), zu0_sd(jpi,jpj), zv0_sd(jpi,jpj) ) 
    110110      ! 
  • NEMO/trunk/src/OCE/ZDF/zdfgls.F90

    r13506 r13546  
    327327      ! at k=2, set de/dz=Fw 
    328328      !cbr 
    329       zdiag(:,:,2) = zdiag(:,:,2) +  zd_lw(:,:,2) ! Remove zd_lw from zdiag 
    330       zd_lw(:,:,2) = 0._wp 
     329      DO_2D( 0, 0, 0, 0 )   ! zdiag zd_lw not defined/used on the halo 
     330         zdiag(ji,jj,2) = zdiag(ji,jj,2) +  zd_lw(ji,jj,2) ! Remove zd_lw from zdiag 
     331         zd_lw(ji,jj,2) = 0._wp 
     332      END_2D 
    331333      zkar (:,:)   = (rl_sf + (vkarmn-rl_sf)*(1.-EXP(-rtrans*gdept(:,:,1,Kmm)/zhsro(:,:)) )) 
    332334      zflxs(:,:)   = rsbc_tke2 * (1._wp-zice_fra(:,:)) * ustar2_surf(:,:)**1.5_wp * zkar(:,:) & 
     
    419421         zdiag(ji,jj,jk) = zdiag(ji,jj,jk) - zd_lw(ji,jj,jk) * zd_up(ji,jj,jk-1) / zdiag(ji,jj,jk-1) 
    420422      END_3D 
    421       DO_3D( 0, 0, 0, 0, 2, jpk )                  ! Second recurrence : Lk = RHSk - Lk / Dk-1 * Lk-1 
     423      DO_3D( 0, 0, 0, 0, 2, jpkm1 )                ! Second recurrence : Lk = RHSk - Lk / Dk-1 * Lk-1 
    422424         zd_lw(ji,jj,jk) = en(ji,jj,jk) - zd_lw(ji,jj,jk) / zdiag(ji,jj,jk-1) * zd_lw(ji,jj,jk-1) 
    423425      END_3D 
    424       DO_3DS( 0, 0, 0, 0, jpk-1, 2, -1 )           ! thrid recurrence : Ek = ( Lk - Uk * Ek+1 ) / Dk 
     426      DO_3DS( 0, 0, 0, 0, jpkm1, 2, -1 )           ! thrid recurrence : Ek = ( Lk - Uk * Ek+1 ) / Dk 
    425427         en(ji,jj,jk) = ( zd_lw(ji,jj,jk) - zd_up(ji,jj,jk) * en(ji,jj,jk+1) ) / zdiag(ji,jj,jk) 
    426428      END_3D 
     
    537539         ! 
    538540         ! Neumann condition at k=2 
    539          zdiag(:,:,2) = zdiag(:,:,2) +  zd_lw(:,:,2) ! Remove zd_lw from zdiag 
    540          zd_lw(:,:,2) = 0._wp 
     541         DO_2D( 0, 0, 0, 0 )   ! zdiag zd_lw not defined/used on the halo 
     542            zdiag(ji,jj,2) = zdiag(ji,jj,2) +  zd_lw(ji,jj,2) ! Remove zd_lw from zdiag 
     543            zd_lw(ji,jj,2) = 0._wp 
     544         END_2D 
    541545         ! 
    542546         ! Set psi vertical flux at the surface: 
     
    613617         zdiag(ji,jj,jk) = zdiag(ji,jj,jk) - zd_lw(ji,jj,jk) * zd_up(ji,jj,jk-1) / zdiag(ji,jj,jk-1) 
    614618      END_3D 
    615       DO_3D( 0, 0, 0, 0, 2, jpk )                  ! Second recurrence : Lk = RHSk - Lk / Dk-1 * Lk-1 
     619      DO_3D( 0, 0, 0, 0, 2, jpkm1 )                ! Second recurrence : Lk = RHSk - Lk / Dk-1 * Lk-1 
    616620         zd_lw(ji,jj,jk) = psi(ji,jj,jk) - zd_lw(ji,jj,jk) / zdiag(ji,jj,jk-1) * zd_lw(ji,jj,jk-1) 
    617621      END_3D 
    618       DO_3DS( 0, 0, 0, 0, jpk-1, 2, -1 )           ! Third recurrence : Ek = ( Lk - Uk * Ek+1 ) / Dk 
     622      DO_3DS( 0, 0, 0, 0, jpkm1, 2, -1 )           ! Third recurrence : Ek = ( Lk - Uk * Ek+1 ) / Dk 
    619623         psi(ji,jj,jk) = ( zd_lw(ji,jj,jk) - zd_up(ji,jj,jk) * psi(ji,jj,jk+1) ) / zdiag(ji,jj,jk) 
    620624      END_3D 
  • NEMO/trunk/src/SAS/nemogcm.F90

    r13538 r13546  
    371371 
    372372      !                                      ! external forcing  
     373#if defined key_agrif 
     374      uu(:,:,:,:) = 0.0_wp   ;   vv(:,:,:,:) = 0.0_wp   ;   ts(:,:,:,:,:) = 0.0_wp   ! needed for interp done at initialization phase 
     375#endif  
    373376                           CALL sbc_init( Nbb, Nnn, Naa )  ! Forcings : surface module  
    374377 
  • NEMO/trunk/src/SAS/stpctl.F90

    r13538 r13546  
    9898            CALL ctl_opn( numrun, clname, 'REPLACE', 'FORMATTED', 'SEQUENTIAL', -1, numout, lwp, narea ) 
    9999            !                             ! open run.stat.nc netcdf file, done only by 1st subdomain 
    100             clname = clname//'.nc' 
     100            clname = TRIM(clname)//'.nc' 
    101101            IF( .NOT. Agrif_Root() )   clname = TRIM(Agrif_CFixed())//"_"//TRIM(clname) 
    102102            istatus = NF90_CREATE( TRIM(clname), NF90_CLOBBER, nrunid ) 
  • NEMO/trunk/src/TOP/PISCES/P4Z/p4zsed.F90

    r13295 r13546  
    313313      ENDIF 
    314314      ! 
    315       IF(sn_cfctl%l_prttrc) THEN  ! print mean trends (USEd for debugging) 
     315      IF(sn_cfctl%l_prttrc) THEN  ! print mean trneds (USEd for debugging) 
    316316         WRITE(charout, fmt="('sed ')") 
    317317         CALL prt_ctl_info( charout, cdcomp = 'top' ) 
     
    366366      lk_sed = ln_sediment .AND. ln_sed_2way  
    367367      ! 
     368      nitrpot(:,:,jpk) = 0._wp   ! define last level for iom_put 
     369      ! 
    368370   END SUBROUTINE p4z_sed_init 
    369371 
Note: See TracChangeset for help on using the changeset viewer.