source: CONFIG/publications/ICOLMDZORINCA_CO2_Transport_GMD_2023/INCA/build/ppsrc/INCA_PP/prd_loss.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: 1.4 KB
Line 
1
2
3
4
5
6
7
8
9
10
11
12
13      SUBROUTINE EXP_PROD_LOSS( prod, loss, y, rxt, &
14                het_rates)
15! Stacy Walters, NCAR, 1998.
16! Modified by Didier Hauglustaine, IPSL, for LMDZ/INCA, 2000.
17
18      USE INCA_DIM
19      IMPLICIT NONE
20
21!--------------------------------------------------------------------
22!     ... Dummy args                                                                     
23!--------------------------------------------------------------------
24      REAL, DIMENSION(PLNPLV,8), INTENT(out) :: prod,  loss
25      REAL, INTENT(in)    ::  y(PLNPLV,8)
26      REAL, INTENT(in)    ::  rxt(PLNPLV,12)
27      REAL, INTENT(in)    ::  het_rates(PLNPLV,1)
28
29
30
31!--------------------------------------------------------------------
32!       ... Loss and production for Explicit method
33!--------------------------------------------------------------------
34
35      loss(:,1) = ( + rxt(:,4))* y(:,1)
36      prod(:,1) = 0.
37      loss(:,2) = ( + het_rates(:,1))* y(:,2)
38      prod(:,2) =rxt(:,4)*y(:,1)
39      loss(:,3) = ( + rxt(:,2) + rxt(:,5))* y(:,3)
40      prod(:,3) = 0.
41      loss(:,4) = ( + rxt(:,6))* y(:,4)
42      prod(:,4) = 0.
43      loss(:,5) = ( + rxt(:,9) + rxt(:,10) + rxt(:,11) + rxt(:,12)) &
44                 * y(:,6)
45      prod(:,5) = 0.
46      loss(:,6) = ( + rxt(:,1) + rxt(:,7) + rxt(:,8))* y(:,5)
47      prod(:,6) = 0.
48      loss(:,7) = ( + rxt(:,3))* y(:,7)
49      prod(:,7) = 0.
50      loss(:,8) = 0.
51      prod(:,8) = 0.
52
53      end subroutine EXP_PROD_LOSS
Note: See TracBrowser for help on using the repository browser.