Skip to content

Commit e92366e

Browse files
hwpangmjohnson541
authored andcommitted
Use getphasespecies to generalize post processing codes
1 parent 142bfc1 commit e92366e

File tree

7 files changed

+41
-41
lines changed

7 files changed

+41
-41
lines changed

src/AutomaticMechanismAnalysis.jl

Lines changed: 2 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -130,7 +130,7 @@ function follow(sim,rxnind,spcind,ropp,ropl,rts,forward;steptol=1e-2,branchtol=5
130130
return rpout
131131
else
132132
rpout = newrps[argmax([getsimilarity(sim.species[rpout.spcsinds[end]],
133-
sim.domain.phase.species[nrp.spcsinds[end]]) for nrp in newrps])]
133+
getphasespecies(sim.domain.phase)[nrp.spcsinds[end]]) for nrp in newrps])]
134134
end
135135
end
136136
end
@@ -361,7 +361,7 @@ function gettimescaleconnectivity(ssys::SystemSimulation,t)
361361
tsc = ones(length(ssys.species),length(ssys.species))*Inf
362362
domains = getfield.(ssys.sims,:domain)
363363
Nrxns = sum([length(sim.domain.phase.reactions) for sim in ssys.sims])+sum([length(inter.reactions) for inter in ssys.interfaces if hasproperty(inter,:reactions)])
364-
Nspcs = sum([length(sim.domain.phase.species) for sim in ssys.sims])
364+
Nspcs = sum([length(getphasespecies(sim.domain.phase)) for sim in ssys.sims])
365365
cstot = zeros(Nspcs)
366366
vns = Array{Any,1}(undef,length(domains))
367367
vcs = Array{Any,1}(undef,length(domains))

src/Debugging.jl

Lines changed: 2 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -129,7 +129,7 @@ function analyzecrash(ssys::SystemSimulation;tol=1e6)
129129
end
130130
end
131131
rdindex += length(sim.domain.phase.reactions)
132-
for (i,dy) in enumerate(dydt[sdindex:sdindex-1+length(sim.domain.phase.species)])
132+
for (i,dy) in enumerate(dydt[sdindex:sdindex-1+length(getphasespecies(sim.domain.phase))])
133133
if i > length(sim.species)
134134
continue
135135
end
@@ -140,7 +140,7 @@ function analyzecrash(ssys::SystemSimulation;tol=1e6)
140140
push!(spcs,getdebugspecies(sim.species[i],T;dy=dy,ratio=ratio,tol=tol,index=i))
141141
end
142142
end
143-
sdindex += length(sim.domain.phase.species)
143+
sdindex += length(getphasespecies(sim.domain.phase))
144144
end
145145
return DebugMech(spcs,rxns)
146146
end

