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 8386 – NEMO

Changeset 8386


Ignore:
Timestamp:
2017-07-27T14:22:16+02:00 (7 years ago)
Author:
frrh
Message:

Avoid passing in the same variable twice to repcmo with conflicting
INTENTS which leads to junk values in coupling fields and crashes
when using -ei.

Apply what I think is the correct solution to use fse3t_n instead
of fse3t_a in passive tracer summary output.

Location:
branches/UKMO/dev_r5518_fix_NaNs/NEMOGCM/NEMO
Files:
2 edited

Legend:

Unmodified
Added
Removed
  • branches/UKMO/dev_r5518_fix_NaNs/NEMOGCM/NEMO/OPA_SRC/SBC/sbccpl.F90

    r8280 r8386  
    21372137      REAL(wp) ::   zumax, zvmax 
    21382138      REAL(wp), POINTER, DIMENSION(:,:)   ::   zfr_l, ztmp1, ztmp2, zotx1, zoty1, zotz1, zitx1, zity1, zitz1 
     2139      REAL(wp), POINTER, DIMENSION(:,:)   ::   zotx1_in, zoty1_in 
    21392140      REAL(wp), POINTER, DIMENSION(:,:,:) ::   ztmp3, ztmp4    
    21402141      !!---------------------------------------------------------------------- 
     
    21432144      ! 
    21442145      CALL wrk_alloc( jpi,jpj, zfr_l, ztmp1, ztmp2, zotx1, zoty1, zotz1, zitx1, zity1, zitz1 ) 
     2146      CALL wrk_alloc( jpi,jpj, zotx1_in, zoty1_in) 
    21452147      CALL wrk_alloc( jpi,jpj,jpl, ztmp3, ztmp4 ) 
    21462148 
     
    24112413            zotx1(:,:) = un(:,:,1)   
    24122414            zoty1(:,:) = vn(:,:,1)   
    2413          ELSE         
     2415         ELSE 
    24142416            SELECT CASE( TRIM( sn_snd_crt%cldes ) ) 
    24152417            CASE( 'oce only'             )      ! C-grid ==> T 
     
    25472549                  ENDDO 
    25482550               ENDDO 
    2549                 
     2551 
    25502552               ! Ensure any N fold and wrap columns are updated 
    25512553               CALL lbc_lnk(ztmp1, 'V', -1.0) 
    25522554               CALL lbc_lnk(ztmp2, 'U', -1.0) 
    2553                 
     2555                             
    25542556               ikchoix = -1 
    2555                CALL repcmo (zotx1,ztmp2,ztmp1,zoty1,zotx1,zoty1,ikchoix) 
     2557               ! We need copies of zotx1 and zoty2 in order to avoid problems  
     2558               ! caused by INTENTs used in the following subroutine.  
     2559               zotx1_in(:,:) = zotx1(:,:) 
     2560               zoty1_in(:,:) = zoty1(:,:) 
     2561               CALL repcmo (zotx1_in,ztmp2,ztmp1,zoty1_in,zotx1,zoty1,ikchoix) 
    25562562           ENDIF 
    25572563         ENDIF 
     
    26222628      ! 
    26232629      CALL wrk_dealloc( jpi,jpj, zfr_l, ztmp1, ztmp2, zotx1, zoty1, zotz1, zitx1, zity1, zitz1 ) 
     2630      CALL wrk_dealloc( jpi,jpj, zotx1_in, zoty1_in ) 
    26242631      CALL wrk_dealloc( jpi,jpj,jpl, ztmp3, ztmp4 ) 
    26252632      ! 
  • branches/UKMO/dev_r5518_fix_NaNs/NEMOGCM/NEMO/TOP_SRC/trcrst.F90

    r8377 r8386  
    752752      IF( lwp )  WRITE(numout,*) 'STAT- ', names 
    753753      ! 
    754       zvol(:,:) = e1e2t(:,:) * fse3t_a(:,:,1) * tmask(:,:,1) 
     754      ! RSRH The following should use fse3t_n not fse3t_a which  
     755      ! will be undefined at the start of a run! Just because it  
     756      ! doesn't crash on certain platforms doesn't make it universally  
     757      ! safe or portable!  
     758      zvol(:,:) = e1e2t(:,:) * fse3t_n(:,:,1) * tmask(:,:,1) 
    755759      ztraf = glob_sum( dgtr(:,:) * zvol(:,:) ) 
    756760      !! areasf = glob_sum(e1e2t(:,:) * tmask(:,:,1) ) 
     
    764768 
    765769      text_zmean = "N/A" 
    766       ! Avoid divide by zero when this routine is called from parts of the code 
    767       ! which may not have necessary time level variables to calculate areasf. 
     770      ! Avoid divide by zero. areasf must be positive. 
    768771      IF  (areasf > 0.0) THEN  
    769772         zmean = ztraf / areasf 
Note: See TracChangeset for help on using the changeset viewer.