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

Changeset 9227


Ignore:
Timestamp:
2018-01-15T10:30:57+01:00 (6 years ago)
Author:
gm
Message:

dev_merge_2017: diahsb.F90: reduce mpp-global communication and add a control print at nitend

File:
1 edited

Legend:

Unmodified
Added
Removed
  • branches/2017/dev_merge_2017/NEMOGCM/NEMO/OPA_SRC/DIA/diahsb.F90

    r9169 r9227  
    8181      REAL(wp)   ::   z_wn_trd_t , z_wn_trd_s     !    -     - 
    8282      REAL(wp)   ::   z_ssh_hc , z_ssh_sc         !    -     - 
    83       REAL(wp), DIMENSION(jpi,jpj) ::   z2d0, z2d1   ! 2D workspace 
     83      REAL(wp), DIMENSION(jpi,jpj)       ::   z2d0, z2d1   ! 2D workspace 
     84      REAL(wp), DIMENSION(jpi,jpj,jpkm1) ::   zwrk         ! 3D workspace 
    8485      !!--------------------------------------------------------------------------- 
    8586      IF( ln_timing )   CALL timing_start('dia_hsb')       
     
    9091      ! 1 - Trends due to forcing ! 
    9192      ! ------------------------- ! 
    92       z_frc_trd_v = r1_rau0 * glob_sum( - ( emp(:,:) - rnf(:,:) + fwfisf(:,:) ) * surf(:,:) ) ! volume fluxes 
    93       z_frc_trd_t =           glob_sum( sbc_tsc(:,:,jp_tem) * surf(:,:) )                               ! heat fluxes 
    94       z_frc_trd_s =           glob_sum( sbc_tsc(:,:,jp_sal) * surf(:,:) )                               ! salt fluxes 
    95       ! Add runoff    heat & salt input 
     93      z_frc_trd_v = r1_rau0 * glob_sum( - ( emp(:,:) - rnf(:,:) + fwfisf(:,:) ) * surf(:,:) )   ! volume fluxes 
     94      z_frc_trd_t =           glob_sum( sbc_tsc(:,:,jp_tem) * surf(:,:) )                       ! heat fluxes 
     95      z_frc_trd_s =           glob_sum( sbc_tsc(:,:,jp_sal) * surf(:,:) )                       ! salt fluxes 
     96      !                    !  Add runoff    heat & salt input 
    9697      IF( ln_rnf    )   z_frc_trd_t = z_frc_trd_t + glob_sum( rnf_tsc(:,:,jp_tem) * surf(:,:) ) 
    9798      IF( ln_rnf_sal)   z_frc_trd_s = z_frc_trd_s + glob_sum( rnf_tsc(:,:,jp_sal) * surf(:,:) ) 
    98       ! Add ice shelf heat & salt input 
    99       IF( ln_isf    ) z_frc_trd_t = z_frc_trd_t + glob_sum( risf_tsc(:,:,jp_tem) * surf(:,:) ) 
    100       ! Add penetrative solar radiation 
     99      !                    ! Add ice shelf heat & salt input 
     100      IF( ln_isf    )   z_frc_trd_t = z_frc_trd_t + glob_sum( risf_tsc(:,:,jp_tem) * surf(:,:) ) 
     101      !                    ! Add penetrative solar radiation 
    101102      IF( ln_traqsr )   z_frc_trd_t = z_frc_trd_t + r1_rau0_rcp * glob_sum( qsr     (:,:) * surf(:,:) ) 
    102       ! Add geothermal heat flux 
     103      !                    ! Add geothermal heat flux 
    103104      IF( ln_trabbc )   z_frc_trd_t = z_frc_trd_t +               glob_sum( qgh_trd0(:,:) * surf(:,:) ) 
    104105      ! 
     
    129130 
    130131      ! ------------------------ ! 
    131       ! 2 -  Content variations ! 
     132      ! 2 -  Content variations  ! 
    132133      ! ------------------------ ! 
    133134      ! glob_sum_full is needed because you keep the full interior domain to compute the sum (iscpl) 
    134       zdiff_v2 = 0._wp 
    135       zdiff_hc = 0._wp 
    136       zdiff_sc = 0._wp 
    137  
    138       ! volume variation (calculated with ssh) 
    139       zdiff_v1 = glob_sum_full( surf(:,:) * sshn(:,:) - surf_ini(:,:) * ssh_ini(:,:) ) 
    140  
    141       ! heat & salt content variation (associated with ssh) 
    142       IF( ln_linssh ) THEN 
    143          IF( ln_isfcav ) THEN 
     135 
     136      !                    ! volume variation (calculated with ssh) 
     137      zdiff_v1 = glob_sum_full( surf(:,:)*sshn(:,:) - surf_ini(:,:)*ssh_ini(:,:) ) 
     138 
     139      !                    ! heat & salt content variation (associated with ssh) 
     140      IF( ln_linssh ) THEN       ! linear free surface case 
     141         IF( ln_isfcav ) THEN          ! ISF case 
    144142            DO ji = 1, jpi 
    145143               DO jj = 1, jpj 
     
    148146               END DO 
    149147            END DO 
    150          ELSE 
     148         ELSE                          ! no under ice-shelf seas 
    151149            z2d0(:,:) = surf(:,:) * ( tsn(:,:,1,jp_tem) * sshn(:,:) - ssh_hc_loc_ini(:,:) )  
    152150            z2d1(:,:) = surf(:,:) * ( tsn(:,:,1,jp_sal) * sshn(:,:) - ssh_sc_loc_ini(:,:) )  
     
    155153         z_ssh_sc = glob_sum_full( z2d1 )  
    156154      ENDIF 
    157  
    158       DO jk = 1, jpkm1 
    159          ! volume variation (calculated with scale factors) 
    160          zdiff_v2 = zdiff_v2 + glob_sum_full( surf(:,:) * tmask(:,:,jk)            & 
    161             &                           * e3t_n(:,:,jk) - surf_ini(:,:) * e3t_ini(:,:,jk) ) 
    162          ! heat content variation 
    163          zdiff_hc = zdiff_hc + glob_sum_full(  surf(:,:) * tmask(:,:,jk)                                   &  
    164             &                           * e3t_n(:,:,jk) * tsn(:,:,jk,jp_tem) - surf_ini(:,:) * hc_loc_ini(:,:,jk) )  
    165          ! salt content variation 
    166          zdiff_sc = zdiff_sc + glob_sum_full( surf    (:,:) * tmask(:,:,jk)                           & 
    167                                         * e3t_n(:,:,jk) * tsn(:,:,jk,jp_sal) - surf_ini(:,:) * sc_loc_ini(:,:,jk) ) 
    168       ENDDO 
     155      ! 
     156      DO jk = 1, jpkm1     ! volume variation (calculated with scale factors) 
     157         zwrk(:,:,jk) = ( surf(:,:)*e3t_n(:,:,jk) - surf_ini(:,:)*e3t_ini(:,:,jk) ) * tmask(:,:,jk) 
     158      END DO 
     159      zdiff_v2 = glob_sum_full( zwrk(:,:,:) ) 
     160      DO jk = 1, jpkm1           ! heat content variation 
     161         zwrk(:,:,jk) = ( surf(:,:)*e3t_n(:,:,jk)*tsn(:,:,jk,jp_tem) - surf_ini(:,:)*hc_loc_ini(:,:,jk) ) * tmask(:,:,jk) 
     162      END DO 
     163      zdiff_hc = glob_sum_full( zwrk(:,:,:) ) 
     164      DO jk = 1, jpkm1           ! salt content variation 
     165         zwrk(:,:,jk) = ( surf(:,:)*e3t_n(:,:,jk)*tsn(:,:,jk,jp_sal) - surf_ini(:,:)*sc_loc_ini(:,:,jk) ) * tmask(:,:,jk) 
     166      END DO 
     167      zdiff_sc = glob_sum_full( zwrk(:,:,:) ) 
    169168 
    170169      ! ------------------------ ! 
     
    185184      ! 4 - Diagnostics writing ! 
    186185      ! ----------------------- ! 
    187       zvol_tot = 0._wp                    ! total ocean volume (calculated with scale factors) 
    188       DO jk = 1, jpkm1 
    189          zvol_tot  = zvol_tot + glob_sum_full( surf(:,:) * tmask(:,:,jk) * e3t_n(:,:,jk) ) 
     186      DO jk = 1, jpkm1           ! total ocean volume (calculated with scale factors) 
     187         zwrk(:,:,jk) = surf(:,:) * e3t_n(:,:,jk) * tmask(:,:,jk) 
    190188      END DO 
     189      zvol_tot = glob_sum_full( zwrk(:,:,:) ) 
    191190 
    192191!!gm to be added ? 
     
    203202 
    204203      IF( .NOT. ln_linssh ) THEN 
    205         CALL iom_put( 'bgtemper' , zdiff_hc / zvol_tot )              ! Temperature drift     (C)  
    206         CALL iom_put( 'bgsaline' , zdiff_sc / zvol_tot )              ! Salinity    drift     (pss) 
    207         CALL iom_put( 'bgheatco' , zdiff_hc * 1.e-20 * rau0 * rcp )   ! Heat content drift    (1.e20 J)  
    208         CALL iom_put( 'bgheatfx' , zdiff_hc * rau0 * rcp /  &         ! Heat flux drift       (W/m2)  
    209            &                       ( surf_tot * kt * rdt )        ) 
    210         CALL iom_put( 'bgsaltco' , zdiff_sc * 1.e-9    )              ! Salt content drift    (psu*km3) 
    211         CALL iom_put( 'bgvolssh' , zdiff_v1 * 1.e-9    )              ! volume ssh drift      (km3)   
    212         CALL iom_put( 'bgvole3t' , zdiff_v2 * 1.e-9    )              ! volume e3t drift      (km3)   
     204         CALL iom_put( 'bgtemper' , zdiff_hc / zvol_tot )              ! Temperature drift     (C)  
     205         CALL iom_put( 'bgsaline' , zdiff_sc / zvol_tot )              ! Salinity    drift     (PSU) 
     206         CALL iom_put( 'bgheatco' , zdiff_hc * 1.e-20 * rau0 * rcp )   ! Heat content drift    (1.e20 J)  
     207         CALL iom_put( 'bgheatfx' , zdiff_hc * rau0 * rcp /  &         ! Heat flux drift       (W/m2)  
     208            &                       ( surf_tot * kt * rdt )        ) 
     209         CALL iom_put( 'bgsaltco' , zdiff_sc * 1.e-9    )              ! Salt content drift    (psu*km3) 
     210         CALL iom_put( 'bgvolssh' , zdiff_v1 * 1.e-9    )              ! volume ssh drift      (km3)   
     211         CALL iom_put( 'bgvole3t' , zdiff_v2 * 1.e-9    )              ! volume e3t drift      (km3)   
     212         ! 
     213         IF( kt == nitend .AND. lwp ) THEN 
     214            WRITE(numout,*) 
     215            WRITE(numout,*) 'dia_hsb : last time step hsb diagnostics: at it= ', kt,' date= ', ndastp 
     216            WRITE(numout,*) '~~~~~~~' 
     217            WRITE(numout,*) '   Temperature drift = ', zdiff_hc / zvol_tot, ' C' 
     218            WRITE(numout,*) '   Salinity    drift = ', zdiff_sc / zvol_tot, ' PSU' 
     219            WRITE(numout,*) '   volume ssh  drift = ', zdiff_v1 * 1.e-9   , ' km^3' 
     220            WRITE(numout,*) '   volume e3t  drift = ', zdiff_v2 * 1.e-9   , ' km^3' 
     221         ENDIF 
     222         ! 
    213223      ELSE 
    214         CALL iom_put( 'bgtemper' , zdiff_hc1 / zvol_tot)              ! Heat content drift    (C)  
    215         CALL iom_put( 'bgsaline' , zdiff_sc1 / zvol_tot)              ! Salt content drift    (pss) 
    216         CALL iom_put( 'bgheatco' , zdiff_hc1 * 1.e-20 * rau0 * rcp )  ! Heat content drift    (1.e20 J)  
    217         CALL iom_put( 'bgheatfx' , zdiff_hc1 * rau0 * rcp /  &        ! Heat flux drift       (W/m2)  
    218            &                       ( surf_tot * kt * rdt )         ) 
    219         CALL iom_put( 'bgsaltco' , zdiff_sc1 * 1.e-9    )             ! Salt content drift    (psu*km3) 
    220         CALL iom_put( 'bgvolssh' , zdiff_v1 * 1.e-9    )              ! volume ssh drift      (km3)   
    221         CALL iom_put( 'bgmistem' , zerr_hc1 / zvol_tot )              ! hc  - error due to free surface (C) 
    222         CALL iom_put( 'bgmissal' , zerr_sc1 / zvol_tot )              ! sc  - error due to free surface (psu) 
     224         CALL iom_put( 'bgtemper' , zdiff_hc1 / zvol_tot)              ! Heat content drift    (C)  
     225         CALL iom_put( 'bgsaline' , zdiff_sc1 / zvol_tot)              ! Salt content drift    (PSU) 
     226         CALL iom_put( 'bgheatco' , zdiff_hc1 * 1.e-20 * rau0 * rcp )  ! Heat content drift    (1.e20 J)  
     227         CALL iom_put( 'bgheatfx' , zdiff_hc1 * rau0 * rcp /  &        ! Heat flux drift       (W/m2)  
     228            &                       ( surf_tot * kt * rdt )         ) 
     229         CALL iom_put( 'bgsaltco' , zdiff_sc1 * 1.e-9    )             ! Salt content drift    (psu*km3) 
     230         CALL iom_put( 'bgvolssh' , zdiff_v1 * 1.e-9    )              ! volume ssh drift      (km3)   
     231         CALL iom_put( 'bgmistem' , zerr_hc1 / zvol_tot )              ! hc  - error due to free surface (C) 
     232         CALL iom_put( 'bgmissal' , zerr_sc1 / zvol_tot )              ! sc  - error due to free surface (psu) 
    223233      ENDIF 
    224234      ! 
     
    380390      ! 2 - Time independant variables and file opening ! 
    381391      ! ----------------------------------------------- ! 
    382       surf(:,:) = e1t(:,:) * e2t(:,:) * tmask_i(:,:)      ! masked surface grid cell area 
    383       surf_tot  = glob_sum( surf(:,:) )                   ! total ocean surface area 
     392      surf(:,:) = e1e2t(:,:) * tmask_i(:,:)     ! masked surface grid cell area 
     393      surf_tot  = glob_sum( surf(:,:) )         ! total ocean surface area 
    384394 
    385395      IF( ln_bdy ) CALL ctl_warn( 'dia_hsb_init: heat/salt budget does not consider open boundary fluxes' )          
Note: See TracChangeset for help on using the changeset viewer.