src/Domain.jl

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -3304,7 +3304,7 @@ export getreactionindices
33043304
senstooriginspcind = Array{Int64,1}(undef,length(sensspcinds))
33053305
senstooriginrxnind = Array{Int64,1}(undef,length(sensrxninds))
33063306
for (i,spcind) in enumerate(sensspcinds)
3307-
spc = domain.phase.species[spcind]
3307+
spc = getphasespecies(domain.phase)[spcind]
33083308
sensspcnames[i] = spc.name
33093309
@inbounds sensspcs[i] = Species(
33103310
name=spc.name,

src/Plotting.jl

Lines changed: 15 additions & 15 deletions
Original file line numberDiff line numberDiff line change
@@ -12,9 +12,9 @@ function plotmolefractions(bsol::Q, tf::V; t0::Z=1e-15,N::Z2=1000,tol::Z3=0.01,e
1212
maxes = maximum(xs,dims=2)
1313
spnames = []
1414
for i = 1:length(maxes)
15-
if maxes[i] > tol && !(bsol.domain.phase.species[i].name in exclude)
15+
if maxes[i] > tol && !(getphasespecies(bsol.domain.phase)[i].name in exclude)
1616
plot(ts,xs[i,:])
17-
push!(spnames,bsol.domain.phase.species[i].name)
17+
push!(spnames,getphasespecies(bsol.domain.phase)[i].name)
1818
end
1919
end
2020
legend(spnames)
@@ -32,9 +32,9 @@ function plotmolefractions(bsol::Q; tol::V=0.01, exclude::M=Array{String,1}()) w
3232
maxes = maximum(xs,dims=2)
3333
spnames = []
3434
for i = 1:length(maxes)
35-
if maxes[i] > tol && !(bsol.domain.phase.species[i].name in exclude)
35+
if maxes[i] > tol && !(getphasespecies(bsol.domain.phase)[i].name in exclude)
3636
plot(bsol.sol.t,xs[i,:])
37-
push!(spnames,bsol.domain.phase.species[i].name)
37+
push!(spnames,getphasespecies(bsol.domain.phase)[i].name)
3838
end
3939
end
4040
legend(spnames)
@@ -63,7 +63,7 @@ function plotradicalmolefraction(bsol;t=0.0,ts=[])
6363
ts = range(0.0,stop=t, length=100);
6464
end
6565
radmf = zeros(length(ts))
66-
rads = [x.radicalelectrons for x in bsol.domain.phase.species]
66+
rads = [x.radicalelectrons for x in getphasespecies(bsol.domain.phase)]
6767
for (i,t) in enumerate(ts)
6868
radmf[i] = dot(rads,molefractions(bsol,t))
6969
end
@@ -75,7 +75,7 @@ end
7575
export plotradicalmolefraction
7676

7777
function plotmaxthermoforwardsensitivity(bsol, spcname; N=0, tol= 1e-2)
78-
spnames = getfield.(bsol.domain.phase.species,:name)
78+
spnames = getfield.(getphasespecies(bsol.domain.phase),:name)
7979
values = Array{Float64,1}()
8080
outnames = Array{String,1}()
8181
for spn in spnames
@@ -132,7 +132,7 @@ associated with each reaction
132132
N reactions are included all of which must have absolute value greater than abs(maximum prod or loss rate)*tol
133133
"""
134134
function plotrops(bsol::Y,name::X,t::Z;N=0,tol=0.01) where {Y<:Simulation, X<:AbstractString, Z<:Real}
135-
if !(name in getfield.(bsol.domain.phase.species,:name))
135+
if !(name in getfield.(getphasespecies(bsol.domain.phase),:name))
136136
error("Species $name not in domain")
137137
end
138138
rop = rops(bsol,name,t)
@@ -195,7 +195,7 @@ reactions with maximum (over time) production value greater than max production*
195195
maximum (over time) loss value greater than maximum loss*tol are included
196196
"""
197197
function plotrops(bsol::Y,name::X;rxnrates=Array{Float64,1}(),ts=Array{Float64,1}(),tol=0.05) where {Y<:Simulation, X<:AbstractString}
198-
if !(name in getfield.(bsol.domain.phase.species,:name))
198+
if !(name in getfield.(getphasespecies(bsol.domain.phase),:name))
199199
error("Species $name not in domain")
200200
end
201201
if length(rxnrates) == 0 || length(ts) == 0
@@ -243,7 +243,7 @@ reactions with maximum (over time) production value greater than max production*
243243
maximum (over time) loss value greater than maximum loss*tol are included
244244
"""
245245
function plotrops(bsol::Y,name::X;rxnrates=Array{Float64,1}(),ts=Array{Float64,1}(),tol=0.05) where {Y<:Simulation, X<:AbstractString}
246-
if !(name in getfield.(bsol.domain.phase.species,:name))
246+
if !(name in getfield.(getphasespecies(bsol.domain.phase),:name))
247247
error("Species $name not in domain")
248248
end
249249
if length(rxnrates) == 0 || length(ts) == 0
@@ -291,7 +291,7 @@ reactions with maximum (over time) production value greater than max production*
291291
maximum (over time) loss value greater than maximum loss*tol are included
292292
"""
293293
function plotrops(bsol::Y,name::X;rxnrates=Array{Float64,1}(),ts=Array{Float64,1}(),tol=0.05) where {Y<:Simulation, X<:AbstractString}
294-
if !(name in getfield.(bsol.domain.phase.species,:name))
294+
if !(name in getfield.(getphasespecies(bsol.domain.phase),:name))
295295
error("Species $name not in domain")
296296
end
297297
if length(rxnrates) == 0 || length(ts) == 0
@@ -431,7 +431,7 @@ function plotthermoadjointsensitivities(bsol::Y,name::X,dps::Z;N=0,tol=0.01) whe
431431
inds = inds[1:k]
432432
xs = Array{Float64,1}(1:length(inds))
433433
barh(xs,reverse(dpvals[inds]))
434-
yticks(xs,reverse(getfield.(bsol.domain.phase.species[inds],:name)))
434+
yticks(xs,reverse(getfield.(getphasespecies(bsol.domain.phase)[inds],:name)))
435435
if name in ["T","V"]
436436
xlabel("d$name/dG mol/kcal")
437437
else
@@ -445,7 +445,7 @@ function plotrateadjointsensitivities(bsol::Y,name::X,dps::Z;N=0,tol=0.01) where
445445
if !(name in ["T","V"] || name in bsol.names)
446446
error("Name $name not in domain")
447447
end
448-
dpvals = dps[length(bsol.domain.phase.species)+1:end]
448+
dpvals = dps[length(getphasespecies(bsol.domain.phase))+1:end]
449449
inds = reverse(sortperm(abs.(dpvals)))
450450
if N == 0
451451
N = length(inds)
@@ -492,7 +492,7 @@ end
492492
export plottimescales
493493

494494
function plotrxntransitorysensitivities(bsol,name,t;dSdt=nothing,tau=nothing,tol=1e-3,N=0,rxntol=1e-6)
495-
if !(name in getfield.(bsol.domain.phase.species,:name))
495+
if !(name in getfield.(getphasespecies(bsol.domain.phase),:name))
496496
error("Species $name not in domain")
497497
elseif !isnothing(dSdt) && (sum(dim > 1 for dim in size(dSdt)) > 1 || maximum(size(dSdt)) != length(bsol.p))
498498
error("dSdt must be a vector of length number of parameters")
@@ -546,7 +546,7 @@ end
546546
export plotrxntransitorysensitivities
547547

548548
function plotthermotransitorysensitivities(bsol,name,t;dSdt=nothing,tau=nothing,tol=1e-3,N=0)
549-
if !(name in getfield.(bsol.domain.phase.species,:name))
549+
if !(name in getfield.(getphasespecies(bsol.domain.phase),:name))
550550
error("Species $name not in domain")
551551
end
552552
ind = findfirst(isequal(name),bsol.names)
@@ -582,7 +582,7 @@ function plotthermotransitorysensitivities(bsol,name,t;dSdt=nothing,tau=nothing,
582582
inds = inds[1:k]
583583
xs = Array{Float64,1}(1:length(inds))
584584
barh(xs,reverse(dSdt[inds]))
585-
yticks(xs,reverse(getfield.(bsol.domain.phase.species[inds],:name)))
585+
yticks(xs,reverse(getfield.(getphasespecies(bsol.domain.phase)[inds],:name)))
586586
xlabel("Normalized Transitory Sensitivities for $name")
587587
return
588588
end

src/Reactor.jl

Lines changed: 4 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -100,7 +100,7 @@ function Reactor(domains::T,y0s::W1,tspan::W2,interfaces::Z=Tuple(),ps::X=SciMLB
100100
n = Nvars
101101
k = 1
102102
for (j,domain) in enumerate(domains)
103-
Nspcs = length(domain.phase.species)
103+
Nspcs = length(getphasespecies(domain.phase))
104104
Ntherm = length(domain.indexes) - 2
105105
for i = 1:8, j = 1:size(domain.rxnarray)[2]
106106
if domain.rxnarray[i,j] != 0
@@ -827,12 +827,12 @@ end
827827
export jacobianpforwarddiff!
828828

829829
function jacobianpforwarddiff(y::U,p::W,t::Z,domain::V,interfaces::Q3,colorvec::Q2=nothing) where {Q3,Q2,U<:AbstractArray,W,Z<:Real,V<:AbstractDomain}
830-
J = zeros(length(y),length(domain.phase.species)+length(domain.phase.reactions))
830+
J = zeros(length(y),length(getphasespecies(domain.phase))+length(domain.phase.reactions))
831831
jacobianpforwarddiff!(J,y,p,t,domain,interfaces,colorvec)
832832
end
833833

834834
function jacobianpforwarddiff(y::U,p::W,t::Z,domains::V,interfaces::Q3,colorvec::Q2=nothing) where {Q3,Q2,Q<:AbstractArray,U<:AbstractArray,W,Z<:Real,V<:Tuple}
835-
J = zeros(length(y),length(domains.phase.species)+length(domains.phase.reactions))
835+
J = zeros(length(y),length(getphasespecies(domains.phase))+length(domains.phase.reactions))
836836
jacobianpforwarddiff!(J,y,p,t,domains,interfaces,colorvec)
837837
end
838838

@@ -858,7 +858,7 @@ end
858858
export jacobiany
859859

860860
function jacobianp(y::U,p::W,t::Z,domain::V,interfaces::Q3,colorvec::Q2=nothing) where {Q3,Q2,U<:AbstractArray,W,Z<:Real,V<:AbstractDomain}
861-
J = zeros(length(y),length(domain.phase.species)+length(domain.phase.reactions))
861+
J = zeros(length(y),length(getphasespecies(domain.phase))+length(domain.phase.reactions))
862862
jacobianp!(J,y,p,t,domain,interfaces,colorvec)
863863
return J
864864
end

src/Simulation.jl

Lines changed: 16 additions & 16 deletions
Original file line numberDiff line numberDiff line change
@@ -20,7 +20,7 @@ struct Simulation{Q<:AbstractODESolution,W<:AbstractDomain,M,L<:AbstractArray,G<
2020
end
2121

2222
function Simulation(sol::Q,domain::W,interfaces=[],p=nothing) where {Q<:AbstractODESolution,W<:AbstractDomain}
23-
names = getfield.(domain.phase.species,:name)
23+
names = getfield.(getphasespecies(domain.phase),:name)
2424
Ns = sum(hcat(sol.interp.u...)[domain.indexes[1]:domain.indexes[2],:],dims=1)
2525
if hasproperty(sol.interp,:du)
2626
Nderivs = sum(hcat(sol.interp.du...)[domain.indexes[1]:domain.indexes[2],:],dims=1)
@@ -32,7 +32,7 @@ function Simulation(sol::Q,domain::W,interfaces=[],p=nothing) where {Q<:Abstract
3232
if p === nothing
3333
p = domain.p
3434
end
35-
return Simulation(sol,domain,interfaces,names,F,Ns,domain.phase.species,domain.phase.reactions,p)
35+
return Simulation(sol,domain,interfaces,names,F,Ns,getphasespecies(domain.phase),domain.phase.reactions,p)
3636
end
3737

3838
function Simulation(sol::Q,domain::W,reducedmodelmappings::ReducedModelMappings,interfaces=[],p=nothing) where {Q<:AbstractODESolution,W<:AbstractDomain}
@@ -68,8 +68,8 @@ function Simulation(sol::Q,domain::W,reducedmodelmappings::ReducedModelMappings,
6868
t = sol.t
6969
sol = SciMLBase.build_solution(sol.prob, sol.alg, t, u, retcode = :Success)
7070

71-
species_range = 1:length(domain.phase.species)
72-
names = getfield.(domain.phase.species,:name)
71+
species_range = 1:length(getphasespecies(domain.phase))
72+
names = getfield.(getphasespecies(domain.phase),:name)
7373
Ns = sum(hcat(sol.interp.u...)[species_range,:],dims=1)
7474
if hasproperty(sol.interp,:du)
7575
Nderivs = sum(hcat(sol.interp.du...)[species_range,:],dims=1)
@@ -81,7 +81,7 @@ function Simulation(sol::Q,domain::W,reducedmodelmappings::ReducedModelMappings,
8181
if p === nothing
8282
p = domain.p
8383
end
84-
return Simulation(sol,domain,interfaces,names,F,Ns,domain.phase.species,domain.phase.reactions,p)
84+
return Simulation(sol,domain,interfaces,names,F,Ns,getphasespecies(domain.phase),domain.phase.reactions,p)
8585
end
8686

8787
export Simulation
@@ -119,7 +119,7 @@ function SystemSimulation(sol,domains,interfaces,p)
119119
species = Array{Species,1}()
120120
for sim in sims
121121
append!(names,sim.names)
122-
append!(species,sim.domain.phase.species)
122+
append!(species,getphasespecies(sim.domain.phase))
123123
append!(reactions,sim.domain.phase.reactions)
124124
end
125125
for inter in interfaces
@@ -140,7 +140,7 @@ export iterate
140140
Broadcast.broadcastable(p::T) where {T<:AbstractSimulation} = Ref(p)
141141
export broadcastable
142142

143-
spcindex(bsol::Z,name::Q) where {Z<:Simulation,Q<:AbstractString} = findfirst(isequal(name),getfield.(bsol.domain.phase.species,:name))
143+
spcindex(bsol::Z,name::Q) where {Z<:Simulation,Q<:AbstractString} = findfirst(isequal(name),getfield.(getphasespecies(bsol.domain.phase),:name))
144144
export spcindex
145145

146146
function molefractions(bsol::Q,name::W,t::E) where {Q<:AbstractSimulation, W<:String, E<:Real}
@@ -234,7 +234,7 @@ this outputs a sparse matrix of num reactions xnum species containing the produ
234234
rate of that species associated with that reaction
235235
"""
236236
function rops(bsol::Q,t::X) where {Q<:Simulation,X<:Real}
237-
ropmat = spzeros(length(bsol.domain.phase.reactions),length(bsol.domain.phase.species))
237+
ropmat = spzeros(length(bsol.domain.phase.reactions),length(getphasespecies(bsol.domain.phase)))
238238
cs,kfs,krevs = calcthermo(bsol.domain,bsol.sol(t),t)[[2,9,10]]
239239
V = getdomainsize(bsol,t)
240240
@simd for i in 1:length(bsol.domain.phase.reactions)
@@ -253,7 +253,7 @@ end
253253
function rops(ssys::SystemSimulation,t)
254254
domains = getfield.(ssys.sims,:domain)
255255
Nrxns = sum([length(sim.domain.phase.reactions) for sim in ssys.sims])+sum([length(inter.reactions) for inter in ssys.interfaces if hasproperty(inter,:reactions)])
256-
Nspcs = sum([length(sim.domain.phase.species) for sim in ssys.sims])
256+
Nspcs = sum([length(getphasespecies(sim.domain.phase)) for sim in ssys.sims])
257257
cstot = zeros(Nspcs)
258258
vns = Array{Any,1}(undef,length(domains))
259259
vcs = Array{Any,1}(undef,length(domains))
@@ -302,7 +302,7 @@ function rops(bsol::Y,name::X,t::Z) where {Y<:Simulation, X<:AbstractString, Z<:
302302
rop = spzeros(length(bsol.domain.phase.reactions))
303303
cs,kfs,krevs = calcthermo(bsol.domain,bsol.sol(t),t)[[2,9,10]]
304304
V = getdomainsize(bsol,t)
305-
ind = findfirst(isequal(name),getfield.(bsol.domain.phase.species,:name))
305+
ind = findfirst(isequal(name),getfield.(getphasespecies(bsol.domain.phase),:name))
306306
@assert !isa(ind,Nothing) "species $name not in species array"
307307
for (i,rxn) in enumerate(bsol.domain.phase.reactions)
308308
c = 0
@@ -320,7 +320,7 @@ function rops(ssys::SystemSimulation,name,t)
320320
domains = getfield.(ssys.sims,:domain)
321321
ind = findfirst(isequal(name),ssys.names)
322322
Nrxns = sum([length(sim.domain.phase.reactions) for sim in ssys.sims])+sum([length(inter.reactions) for inter in ssys.interfaces if hasproperty(inter,:reactions)])
323-
Nspcs = sum([length(sim.domain.phase.species) for sim in ssys.sims])
323+
Nspcs = sum([length(getphasespecies(sim.domain.phase)) for sim in ssys.sims])
324324
cstot = zeros(Nspcs)
325325
vns = Array{Any,1}(undef,length(domains))
326326
vcs = Array{Any,1}(undef,length(domains))
@@ -609,7 +609,7 @@ function getconcentrationsensitivity(bsol::Simulation{Q,W,L,G}, numerator::Strin
609609
@assert denominator in bsol.names
610610
indnum = findfirst(isequal(numerator),bsol.names)+bsol.domain.indexes[1]-1
611611
inddeno = findfirst(isequal(denominator),bsol.names)+bsol.domain.parameterindexes[1]-1
612-
Nvars = length(bsol.domain.phase.species)+length(bsol.domain.indexes)-2
612+
Nvars = length(getphasespecies(bsol.domain.phase))+length(bsol.domain.indexes)-2
613613
Nrxns = length(bsol.domain.phase.reactions)
614614
x,dp = extract_local_sensitivities(bsol.sol,t)
615615
s = dp[inddeno][indnum]
@@ -626,7 +626,7 @@ function getconcentrationsensitivity(bsol::Simulation{Q,W,L,G}, numerator::Strin
626626
@assert denominator in bsol.names
627627
indnum = findfirst(isequal(numerator),bsol.names)+bsol.domain.indexes[1]-1
628628
inddeno = findfirst(isequal(denominator),bsol.names)+bsol.domain.parameterindexes[1]-1
629-
Nvars = length(bsol.domain.phase.species)+length(bsol.domain.indexes)-2
629+
Nvars = length(getphasespecies(bsol.domain.phase))+length(bsol.domain.indexes)-2
630630
Nrxns = length(bsol.domain.phase.reactions)
631631
x,dp = extract_local_sensitivities(bsol.sol,t)
632632
svals = dp[inddeno][bsol.domain.indexes[1]:bsol.domain.indexes[2]]
@@ -645,7 +645,7 @@ function getconcentrationsensitivity(bsol::Simulation{Q,W,L,G}, numerator::Strin
645645
@assert numerator in bsol.names
646646
indnum = findfirst(isequal(numerator),bsol.names)+bsol.domain.indexes[1]-1
647647
inddeno = denominator+bsol.domain.parameterindexes[1]-1
648-
Nvars = length(bsol.domain.phase.species)+length(bsol.domain.indexes)-2
648+
Nvars = length(getphasespecies(bsol.domain.phase))+length(bsol.domain.indexes)-2
649649
Nrxns = length(bsol.domain.phase.reactions)
650650
x,dp = extract_local_sensitivities(bsol.sol,t)
651651
s = dp[inddeno+length(bsol.domain.phase.species)][indnum]
@@ -665,7 +665,7 @@ function getconcentrationsensitivity(bsol::Simulation{Q,W,L,G}, numerator::Strin
665665
@assert numerator in bsol.names
666666
indnum = findfirst(isequal(numerator),bsol.names)+bsol.domain.indexes[1]-1
667667
inddeno = denominator+bsol.domain.parameterindexes[1]-1
668-
Nvars = length(bsol.domain.phase.species)+length(bsol.domain.indexes)-2
668+
Nvars = length(getphasespecies(bsol.domain.phase))+length(bsol.domain.indexes)-2
669669
Nrxns = length(bsol.domain.phase.reactions)
670670
x,dp = extract_local_sensitivities(bsol.sol,t)
671671
svals = dp[inddeno+length(bsol.domain.phase.species)][bsol.domain.indexes[1]:bsol.domain.indexes[2]]
@@ -713,7 +713,7 @@ function rates(ssys::Q,t::X) where {Q<:SystemSimulation,X<:Real}
713713
rts = zeros(length(ssys.reactions))
714714
domains = getfield.(ssys.sims,:domain)
715715
Nrxns = sum([length(sim.domain.phase.reactions) for sim in ssys.sims])+sum([hasproperty(inter,:reactions) ? length(inter.reactions) : 0 for inter in ssys.interfaces])
716-
Nspcs = sum([length(sim.domain.phase.species) for sim in ssys.sims])
716+
Nspcs = sum([length(getphasespecies(sim.domain.phase)) for sim in ssys.sims])
717717
cstot = zeros(Nspcs)
718718
vns = Array{Any,1}(undef,length(domains))
719719
vcs = Array{Any,1}(undef,length(domains))

src/fluxdiagrams.jl

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -133,7 +133,7 @@ function makefluxdiagrams(bsol,ts;centralspecieslist=Array{String,1}(),superimpo
133133
colorscheme="viridis",removeunconnectednodes=false)
134134

135135
if hasproperty(bsol,:domain)
136-
specieslist = bsol.domain.phase.species
136+
specieslist = getphasespecies(bsol.domain.phase)
137137
reactionlist = bsol.domain.phase.reactions
138138
else
139139
specieslist = bsol.species

0 commit comments

Comments
 (0)