source: CONFIG/publications/ICOLMDZORINCA_CO2_Transport_GMD_2023/INCA/build/ppsrc/INCA_VEG/surf_weightedflx.f90 @ 6610

Last change on this file since 6610 was 6610, checked in by acosce, 9 months ago

INCA used for ICOLMDZORINCA_CO2_Transport_GMD_2023

File size: 550 bytes
Line 
1
2
3
4
5
6
7
8
9
10
11
12SUBROUTINE SURF_WEIGHTEDFLX() 
13 
14  USE SURF_CHEM_MOD 
15  USE INCA_DIM
16  USE IOIPSL
17  USE PRINT_INCA
18  USE PARAM_CHEM
19   
20  IMPLICIT NONE
21
22  INTEGER :: i, j
23  REAL, DIMENSION(PLON,nb_flux) :: emiflx_tmp
24
25  emiflx_tmp(:,:) = 0.
26  DO j = 1,nb_flux
27     DO i = 1,nbveget
28        emiflx_tmp(:,j) = emiflx_tmp(:,j) + emiflx_fromOrch(:,i,j)* maxvegetfrac_fromOrch(:,i) 
29     ENDDO
30     WHERE ( SUM(maxvegetfrac_fromOrch,dim=2) .NE. 0) 
31        tot_emiflx_fromOrch(:,j) = emiflx_tmp(:,j) 
32     ENDWHERE
33  ENDDO
34 
35END SUBROUTINE SURF_WEIGHTEDFLX
Note: See TracBrowser for help on using the repository browser.