SUBROUTINE SURF_WEIGHTEDFLX() USE SURF_CHEM_MOD USE INCA_DIM USE IOIPSL USE PRINT_INCA USE PARAM_CHEM IMPLICIT NONE INTEGER :: i, j REAL, DIMENSION(PLON,nb_flux) :: emiflx_tmp emiflx_tmp(:,:) = 0. DO j = 1,nb_flux DO i = 1,nbveget emiflx_tmp(:,j) = emiflx_tmp(:,j) + emiflx_fromOrch(:,i,j)* maxvegetfrac_fromOrch(:,i) ENDDO WHERE ( SUM(maxvegetfrac_fromOrch,dim=2) .NE. 0) tot_emiflx_fromOrch(:,j) = emiflx_tmp(:,j) ENDWHERE ENDDO END SUBROUTINE SURF_WEIGHTEDFLX