module Drasil.PDController.Unitals where
import Data.Drasil.Constraints (gtZeroConstr)
import Data.Drasil.SI_Units (second)
import Language.Drasil
import Language.Drasil.Chunk.Concept.NamedCombinators
import Drasil.PDController.Concepts
syms, symFS, symFt, syminvLaplace, symKd, symKp,
symYT, symYS, symYrT, symYrS, symET, symES, symPS, symDS, symHS,
symCT, symCS, symTStep, symTSim, symAbsTol, symRelTol,
symDampingCoeff, symStifnessCoeff :: Symbol
symFS :: Symbol
symFS = Symbol -> Symbol -> Symbol
sub (String -> Symbol
variable String
"F") (Symbol -> Symbol) -> Symbol -> Symbol
forall a b. (a -> b) -> a -> b
$ String -> Symbol
label String
"s"
syminvLaplace :: Symbol
syminvLaplace = String -> Symbol
variable String
"L⁻¹[F(s)]"
syms :: Symbol
syms = String -> Symbol
variable String
"s"
symFt :: Symbol
symFt = Symbol -> Symbol -> Symbol
sub (String -> Symbol
variable String
"f") (Symbol -> Symbol) -> Symbol -> Symbol
forall a b. (a -> b) -> a -> b
$ String -> Symbol
label String
"t"
symKd :: Symbol
symKd = Symbol -> Symbol -> Symbol
sub (String -> Symbol
variable String
"K") (Symbol -> Symbol) -> Symbol -> Symbol
forall a b. (a -> b) -> a -> b
$ String -> Symbol
label String
"d"
symKp :: Symbol
symKp = Symbol -> Symbol -> Symbol
sub (String -> Symbol
variable String
"K") (Symbol -> Symbol) -> Symbol -> Symbol
forall a b. (a -> b) -> a -> b
$ String -> Symbol
label String
"p"
symYrT :: Symbol
symYrT = Symbol -> Symbol -> Symbol
sub (String -> Symbol
variable String
"r") (Symbol -> Symbol) -> Symbol -> Symbol
forall a b. (a -> b) -> a -> b
$ String -> Symbol
label String
"t"
symYrS :: Symbol
symYrS = Symbol -> Symbol -> Symbol
sub (String -> Symbol
variable String
"R") (Symbol -> Symbol) -> Symbol -> Symbol
forall a b. (a -> b) -> a -> b
$ String -> Symbol
label String
"s"
symYT :: Symbol
symYT = Symbol -> Symbol -> Symbol
sub (String -> Symbol
variable String
"y") (Symbol -> Symbol) -> Symbol -> Symbol
forall a b. (a -> b) -> a -> b
$ String -> Symbol
label String
"t"
symYS :: Symbol
symYS = Symbol -> Symbol -> Symbol
sub (String -> Symbol
variable String
"Y") (Symbol -> Symbol) -> Symbol -> Symbol
forall a b. (a -> b) -> a -> b
$ String -> Symbol
label String
"s"
symET :: Symbol
symET = Symbol -> Symbol -> Symbol
sub (String -> Symbol
variable String
"e") (Symbol -> Symbol) -> Symbol -> Symbol
forall a b. (a -> b) -> a -> b
$ String -> Symbol
label String
"t"
symES :: Symbol
symES = Symbol -> Symbol -> Symbol
sub (String -> Symbol
variable String
"E") (Symbol -> Symbol) -> Symbol -> Symbol
forall a b. (a -> b) -> a -> b
$ String -> Symbol
label String
"s"
symPS :: Symbol
symPS = Symbol -> Symbol -> Symbol
sub (String -> Symbol
variable String
"P") (Symbol -> Symbol) -> Symbol -> Symbol
forall a b. (a -> b) -> a -> b
$ String -> Symbol
label String
"s"
symDS :: Symbol
symDS = Symbol -> Symbol -> Symbol
sub (String -> Symbol
variable String
"D") (Symbol -> Symbol) -> Symbol -> Symbol
forall a b. (a -> b) -> a -> b
$ String -> Symbol
label String
"s"
symHS :: Symbol
symHS = Symbol -> Symbol -> Symbol
sub (String -> Symbol
variable String
"H") (Symbol -> Symbol) -> Symbol -> Symbol
forall a b. (a -> b) -> a -> b
$ String -> Symbol
label String
"s"
symCT :: Symbol
symCT = Symbol -> Symbol -> Symbol
sub (String -> Symbol
variable String
"c") (Symbol -> Symbol) -> Symbol -> Symbol
forall a b. (a -> b) -> a -> b
$ String -> Symbol
label String
"t"
symCS :: Symbol
symCS = Symbol -> Symbol -> Symbol
sub (String -> Symbol
variable String
"C") (Symbol -> Symbol) -> Symbol -> Symbol
forall a b. (a -> b) -> a -> b
$ String -> Symbol
label String
"s"
symTStep :: Symbol
symTStep = Symbol -> Symbol -> Symbol
sub (String -> Symbol
variable String
"t") (Symbol -> Symbol) -> Symbol -> Symbol
forall a b. (a -> b) -> a -> b
$ String -> Symbol
label String
"step"
symTSim :: Symbol
symTSim = Symbol -> Symbol -> Symbol
sub (String -> Symbol
variable String
"t") (Symbol -> Symbol) -> Symbol -> Symbol
forall a b. (a -> b) -> a -> b
$ String -> Symbol
label String
"sim"
symAbsTol :: Symbol
symAbsTol = String -> Symbol
variable String
"AbsTol"
symRelTol :: Symbol
symRelTol = String -> Symbol
variable String
"RelTol"
symDampingCoeff :: Symbol
symDampingCoeff = String -> Symbol
variable String
"c"
symStifnessCoeff :: Symbol
symStifnessCoeff = String -> Symbol
variable String
"k"
symbols :: [QuantityDict]
symbols :: [QuantityDict]
symbols
= [QuantityDict
qdLaplaceTransform, QuantityDict
qdFreqDomain, QuantityDict
qdFxnTDomain,
QuantityDict
qdInvLaplaceTransform, QuantityDict
qdPropGain, QuantityDict
qdDerivGain, QuantityDict
qdSetPointTD, QuantityDict
qdSetPointFD,
QuantityDict
qdProcessVariableTD, QuantityDict
qdProcessVariableFD, QuantityDict
qdProcessErrorTD,
QuantityDict
qdProcessErrorFD, QuantityDict
qdDerivativeControlFD, QuantityDict
qdPropControlFD,
QuantityDict
qdTransferFunctionFD, QuantityDict
qdCtrlVarTD, QuantityDict
qdCtrlVarFD, QuantityDict
qdStepTime, QuantityDict
qdSimTime,
QuantityDict
qdDampingCoeff, QuantityDict
qdStiffnessCoeff]
qdLaplaceTransform, qdFreqDomain, qdFxnTDomain,
qdInvLaplaceTransform, qdPropGain, qdDerivGain,
qdSetPointTD, qdSetPointFD, qdProcessVariableTD,
qdProcessVariableFD, qdProcessErrorTD, qdProcessErrorFD,
qdPropControlFD, qdDerivativeControlFD,
qdTransferFunctionFD, qdCtrlVarFD, qdCtrlVarTD, qdStepTime,
qdSimTime, qdDampingCoeff, qdStiffnessCoeff :: QuantityDict
inputs :: [QuantityDict]
inputs :: [QuantityDict]
inputs = [QuantityDict
qdSetPointTD, QuantityDict
qdDerivGain, QuantityDict
qdPropGain, QuantityDict
qdStepTime, QuantityDict
qdSimTime]
outputs :: [QuantityDict]
outputs :: [QuantityDict]
outputs = [QuantityDict
qdProcessVariableTD]
inputsUC :: [UncertQ]
inputsUC :: [UncertQ]
inputsUC
= [UncertQ
ipSetPtUnc, UncertQ
ipPropGainUnc, UncertQ
ipDerGainUnc, UncertQ
ipStepTimeUnc, UncertQ
ipSimTimeUnc]
inpConstrained :: [ConstrConcept]
inpConstrained :: [ConstrConcept]
inpConstrained
= [ConstrConcept
ipPropGain, ConstrConcept
ipDerivGain, ConstrConcept
ipSetPt, ConstrConcept
ipStepTime, ConstrConcept
ipSimTime, ConstrConcept
opProcessVariable]
ipPropGain, ipDerivGain, ipSetPt, ipStepTime, ipSimTime, opProcessVariable ::
ConstrConcept
ipSetPtUnc, ipPropGainUnc, ipDerGainUnc, ipStepTimeUnc, ipSimTimeUnc :: UncertQ
ipPropGain :: ConstrConcept
ipPropGain
= DefinedQuantityDict -> [ConstraintE] -> Expr -> ConstrConcept
forall c.
(Concept c, MayHaveUnit c, Quantity c) =>
c -> [ConstraintE] -> Expr -> ConstrConcept
constrained' (ConceptChunk -> Symbol -> Space -> DefinedQuantityDict
dqdNoUnit ConceptChunk
propGain Symbol
symKp Space
Real) [ConstraintE
gtZeroConstr] (Integer -> Expr
forall r. LiteralC r => Integer -> r
exactDbl Integer
20)
ipPropGainUnc :: UncertQ
ipPropGainUnc = ConstrConcept -> Uncertainty -> UncertQ
forall c.
(Quantity c, Constrained c, Concept c, HasReasVal c,
MayHaveUnit c) =>
c -> Uncertainty -> UncertQ
uq ConstrConcept
ipPropGain Uncertainty
defaultUncrt
qdPropGain :: QuantityDict
qdPropGain = ConstrConcept -> QuantityDict
forall q. (Quantity q, MayHaveUnit q) => q -> QuantityDict
qw ConstrConcept
ipPropGain
ipDerivGain :: ConstrConcept
ipDerivGain
= DefinedQuantityDict -> [ConstraintE] -> Expr -> ConstrConcept
forall c.
(Concept c, MayHaveUnit c, Quantity c) =>
c -> [ConstraintE] -> Expr -> ConstrConcept
constrained' (ConceptChunk -> Symbol -> Space -> DefinedQuantityDict
dqdNoUnit ConceptChunk
derGain Symbol
symKd Space
Real) [RealInterval Expr Expr -> ConstraintE
physRange (RealInterval Expr Expr -> ConstraintE)
-> RealInterval Expr Expr -> ConstraintE
forall a b. (a -> b) -> a -> b
$ (Inclusive, Expr) -> RealInterval Expr Expr
forall b a. (Inclusive, b) -> RealInterval a b
UpFrom (Inclusive
Inc, Integer -> Expr
forall r. LiteralC r => Integer -> r
exactDbl Integer
0)]
(Integer -> Expr
forall r. LiteralC r => Integer -> r
exactDbl Integer
1)
ipDerGainUnc :: UncertQ
ipDerGainUnc = ConstrConcept -> Uncertainty -> UncertQ
forall c.
(Quantity c, Constrained c, Concept c, HasReasVal c,
MayHaveUnit c) =>
c -> Uncertainty -> UncertQ
uq ConstrConcept
ipDerivGain Uncertainty
defaultUncrt
qdDerivGain :: QuantityDict
qdDerivGain = ConstrConcept -> QuantityDict
forall q. (Quantity q, MayHaveUnit q) => q -> QuantityDict
qw ConstrConcept
ipDerivGain
ipSetPt :: ConstrConcept
ipSetPt = DefinedQuantityDict -> [ConstraintE] -> Expr -> ConstrConcept
forall c.
(Concept c, MayHaveUnit c, Quantity c) =>
c -> [ConstraintE] -> Expr -> ConstrConcept
constrained' (ConceptChunk -> Symbol -> Space -> DefinedQuantityDict
dqdNoUnit ConceptChunk
setPoint Symbol
symYrT Space
Real) [ConstraintE
gtZeroConstr] (Integer -> Expr
forall r. LiteralC r => Integer -> r
exactDbl Integer
1)
ipSetPtUnc :: UncertQ
ipSetPtUnc = ConstrConcept -> Uncertainty -> UncertQ
forall c.
(Quantity c, Constrained c, Concept c, HasReasVal c,
MayHaveUnit c) =>
c -> Uncertainty -> UncertQ
uq ConstrConcept
ipSetPt Uncertainty
defaultUncrt
qdSetPointTD :: QuantityDict
qdSetPointTD = ConstrConcept -> QuantityDict
forall q. (Quantity q, MayHaveUnit q) => q -> QuantityDict
qw ConstrConcept
ipSetPt
ipStepTime :: ConstrConcept
ipStepTime = UnitalChunk -> [ConstraintE] -> Expr -> ConstrConcept
forall c.
(Concept c, MayHaveUnit c, Quantity c) =>
c -> [ConstraintE] -> Expr -> ConstrConcept
constrained' (ConceptChunk -> Symbol -> Space -> UnitDefn -> UnitalChunk
forall c u.
(Concept c, IsUnit u) =>
c -> Symbol -> Space -> u -> UnitalChunk
uc ConceptChunk
stepTime Symbol
symTStep Space
Real UnitDefn
second)
[RealInterval Expr Expr -> ConstraintE
physRange (RealInterval Expr Expr -> ConstraintE)
-> RealInterval Expr Expr -> ConstraintE
forall a b. (a -> b) -> a -> b
$ (Inclusive, Expr) -> (Inclusive, Expr) -> RealInterval Expr Expr
forall a b. (Inclusive, a) -> (Inclusive, b) -> RealInterval a b
Bounded (Inclusive
Inc, Integer -> Integer -> Expr
forall r. (ExprC r, LiteralC r) => Integer -> Integer -> r
frac Integer
1 Integer
1000) (Inclusive
Exc, ConstrConcept -> Expr
forall c. (HasUID c, HasSymbol c) => c -> Expr
forall r c. (ExprC r, HasUID c, HasSymbol c) => c -> r
sy ConstrConcept
ipSimTime)]
(Double -> Expr
forall r. LiteralC r => Double -> r
dbl Double
0.001)
ipStepTimeUnc :: UncertQ
ipStepTimeUnc = ConstrConcept -> Uncertainty -> UncertQ
forall c.
(Quantity c, Constrained c, Concept c, HasReasVal c,
MayHaveUnit c) =>
c -> Uncertainty -> UncertQ
uq ConstrConcept
ipStepTime Uncertainty
defaultUncrt
qdStepTime :: QuantityDict
qdStepTime = ConstrConcept -> QuantityDict
forall q. (Quantity q, MayHaveUnit q) => q -> QuantityDict
qw ConstrConcept
ipStepTime
ipSimTime :: ConstrConcept
ipSimTime
= UnitalChunk -> [ConstraintE] -> Expr -> ConstrConcept
forall c.
(Concept c, MayHaveUnit c, Quantity c) =>
c -> [ConstraintE] -> Expr -> ConstrConcept
constrained' (ConceptChunk -> Symbol -> Space -> UnitDefn -> UnitalChunk
forall c u.
(Concept c, IsUnit u) =>
c -> Symbol -> Space -> u -> UnitalChunk
uc ConceptChunk
simulationTime Symbol
symTSim Space
Real UnitDefn
second)
[RealInterval Expr Expr -> ConstraintE
physRange (RealInterval Expr Expr -> ConstraintE)
-> RealInterval Expr Expr -> ConstraintE
forall a b. (a -> b) -> a -> b
$ (Inclusive, Expr) -> (Inclusive, Expr) -> RealInterval Expr Expr
forall a b. (Inclusive, a) -> (Inclusive, b) -> RealInterval a b
Bounded (Inclusive
Inc, Integer -> Expr
forall r. LiteralC r => Integer -> r
exactDbl Integer
1) (Inclusive
Inc, Integer -> Expr
forall r. LiteralC r => Integer -> r
exactDbl Integer
60)]
(Integer -> Expr
forall r. LiteralC r => Integer -> r
exactDbl Integer
10)
ipSimTimeUnc :: UncertQ
ipSimTimeUnc = ConstrConcept -> Uncertainty -> UncertQ
forall c.
(Quantity c, Constrained c, Concept c, HasReasVal c,
MayHaveUnit c) =>
c -> Uncertainty -> UncertQ
uq ConstrConcept
ipSimTime Uncertainty
defaultUncrt
qdSimTime :: QuantityDict
qdSimTime = ConstrConcept -> QuantityDict
forall q. (Quantity q, MayHaveUnit q) => q -> QuantityDict
qw ConstrConcept
ipSimTime
odeAbsTolConst, odeRelTolConst :: ConstQDef
dqdAbsTol, dqdRelTol :: DefinedQuantityDict
pidConstants :: [ConstQDef]
pidConstants :: [ConstQDef]
pidConstants = [ConstQDef
odeAbsTolConst, ConstQDef
odeRelTolConst]
pidDqdConstants :: [DefinedQuantityDict]
pidDqdConstants :: [DefinedQuantityDict]
pidDqdConstants = [DefinedQuantityDict
dqdAbsTol, DefinedQuantityDict
dqdRelTol]
dqdAbsTol :: DefinedQuantityDict
dqdAbsTol = ConceptChunk -> Symbol -> Space -> DefinedQuantityDict
dqdNoUnit ConceptChunk
ccAbsTolerance Symbol
symAbsTol Space
Real
dqdRelTol :: DefinedQuantityDict
dqdRelTol = ConceptChunk -> Symbol -> Space -> DefinedQuantityDict
dqdNoUnit ConceptChunk
ccRelTolerance Symbol
symRelTol Space
Real
odeAbsTolConst :: ConstQDef
odeAbsTolConst = DefinedQuantityDict -> Literal -> ConstQDef
forall c e. (Quantity c, MayHaveUnit c) => c -> e -> QDefinition e
mkQuantDef DefinedQuantityDict
dqdAbsTol (Double -> Literal
forall r. LiteralC r => Double -> r
dbl Double
1.0e-10)
odeRelTolConst :: ConstQDef
odeRelTolConst = DefinedQuantityDict -> Literal -> ConstQDef
forall c e. (Quantity c, MayHaveUnit c) => c -> e -> QDefinition e
mkQuantDef DefinedQuantityDict
dqdRelTol (Double -> Literal
forall r. LiteralC r => Double -> r
dbl Double
1.0e-10)
opProcessVariable :: ConstrConcept
opProcessVariable
= DefinedQuantityDict -> [ConstraintE] -> Expr -> ConstrConcept
forall c.
(Concept c, MayHaveUnit c, Quantity c) =>
c -> [ConstraintE] -> Expr -> ConstrConcept
constrained' (ConceptChunk -> Symbol -> Space -> DefinedQuantityDict
dqdNoUnit ConceptChunk
processVariable Symbol
symYT (Space -> Space
Vect Space
Real))
[ConstraintE
gtZeroConstr]
(Integer -> Expr
forall r. LiteralC r => Integer -> r
exactDbl Integer
1)
qdProcessVariableTD :: QuantityDict
qdProcessVariableTD = ConstrConcept -> QuantityDict
forall q. (Quantity q, MayHaveUnit q) => q -> QuantityDict
qw ConstrConcept
opProcessVariable
qdSetPointFD :: QuantityDict
qdSetPointFD
= String -> NP -> Symbol -> Space -> QuantityDict
vc String
"qdSetPointFD" (ConceptChunk
setPoint ConceptChunk -> ConceptChunk -> NP
forall c d. (NamedIdea c, NamedIdea d) => c -> d -> NP
`inThe` ConceptChunk
ccFrequencyDomain) Symbol
symYrS Space
Real
qdProcessVariableFD :: QuantityDict
qdProcessVariableFD = String -> NP -> Symbol -> Space -> QuantityDict
vc String
"qdProcessVariableFD" (ConceptChunk
processVariable ConceptChunk -> ConceptChunk -> NP
forall c d. (NamedIdea c, NamedIdea d) => c -> d -> NP
`inThe` ConceptChunk
ccFrequencyDomain) Symbol
symYS Space
Real
qdProcessErrorTD :: QuantityDict
qdProcessErrorTD
= String -> NP -> Symbol -> Space -> QuantityDict
vc String
"qdProcessErrorTD"
(Sentence -> NP
nounPhraseSent (String -> Sentence
S String
"Process Error in the time domain"))
Symbol
symET
Space
Real
qdProcessErrorFD :: QuantityDict
qdProcessErrorFD = String -> NP -> Symbol -> Space -> QuantityDict
vc String
"qdProcessErrorFD" (ConceptChunk
processError ConceptChunk -> ConceptChunk -> NP
forall c d. (NamedIdea c, NamedIdea d) => c -> d -> NP
`inThe` ConceptChunk
ccFrequencyDomain) Symbol
symES Space
Real
qdPropControlFD :: QuantityDict
qdPropControlFD = String -> NP -> Symbol -> Space -> QuantityDict
vc String
"qdPropControlFD" (ConceptChunk
propControl ConceptChunk -> ConceptChunk -> NP
forall c d. (NamedIdea c, NamedIdea d) => c -> d -> NP
`inThe` ConceptChunk
ccFrequencyDomain) Symbol
symPS Space
Real
qdDerivativeControlFD :: QuantityDict
qdDerivativeControlFD = String -> NP -> Symbol -> Space -> QuantityDict
vc String
"qdDerivativeControlFD" (ConceptChunk
derControl ConceptChunk -> ConceptChunk -> NP
forall c d. (NamedIdea c, NamedIdea d) => c -> d -> NP
`inThe` ConceptChunk
ccFrequencyDomain) Symbol
symDS Space
Real
qdTransferFunctionFD :: QuantityDict
qdTransferFunctionFD = String -> NP -> Symbol -> Space -> QuantityDict
vc String
"qdTransferFunctionFD" (ConceptChunk
ccTransferFxn ConceptChunk -> ConceptChunk -> NP
forall c d. (NamedIdea c, NamedIdea d) => c -> d -> NP
`inThe` ConceptChunk
ccFrequencyDomain) Symbol
symHS Space
Real
qdCtrlVarTD :: QuantityDict
qdCtrlVarTD
= String -> NP -> Symbol -> Space -> QuantityDict
vc String
"qdCtrlVarTD" (Sentence -> NP
nounPhraseSent (String -> Sentence
S String
"Control Variable in the time domain"))
Symbol
symCT
Space
Real
qdCtrlVarFD :: QuantityDict
qdCtrlVarFD = String -> NP -> Symbol -> Space -> QuantityDict
vc String
"qdCtrlVarFD" (ConceptChunk
controlVariable ConceptChunk -> ConceptChunk -> NP
forall c d. (NamedIdea c, NamedIdea d) => c -> d -> NP
`inThe` ConceptChunk
ccFrequencyDomain) Symbol
symCS Space
Real
qdLaplaceTransform :: QuantityDict
qdLaplaceTransform
= String -> NP -> Symbol -> Space -> QuantityDict
vc String
"qLaplaceTransform"
(Sentence -> NP
nounPhraseSent (String -> Sentence
S String
"Laplace Transform of a function"))
Symbol
symFS
Space
Real
qdFreqDomain :: QuantityDict
qdFreqDomain
= String -> NP -> Symbol -> Space -> QuantityDict
vc String
"qFreqDomain" (Sentence -> NP
nounPhraseSent (String -> Sentence
S String
"Complex frequency-domain parameter"))
Symbol
syms
Space
Real
qdFxnTDomain :: QuantityDict
qdFxnTDomain
= String -> NP -> Symbol -> Space -> QuantityDict
vc String
"qdFxnTDomain" (Sentence -> NP
nounPhraseSent (String -> Sentence
S String
"Function in the time domain")) Symbol
symFt
Space
Real
qdInvLaplaceTransform :: QuantityDict
qdInvLaplaceTransform
= String -> NP -> Symbol -> Space -> QuantityDict
vc String
"qInvLaplaceTransform"
(Sentence -> NP
nounPhraseSent (String -> Sentence
S String
"Inverse Laplace Transform of a function"))
Symbol
syminvLaplace
Space
Real
qdDampingCoeff :: QuantityDict
qdDampingCoeff
= String -> NP -> Symbol -> Space -> QuantityDict
vc String
"qdDampingCoeff" (Sentence -> NP
nounPhraseSent (String -> Sentence
S String
"Damping coefficient of the spring"))
Symbol
symDampingCoeff
Space
Real
qdStiffnessCoeff :: QuantityDict
qdStiffnessCoeff
= String
-> NP
-> Symbol
-> Space
-> Maybe UnitDefn
-> Maybe String
-> QuantityDict
mkQuant String
"qdTimeConst"
(Sentence -> NP
nounPhraseSent (String -> Sentence
S String
"Stiffness coefficient of the spring"))
Symbol
symStifnessCoeff
Space
Real
(UnitDefn -> Maybe UnitDefn
forall a. a -> Maybe a
Just UnitDefn
second)
Maybe String
forall a. Maybe a
Nothing