1 MODULE KPP_ROOT_Integrator
3 USE KPP_ROOT_Parameters
, ONLY
: NVAR
, NFIX
, NREACT
4 USE KPP_ROOT_Global
, ONLY
: TIME
, RCONST
, Volume
6 USE KPP_ROOT_Stochastic
12 !~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
13 SUBROUTINE Gillespie(Nevents
, T
, SCT
, NmlcV
, NmlcF
)
14 !~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
16 ! Gillespie stochastic integration
18 ! Nevents = no. of individual reaction events to be simulated
19 ! SCT = stochastic rate constants
21 ! NmlcV, NmlcF = no. of molecules for variable and fixed species
23 ! T = updated time (after Nevents reactions)
24 ! NmlcV = updated no. of molecules for variable species
27 !~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
31 INTEGER :: NmlcV(NVAR
), NmlcF(NFIX
)
34 KPP_REAL
:: A(NREACT
), SCT(NREACT
), x
38 ! Uniformly distributed random numbers
39 CALL RANDOM_NUMBER(r1
)
40 CALL RANDOM_NUMBER(r2
)
45 CALL Propensity ( NmlcV
, NmlcF
, SCT
, A
)
46 ! Cumulative sum of propensities
51 ! Index of next reaction
60 ! Update time with time to next reaction
61 T
= T
- LOG(r2
)/A(NREACT
);
64 CALL MoleculeChange( m
, NmlcV
)
70 SUBROUTINE PropensityTemplate( T
, NmlcV
, NmlcF
, Prop
)
71 KPP_REAL
, INTENT(IN
) :: T
72 INTEGER, INTENT(IN
) :: NmlcV(NVAR
), NmlcF(NFIX
)
73 KPP_REAL
, INTENT(OUT
) :: Prop(NREACT
)
74 KPP_REAL
:: Tsave
, SCT(NREACT
)
75 ! Update the stochastic reaction rates, which may be time dependent
79 CALL StochasticRates( RCONST
, Volume
, SCT
)
80 CALL Propensity ( NmlcV
, NmlcF
, SCT
, Prop
)
82 END SUBROUTINE PropensityTemplate
84 END SUBROUTINE Gillespie
86 END MODULE KPP_ROOT_Integrator