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, symnegInf, symposInf, syminvLaplace, symKd, symKp, symYT, symYS, symYrT, symYrS, symET, symES, symPS, symDS, symHS, symCT, symCS, symTStep, symTSim, symAbsTol, symRelTol, symDampingCoeff, symStifnessCoeff :: Symbol symnegInf :: Symbol symnegInf = String -> Symbol variable "-∞" symposInf :: Symbol symposInf = String -> Symbol variable "∞" symFS :: Symbol symFS = Symbol -> Symbol -> Symbol sub (String -> Symbol variable "F") (Symbol -> Symbol) -> Symbol -> Symbol forall a b. (a -> b) -> a -> b $ String -> Symbol label "s" syminvLaplace :: Symbol syminvLaplace = String -> Symbol variable "L⁻¹[F(s)]" syms :: Symbol syms = String -> Symbol variable "s" symFt :: Symbol symFt = Symbol -> Symbol -> Symbol sub (String -> Symbol variable "f") (Symbol -> Symbol) -> Symbol -> Symbol forall a b. (a -> b) -> a -> b $ String -> Symbol label "t" symKd :: Symbol symKd = Symbol -> Symbol -> Symbol sub (String -> Symbol variable "K") (Symbol -> Symbol) -> Symbol -> Symbol forall a b. (a -> b) -> a -> b $ String -> Symbol label "d" symKp :: Symbol symKp = Symbol -> Symbol -> Symbol sub (String -> Symbol variable "K") (Symbol -> Symbol) -> Symbol -> Symbol forall a b. (a -> b) -> a -> b $ String -> Symbol label "p" symYrT :: Symbol symYrT = Symbol -> Symbol -> Symbol sub (String -> Symbol variable "r") (Symbol -> Symbol) -> Symbol -> Symbol forall a b. (a -> b) -> a -> b $ String -> Symbol label "t" symYrS :: Symbol symYrS = Symbol -> Symbol -> Symbol sub (String -> Symbol variable "R") (Symbol -> Symbol) -> Symbol -> Symbol forall a b. (a -> b) -> a -> b $ String -> Symbol label "s" symYT :: Symbol symYT = Symbol -> Symbol -> Symbol sub (String -> Symbol variable "y") (Symbol -> Symbol) -> Symbol -> Symbol forall a b. (a -> b) -> a -> b $ String -> Symbol label "t" symYS :: Symbol symYS = Symbol -> Symbol -> Symbol sub (String -> Symbol variable "Y") (Symbol -> Symbol) -> Symbol -> Symbol forall a b. (a -> b) -> a -> b $ String -> Symbol label "s" symET :: Symbol symET = Symbol -> Symbol -> Symbol sub (String -> Symbol variable "e") (Symbol -> Symbol) -> Symbol -> Symbol forall a b. (a -> b) -> a -> b $ String -> Symbol label "t" symES :: Symbol symES = Symbol -> Symbol -> Symbol sub (String -> Symbol variable "E") (Symbol -> Symbol) -> Symbol -> Symbol forall a b. (a -> b) -> a -> b $ String -> Symbol label "s" symPS :: Symbol symPS = Symbol -> Symbol -> Symbol sub (String -> Symbol variable "P") (Symbol -> Symbol) -> Symbol -> Symbol forall a b. (a -> b) -> a -> b $ String -> Symbol label "s" symDS :: Symbol symDS = Symbol -> Symbol -> Symbol sub (String -> Symbol variable "D") (Symbol -> Symbol) -> Symbol -> Symbol forall a b. (a -> b) -> a -> b $ String -> Symbol label "s" symHS :: Symbol symHS = Symbol -> Symbol -> Symbol sub (String -> Symbol variable "H") (Symbol -> Symbol) -> Symbol -> Symbol forall a b. (a -> b) -> a -> b $ String -> Symbol label "s" symCT :: Symbol symCT = Symbol -> Symbol -> Symbol sub (String -> Symbol variable "c") (Symbol -> Symbol) -> Symbol -> Symbol forall a b. (a -> b) -> a -> b $ String -> Symbol label "t" symCS :: Symbol symCS = Symbol -> Symbol -> Symbol sub (String -> Symbol variable "C") (Symbol -> Symbol) -> Symbol -> Symbol forall a b. (a -> b) -> a -> b $ String -> Symbol label "s" symTStep :: Symbol symTStep = Symbol -> Symbol -> Symbol sub (String -> Symbol variable "t") (Symbol -> Symbol) -> Symbol -> Symbol forall a b. (a -> b) -> a -> b $ String -> Symbol label "step" symTSim :: Symbol symTSim = Symbol -> Symbol -> Symbol sub (String -> Symbol variable "t") (Symbol -> Symbol) -> Symbol -> Symbol forall a b. (a -> b) -> a -> b $ String -> Symbol label "sim" symAbsTol :: Symbol symAbsTol = String -> Symbol variable "AbsTol" symRelTol :: Symbol symRelTol = String -> Symbol variable "RelTol" symDampingCoeff :: Symbol symDampingCoeff = String -> Symbol variable "c" symStifnessCoeff :: Symbol symStifnessCoeff = String -> Symbol variable "k" symbols :: [QuantityDict] symbols :: [QuantityDict] symbols = [QuantityDict qdLaplaceTransform, QuantityDict qdFreqDomain, QuantityDict qdFxnTDomain, QuantityDict qdNegInf, QuantityDict qdPosInf, 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, qdNegInf, qdPosInf, 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 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 physc (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 0)] (Integer -> Expr forall r. LiteralC r => Integer -> r exactDbl 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 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 ucs' ConceptChunk stepTime Symbol symTStep Space Real UnitDefn second) [RealInterval Expr Expr -> ConstraintE physc (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 1 100) (Inclusive Exc, ConstrConcept -> Expr forall r c. (ExprC r, HasUID c, HasSymbol c) => c -> r sy ConstrConcept ipSimTime)] (Double -> Expr forall r. LiteralC r => Double -> r dbl 0.01) 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 ucs' ConceptChunk simulationTime Symbol symTSim Space Real UnitDefn second) [RealInterval Expr Expr -> ConstraintE physc (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 1) (Inclusive Inc, Integer -> Expr forall r. LiteralC r => Integer -> r exactDbl 60)] (Integer -> Expr forall r. LiteralC r => Integer -> r exactDbl 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 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 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 Rational)) [ConstraintE gtZeroConstr] (Integer -> Expr forall r. LiteralC r => Integer -> r exactDbl 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 "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 "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 "qdProcessErrorTD" (Sentence -> NP nounPhraseSent (String -> Sentence S "Process Error in the time domain")) Symbol symET Space Real qdProcessErrorFD :: QuantityDict qdProcessErrorFD = String -> NP -> Symbol -> Space -> QuantityDict vc "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 "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 "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 "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 "qdCtrlVarTD" (Sentence -> NP nounPhraseSent (String -> Sentence S "Control Variable in the time domain")) Symbol symCT Space Real qdCtrlVarFD :: QuantityDict qdCtrlVarFD = String -> NP -> Symbol -> Space -> QuantityDict vc "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 "qLaplaceTransform" (Sentence -> NP nounPhraseSent (String -> Sentence S "Laplace Transform of a function")) Symbol symFS Space Real qdFreqDomain :: QuantityDict qdFreqDomain = String -> NP -> Symbol -> Space -> QuantityDict vc "qFreqDomain" (Sentence -> NP nounPhraseSent (String -> Sentence S "Complex frequency-domain parameter")) Symbol syms Space Real qdFxnTDomain :: QuantityDict qdFxnTDomain = String -> NP -> Symbol -> Space -> QuantityDict vc "qdFxnTDomain" (Sentence -> NP nounPhraseSent (String -> Sentence S "Function in the time domain")) Symbol symFt Space Real qdNegInf :: QuantityDict qdNegInf = String -> NP -> Symbol -> Space -> QuantityDict vc "qdNegInf" (Sentence -> NP nounPhraseSent (String -> Sentence S "Negative Infinity")) Symbol symnegInf Space Real qdPosInf :: QuantityDict qdPosInf = String -> NP -> Symbol -> Space -> QuantityDict vc "qdPosInf" (Sentence -> NP nounPhraseSent (String -> Sentence S "Infinity")) Symbol symposInf Space Real qdInvLaplaceTransform :: QuantityDict qdInvLaplaceTransform = String -> NP -> Symbol -> Space -> QuantityDict vc "qInvLaplaceTransform" (Sentence -> NP nounPhraseSent (String -> Sentence S "Inverse Laplace Transform of a function")) Symbol syminvLaplace Space Real qdDampingCoeff :: QuantityDict qdDampingCoeff = String -> NP -> Symbol -> Space -> QuantityDict vc "qdDampingCoeff" (Sentence -> NP nounPhraseSent (String -> Sentence S "Damping coefficient of the spring")) Symbol symDampingCoeff Space Real qdStiffnessCoeff :: QuantityDict qdStiffnessCoeff = String -> NP -> Symbol -> Space -> Maybe UnitDefn -> Maybe String -> QuantityDict mkQuant "qdTimeConst" (Sentence -> NP nounPhraseSent (String -> Sentence S "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