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 10314 for NEMO/branches/2018/dev_r10164_HPC09_ESIWACE_PREP_MERGE/src/TOP – NEMO

Ignore:
Timestamp:
2018-11-15T17:27:18+01:00 (5 years ago)
Author:
smasson
Message:

dev_r10164_HPC09_ESIWACE_PREP_MERGE: action 2: add generic glob_min/max/sum and locmin/max, complete timing and report (including bdy and icb), see #2133

Location:
NEMO/branches/2018/dev_r10164_HPC09_ESIWACE_PREP_MERGE/src/TOP
Files:
14 edited

Legend:

Unmodified
Added
Removed
  • NEMO/branches/2018/dev_r10164_HPC09_ESIWACE_PREP_MERGE/src/TOP/C14/trcwri_c14.F90

    r10070 r10314  
    9696     
    9797      IF( iom_use("AtmC14") ) THEN 
    98          zarea = glob_sum( e1e2t(:,:) )           ! global ocean surface 
    99          ztemp = glob_sum( c14sbc(:,:) * e1e2t(:,:) ) 
     98         zarea = glob_sum( 'trcwri_c14', e1e2t(:,:) )           ! global ocean surface 
     99         ztemp = glob_sum( 'trcwri_c14', c14sbc(:,:) * e1e2t(:,:) ) 
    100100         ztemp = ( ztemp / zarea - 1._wp ) * 1000._wp 
    101101         CALL iom_put( "AtmC14" , ztemp )   ! Global atmospheric DeltaC14 [permil] 
    102102      ENDIF 
    103103      IF( iom_use("K_C14") ) THEN 
    104          ztemp = glob_sum ( exch_c14(:,:) * e1e2t(:,:) ) 
     104         ztemp = glob_sum ( 'trcwri_c14', exch_c14(:,:) * e1e2t(:,:) ) 
    105105         ztemp = rsiyea * ztemp / zarea 
    106106         CALL iom_put( "K_C14" , ztemp )   ! global mean exchange velocity for C14/C ratio [m/yr] 
    107107      ENDIF 
    108108      IF( iom_use("K_CO2") ) THEN 
    109          zarea = glob_sum( e1e2t(:,:) )           ! global ocean surface 
    110          ztemp = glob_sum ( exch_co2(:,:) * e1e2t(:,:) ) 
     109         zarea = glob_sum( 'trcwri_c14', e1e2t(:,:) )           ! global ocean surface 
     110         ztemp = glob_sum ( 'trcwri_c14', exch_co2(:,:) * e1e2t(:,:) ) 
    111111         ztemp = 360000._wp * ztemp / zarea       ! cm/h units: directly comparable with literature 
    112112         CALL iom_put( "K_CO2", ztemp )  !  global mean CO2 piston velocity [cm/hr] 
    113113      ENDIF 
    114114      IF( iom_use("C14Inv") ) THEN 
    115          ztemp = glob_sum( trn(:,:,:,jp_c14) * cvol(:,:,:) ) 
     115         ztemp = glob_sum( 'trcwri_c14', trn(:,:,:,jp_c14) * cvol(:,:,:) ) 
    116116         ztemp = atomc14 * xdicsur * ztemp 
    117117         CALL iom_put( "C14Inv", ztemp )  !  Radiocarbon ocean inventory [10^26 atoms] 
  • NEMO/branches/2018/dev_r10164_HPC09_ESIWACE_PREP_MERGE/src/TOP/PISCES/P2Z/p2zexp.F90

    r10170 r10314  
    230230      END DO 
    231231      CALL lbc_lnk( 'p2zexp', cmask , 'T', 1. )      ! lateral boundary conditions on cmask   (sign unchanged) 
    232       areacot = glob_sum( e1e2t(:,:) * cmask(:,:) ) 
     232      areacot = glob_sum( 'p2zexp', e1e2t(:,:) * cmask(:,:) ) 
    233233      ! 
    234234      IF( ln_rsttr ) THEN 
  • NEMO/branches/2018/dev_r10164_HPC09_ESIWACE_PREP_MERGE/src/TOP/PISCES/P4Z/p4zflx.F90

    r10068 r10314  
    172172      END DO 
    173173 
    174       t_oce_co2_flx     = glob_sum( oce_co2(:,:) )                    !  Total Flux of Carbon 
     174      t_oce_co2_flx     = glob_sum( 'p4zflx', oce_co2(:,:) )                    !  Total Flux of Carbon 
    175175      t_oce_co2_flx_cum = t_oce_co2_flx_cum + t_oce_co2_flx       !  Cumulative Total Flux of Carbon 
    176 !      t_atm_co2_flx     = glob_sum( satmco2(:,:) * e1e2t(:,:) )       ! Total atmospheric pCO2 
     176!      t_atm_co2_flx     = glob_sum( 'p4zflx', satmco2(:,:) * e1e2t(:,:) )       ! Total atmospheric pCO2 
    177177      t_atm_co2_flx     =  atcco2      ! Total atmospheric pCO2 
    178178  
  • NEMO/branches/2018/dev_r10164_HPC09_ESIWACE_PREP_MERGE/src/TOP/PISCES/P4Z/p4zprod.F90

    r10069 r10314  
    360360    ! Total primary production per year 
    361361    IF( iom_use( "tintpp" ) .OR. ( ln_check_mass .AND. kt == nitend .AND. knt == nrdttrc )  )  & 
    362          & tpp = glob_sum( ( zprorcan(:,:,:) + zprorcad(:,:,:) ) * cvol(:,:,:) ) 
     362         & tpp = glob_sum( 'p4zprod', ( zprorcan(:,:,:) + zprorcad(:,:,:) ) * cvol(:,:,:) ) 
    363363 
    364364    IF( lk_iomput ) THEN 
  • NEMO/branches/2018/dev_r10164_HPC09_ESIWACE_PREP_MERGE/src/TOP/PISCES/P4Z/p4zsbc.F90

    r10170 r10314  
    368368               ztimes_riv = 1._wp / REAL(ntimes_riv, wp)  
    369369               DO jm = 1, ntimes_riv 
    370                   rivinput(ifpr) = rivinput(ifpr) + glob_sum( zriver(:,:,jm) * tmask(:,:,1) * ztimes_riv )  
     370                  rivinput(ifpr) = rivinput(ifpr) + glob_sum( 'p4zsbc', zriver(:,:,jm) * tmask(:,:,1) * ztimes_riv )  
    371371               END DO 
    372372               DEALLOCATE( zriver) 
  • NEMO/branches/2018/dev_r10164_HPC09_ESIWACE_PREP_MERGE/src/TOP/PISCES/P4Z/p4zsink.F90

    r10297 r10314  
    208208     ! Total carbon export per year 
    209209     IF( iom_use( "tcexp" ) .OR. ( ln_check_mass .AND. kt == nitend .AND. knt == nrdttrc )  )  & 
    210         &   t_oce_co2_exp = glob_sum( ( sinking(:,:,ik100) + sinking2(:,:,ik100) ) * e1e2t(:,:) * tmask(:,:,1) ) 
     210        &   t_oce_co2_exp = glob_sum( 'p4zsink', ( sinking(:,:,ik100) + sinking2(:,:,ik100) ) * e1e2t(:,:) * tmask(:,:,1) ) 
    211211     ! 
    212212     IF( lk_iomput ) THEN 
  • NEMO/branches/2018/dev_r10164_HPC09_ESIWACE_PREP_MERGE/src/TOP/PISCES/P4Z/p4zsms.F90

    r10069 r10314  
    355355         !                                                ! --------------------------- ! 
    356356         ! set total alkalinity, phosphate, nitrate & silicate 
    357          zarea          = 1._wp / glob_sum( cvol(:,:,:) ) * 1e6               
    358  
    359          zalksumn = glob_sum( trn(:,:,:,jptal) * cvol(:,:,:)  ) * zarea 
    360          zpo4sumn = glob_sum( trn(:,:,:,jppo4) * cvol(:,:,:)  ) * zarea * po4r 
    361          zno3sumn = glob_sum( trn(:,:,:,jpno3) * cvol(:,:,:)  ) * zarea * rno3 
    362          zsilsumn = glob_sum( trn(:,:,:,jpsil) * cvol(:,:,:)  ) * zarea 
     357         zarea          = 1._wp / glob_sum( 'p4zsms', cvol(:,:,:) ) * 1e6               
     358 
     359         zalksumn = glob_sum( 'p4zsms', trn(:,:,:,jptal) * cvol(:,:,:)  ) * zarea 
     360         zpo4sumn = glob_sum( 'p4zsms', trn(:,:,:,jppo4) * cvol(:,:,:)  ) * zarea * po4r 
     361         zno3sumn = glob_sum( 'p4zsms', trn(:,:,:,jpno3) * cvol(:,:,:)  ) * zarea * rno3 
     362         zsilsumn = glob_sum( 'p4zsms', trn(:,:,:,jpsil) * cvol(:,:,:)  ) * zarea 
    363363  
    364364         IF(lwp) WRITE(numout,*) '       TALKN mean : ', zalksumn 
     
    376376         ! 
    377377         IF( .NOT. ln_top_euler ) THEN 
    378             zalksumb = glob_sum( trb(:,:,:,jptal) * cvol(:,:,:)  ) * zarea 
    379             zpo4sumb = glob_sum( trb(:,:,:,jppo4) * cvol(:,:,:)  ) * zarea * po4r 
    380             zno3sumb = glob_sum( trb(:,:,:,jpno3) * cvol(:,:,:)  ) * zarea * rno3 
    381             zsilsumb = glob_sum( trb(:,:,:,jpsil) * cvol(:,:,:)  ) * zarea 
     378            zalksumb = glob_sum( 'p4zsms', trb(:,:,:,jptal) * cvol(:,:,:)  ) * zarea 
     379            zpo4sumb = glob_sum( 'p4zsms', trb(:,:,:,jppo4) * cvol(:,:,:)  ) * zarea * po4r 
     380            zno3sumb = glob_sum( 'p4zsms', trb(:,:,:,jpno3) * cvol(:,:,:)  ) * zarea * rno3 
     381            zsilsumb = glob_sum( 'p4zsms', trb(:,:,:,jpsil) * cvol(:,:,:)  ) * zarea 
    382382  
    383383            IF(lwp) WRITE(numout,*) ' ' 
     
    442442        ENDIF 
    443443        ! 
    444         no3budget = glob_sum( zwork(:,:,:) * cvol(:,:,:)  )   
     444        no3budget = glob_sum( 'p4zsms', zwork(:,:,:) * cvol(:,:,:)  )   
    445445        no3budget = no3budget / areatot 
    446446        CALL iom_put( "pno3tot", no3budget ) 
     
    460460        ENDIF 
    461461        ! 
    462         po4budget = glob_sum( zwork(:,:,:) * cvol(:,:,:)  )   
     462        po4budget = glob_sum( 'p4zsms', zwork(:,:,:) * cvol(:,:,:)  )   
    463463        po4budget = po4budget / areatot 
    464464        CALL iom_put( "ppo4tot", po4budget ) 
     
    468468         zwork(:,:,:) =  trn(:,:,:,jpsil) + trn(:,:,:,jpgsi) + trn(:,:,:,jpdsi)  
    469469         ! 
    470          silbudget = glob_sum( zwork(:,:,:) * cvol(:,:,:)  )   
     470         silbudget = glob_sum( 'p4zsms', zwork(:,:,:) * cvol(:,:,:)  )   
    471471         silbudget = silbudget / areatot 
    472472         CALL iom_put( "psiltot", silbudget ) 
     
    476476         zwork(:,:,:) =  trn(:,:,:,jpno3) * rno3 + trn(:,:,:,jptal) + trn(:,:,:,jpcal) * 2.               
    477477         ! 
    478          alkbudget = glob_sum( zwork(:,:,:) * cvol(:,:,:)  )         ! 
     478         alkbudget = glob_sum( 'p4zsms', zwork(:,:,:) * cvol(:,:,:)  )         ! 
    479479         alkbudget = alkbudget / areatot 
    480480         CALL iom_put( "palktot", alkbudget ) 
     
    487487         IF( ln_ligand)  zwork(:,:,:) = zwork(:,:,:) + trn(:,:,:,jpfep)                 
    488488         ! 
    489          ferbudget = glob_sum( zwork(:,:,:) * cvol(:,:,:)  )   
     489         ferbudget = glob_sum( 'p4zsms', zwork(:,:,:) * cvol(:,:,:)  )   
    490490         ferbudget = ferbudget / areatot 
    491491         CALL iom_put( "pfertot", ferbudget ) 
     
    496496      ! -------------------------------------------------------------------------------- 
    497497      IF( iom_use( "tnfix" ) .OR.  ( ln_check_mass .AND. kt == nitend )  ) THEN 
    498          znitrpottot  = glob_sum ( nitrpot(:,:,:) * nitrfix * cvol(:,:,:) ) 
     498         znitrpottot  = glob_sum ( 'p4zsms', nitrpot(:,:,:) * nitrfix * cvol(:,:,:) ) 
    499499         CALL iom_put( "tnfix"  , znitrpottot * xfact3 )  ! Global  nitrogen fixation molC/l  to molN/m3  
    500500      ENDIF 
    501501      ! 
    502502      IF( iom_use( "tdenit" ) .OR.  ( ln_check_mass .AND. kt == nitend )  ) THEN 
    503          zrdenittot = glob_sum ( denitr(:,:,:) * rdenit * xnegtr(:,:,:) * cvol(:,:,:) ) 
    504          zsdenittot = glob_sum ( sdenit(:,:) * e1e2t(:,:) * tmask(:,:,1) ) 
     503         zrdenittot = glob_sum ( 'p4zsms', denitr(:,:,:) * rdenit * xnegtr(:,:,:) * cvol(:,:,:) ) 
     504         zsdenittot = glob_sum ( 'p4zsms', sdenit(:,:) * e1e2t(:,:) * tmask(:,:,1) ) 
    505505         CALL iom_put( "tdenit" , ( zrdenittot + zsdenittot ) * xfact3 )  ! Total denitrification molC/l to molN/m3  
    506506      ENDIF 
    507507      ! 
    508508      IF( ln_check_mass .AND. kt == nitend ) THEN   ! Compute the budget of NO3, ALK, Si, Fer 
    509          t_atm_co2_flx  = t_atm_co2_flx / glob_sum( e1e2t(:,:) ) 
     509         t_atm_co2_flx  = t_atm_co2_flx / glob_sum( 'p4zsms', e1e2t(:,:) ) 
    510510         t_oce_co2_flx  = t_oce_co2_flx         * xfact1 * (-1 ) 
    511511         tpp            = tpp           * 1000. * xfact1 
  • NEMO/branches/2018/dev_r10164_HPC09_ESIWACE_PREP_MERGE/src/TOP/PISCES/P4Z/p5zprod.F90

    r10070 r10314  
    459459    ! Total primary production per year 
    460460    IF( iom_use( "tintpp" ) .OR. ( ln_check_mass .AND. kt == nitend .AND. knt == nrdttrc )  )  & 
    461       & tpp = glob_sum( ( zprorcan(:,:,:) + zprorcad(:,:,:) + zprorcap(:,:,:) ) * cvol(:,:,:) ) 
     461      & tpp = glob_sum( 'p5zprod', ( zprorcan(:,:,:) + zprorcad(:,:,:) + zprorcap(:,:,:) ) * cvol(:,:,:) ) 
    462462 
    463463    IF( lk_iomput ) THEN 
  • NEMO/branches/2018/dev_r10164_HPC09_ESIWACE_PREP_MERGE/src/TOP/TRP/trcrad.F90

    r10068 r10314  
    150150            ENDIF 
    151151            !                                                         ! sum over the global domain  
    152             ztrcorb = glob_sum( MIN( 0., ptrb(:,:,:,jn) ) * cvol(:,:,:) ) 
    153             ztrcorn = glob_sum( MIN( 0., ptrn(:,:,:,jn) ) * cvol(:,:,:) ) 
    154             ! 
    155             ztrmasb = glob_sum( MAX( 0., ptrb(:,:,:,jn) ) * cvol(:,:,:) ) 
    156             ztrmasn = glob_sum( MAX( 0., ptrn(:,:,:,jn) ) * cvol(:,:,:) ) 
     152            ztrcorb = glob_sum( 'trcrad', MIN( 0., ptrb(:,:,:,jn) ) * cvol(:,:,:) ) 
     153            ztrcorn = glob_sum( 'trcrad', MIN( 0., ptrn(:,:,:,jn) ) * cvol(:,:,:) ) 
     154            ! 
     155            ztrmasb = glob_sum( 'trcrad', MAX( 0., ptrb(:,:,:,jn) ) * cvol(:,:,:) ) 
     156            ztrmasn = glob_sum( 'trcrad', MAX( 0., ptrn(:,:,:,jn) ) * cvol(:,:,:) ) 
    157157            ! 
    158158            IF( ztrcorb /= 0 ) THEN 
  • NEMO/branches/2018/dev_r10164_HPC09_ESIWACE_PREP_MERGE/src/TOP/trcbdy.F90

    r10069 r10314  
    7171            END SELECT 
    7272            ! Boundary points should be updated 
    73             CALL lbc_bdy_lnk( tra(:,:,:,jn), 'T', 1., ib_bdy ) 
     73            CALL lbc_bdy_lnk( 'trcbdy', tra(:,:,:,jn), 'T', 1., ib_bdy ) 
    7474            ! 
    7575         END DO 
  • NEMO/branches/2018/dev_r10164_HPC09_ESIWACE_PREP_MERGE/src/TOP/trcini.F90

    r10297 r10314  
    119119      END DO 
    120120      !                          ! total volume of the ocean  
    121       areatot = glob_sum( cvol(:,:,:) ) 
     121      areatot = glob_sum( 'trcini', cvol(:,:,:) ) 
    122122      ! 
    123123      trai(:) = 0._wp            ! initial content of all tracers 
    124124      DO jn = 1, jptra 
    125          trai(jn) = trai(jn) + glob_sum( trn(:,:,:,jn) * cvol(:,:,:)   ) 
     125         trai(jn) = trai(jn) + glob_sum( 'trcini', trn(:,:,:,jn) * cvol(:,:,:)   ) 
    126126      END DO 
    127127 
  • NEMO/branches/2018/dev_r10164_HPC09_ESIWACE_PREP_MERGE/src/TOP/trcnam.F90

    r10297 r10314  
    2323   USE trdtrc_oce  ! 
    2424   USE iom         ! I/O manager 
     25#if defined key_mpp_mpi 
    2526   USE lib_mpp, ONLY: ncom_dttrc 
     27#endif 
    2628 
    2729   IMPLICIT NONE 
  • NEMO/branches/2018/dev_r10164_HPC09_ESIWACE_PREP_MERGE/src/TOP/trcrst.F90

    r10297 r10314  
    316316      ! 
    317317      DO jn = 1, jptra 
    318          ztraf = glob_sum( trn(:,:,:,jn) * zvol(:,:,:) ) 
     318         ztraf = glob_sum( 'trcrst', trn(:,:,:,jn) * zvol(:,:,:) ) 
    319319         zmin  = MINVAL( trn(:,:,:,jn), mask= ((tmask*SPREAD(tmask_i,DIM=3,NCOPIES=jpk).NE.0.)) ) 
    320320         zmax  = MAXVAL( trn(:,:,:,jn), mask= ((tmask*SPREAD(tmask_i,DIM=3,NCOPIES=jpk).NE.0.)) ) 
  • NEMO/branches/2018/dev_r10164_HPC09_ESIWACE_PREP_MERGE/src/TOP/trcstp.F90

    r10068 r10314  
    7373            cvol(:,:,jk) = e1e2t(:,:) * e3t_n(:,:,jk) * tmask(:,:,jk) 
    7474         END DO 
    75          areatot         = glob_sum( cvol(:,:,:) ) 
     75         areatot         = glob_sum( 'trcstp', cvol(:,:,:) ) 
    7676      ENDIF 
    7777      ! 
     
    107107      ztrai = 0._wp                                                   !  content of all tracers 
    108108      DO jn = 1, jptra 
    109          ztrai = ztrai + glob_sum( trn(:,:,:,jn) * cvol(:,:,:)   ) 
     109         ztrai = ztrai + glob_sum( 'trcstp', trn(:,:,:,jn) * cvol(:,:,:)   ) 
    110110      END DO 
    111111      IF( lwp ) WRITE(numstr,9300) kt,  ztrai / areatot 
Note: See TracChangeset for help on using the changeset viewer.