{-# LANGUAGE PostfixOperators #-}
module Drasil.PDController.DataDefs where
import Drasil.PDController.Concepts
import Drasil.PDController.Assumptions
import Drasil.PDController.Unitals
import Drasil.PDController.References
import Drasil.PDController.TModel
import Data.Drasil.Concepts.Math (equation)
import Language.Drasil
import Theory.Drasil (DataDefinition, ddE)
import Language.Drasil.Chunk.Concept.NamedCombinators
import qualified Language.Drasil.Sentence.Combinators as S
dataDefinitions :: [DataDefinition]
dataDefinitions :: [DataDefinition]
dataDefinitions = [DataDefinition
ddErrSig, DataDefinition
ddPropCtrl, DataDefinition
ddDerivCtrl, DataDefinition
ddCtrlVar]
ddErrSig :: DataDefinition
ddErrSig :: DataDefinition
ddErrSig
= SimpleQDef
-> [DecRef]
-> Maybe Derivation
-> String
-> [Sentence]
-> DataDefinition
ddE SimpleQDef
ddErrSigDefn [Citation -> DecRef
forall r.
(HasUID r, HasRefAddress r, HasShortName r) =>
r -> DecRef
dRef Citation
johnson2008] Maybe Derivation
forall a. Maybe a
Nothing String
"ddProcessError"
[Sentence
ddErrSigNote]
ddErrSigDefn :: SimpleQDef
ddErrSigDefn :: SimpleQDef
ddErrSigDefn = QuantityDict -> Expr -> SimpleQDef
forall c e. (Quantity c, MayHaveUnit c) => c -> e -> QDefinition e
mkQuantDef QuantityDict
qdProcessErrorFD Expr
ddErrSigEqn
ddErrSigEqn :: Expr
ddErrSigEqn :: Expr
ddErrSigEqn = QuantityDict -> Expr
forall c. (HasUID c, HasSymbol c) => c -> Expr
forall r c. (ExprC r, HasUID c, HasSymbol c) => c -> r
sy QuantityDict
qdSetPointFD Expr -> Expr -> Expr
forall r. ExprC r => r -> r -> r
$- QuantityDict -> Expr
forall c. (HasUID c, HasSymbol c) => c -> Expr
forall r c. (ExprC r, HasUID c, HasSymbol c) => c -> r
sy QuantityDict
qdProcessVariableFD
ddErrSigNote :: Sentence
ddErrSigNote :: Sentence
ddErrSigNote
= [Sentence] -> Sentence
foldlSent
[NP -> Sentence
forall n. NounPhrase n => n -> Sentence
atStartNP (ConceptChunk -> NP
forall t. NamedIdea t => t -> NP
the ConceptChunk
processError), String -> Sentence
S String
"is the difference between the Set-Point and" Sentence -> Sentence -> Sentence
+:+.
ConceptChunk -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase ConceptChunk
processVariable,
NP -> Sentence
forall n. NounPhrase n => n -> Sentence
atStartNP (ConceptChunk -> NP
forall t. NamedIdea t => t -> NP
the ConceptChunk
equation), String -> Sentence
S String
"is converted" Sentence -> Sentence -> Sentence
`S.toThe` ConceptChunk -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase ConceptChunk
ccFrequencyDomain,
String -> Sentence
S String
"by applying the", ConceptChunk -> Sentence
forall n. NamedIdea n => n -> Sentence
atStart ConceptChunk
ccLaplaceTransform Sentence -> Sentence -> Sentence
+:+. TheoryModel -> Sentence
forall r. (Referable r, HasShortName r) => r -> Sentence
fromSource TheoryModel
tmLaplace,
NP -> Sentence
forall n. NounPhrase n => n -> Sentence
atStartNP (ConceptChunk -> NP
forall t. NamedIdea t => t -> NP
the ConceptChunk
setPoint), String -> Sentence
S String
"is assumed to be constant throughout the",
ConceptChunk -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase ConceptChunk
simulation Sentence -> Sentence -> Sentence
+:+. ConceptInstance -> Sentence
forall r. (Referable r, HasShortName r) => r -> Sentence
fromSource ConceptInstance
aSP,
String -> Sentence
S String
"The initial value" Sentence -> Sentence -> Sentence
`S.ofThe` ConceptChunk -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase ConceptChunk
processVariable, String -> Sentence
S String
"is assumed",
String -> Sentence
S String
"to be zero", ConceptInstance -> Sentence
forall r. (Referable r, HasShortName r) => r -> Sentence
fromSource ConceptInstance
aInitialValue]
ddPropCtrl :: DataDefinition
ddPropCtrl :: DataDefinition
ddPropCtrl
= SimpleQDef
-> [DecRef]
-> Maybe Derivation
-> String
-> [Sentence]
-> DataDefinition
ddE SimpleQDef
ddPropCtrlDefn [Citation -> DecRef
forall r.
(HasUID r, HasRefAddress r, HasShortName r) =>
r -> DecRef
dRef Citation
johnson2008] Maybe Derivation
forall a. Maybe a
Nothing String
"ddPropCtrl"
[Sentence
ddPropCtrlNote]
ddPropCtrlDefn :: SimpleQDef
ddPropCtrlDefn :: SimpleQDef
ddPropCtrlDefn = QuantityDict -> Expr -> SimpleQDef
forall c e. (Quantity c, MayHaveUnit c) => c -> e -> QDefinition e
mkQuantDef QuantityDict
qdPropControlFD Expr
ddPropCtrlEqn
ddPropCtrlEqn :: Expr
ddPropCtrlEqn :: Expr
ddPropCtrlEqn = QuantityDict -> Expr
forall c. (HasUID c, HasSymbol c) => c -> Expr
forall r c. (ExprC r, HasUID c, HasSymbol c) => c -> r
sy QuantityDict
qdPropGain Expr -> Expr -> Expr
forall r. ExprC r => r -> r -> r
$* QuantityDict -> Expr
forall c. (HasUID c, HasSymbol c) => c -> Expr
forall r c. (ExprC r, HasUID c, HasSymbol c) => c -> r
sy QuantityDict
qdProcessErrorFD
ddPropCtrlNote :: Sentence
ddPropCtrlNote :: Sentence
ddPropCtrlNote
= [Sentence] -> Sentence
foldlSent
[String -> Sentence
S String
"The Proportional Controller" Sentence -> Sentence -> Sentence
`S.is` String -> Sentence
S String
"the product" Sentence -> Sentence -> Sentence
`S.ofThe` NP -> Sentence
forall n. NounPhrase n => n -> Sentence
phraseNP (ConceptChunk
propGain ConceptChunk -> ConceptChunk -> NP
forall c d. (NamedIdea c, NamedIdea d) => c -> d -> NP
`andThe`
ConceptChunk
processError) Sentence -> Sentence -> Sentence
+:+. DataDefinition -> Sentence
forall r. (Referable r, HasShortName r) => r -> Sentence
fromSource DataDefinition
ddErrSig,
NP -> Sentence
forall n. NounPhrase n => n -> Sentence
atStartNP (ConceptChunk -> NP
forall t. NamedIdea t => t -> NP
the ConceptChunk
equation), String -> Sentence
S String
"is converted" Sentence -> Sentence -> Sentence
`S.toThe` ConceptChunk -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase ConceptChunk
ccFrequencyDomain,
String -> Sentence
S String
"by applying the", ConceptChunk -> Sentence
forall n. NamedIdea n => n -> Sentence
atStart ConceptChunk
ccLaplaceTransform, TheoryModel -> Sentence
forall r. (Referable r, HasShortName r) => r -> Sentence
fromSource TheoryModel
tmLaplace]
ddDerivCtrl :: DataDefinition
ddDerivCtrl :: DataDefinition
ddDerivCtrl
= SimpleQDef
-> [DecRef]
-> Maybe Derivation
-> String
-> [Sentence]
-> DataDefinition
ddE SimpleQDef
ddDerivCtrlDefn [Citation -> DecRef
forall r.
(HasUID r, HasRefAddress r, HasShortName r) =>
r -> DecRef
dRef Citation
johnson2008] Maybe Derivation
forall a. Maybe a
Nothing String
"ddDerivCtrl"
[Sentence
ddDerivCtrlNote]
ddDerivCtrlDefn :: SimpleQDef
ddDerivCtrlDefn :: SimpleQDef
ddDerivCtrlDefn = QuantityDict -> Expr -> SimpleQDef
forall c e. (Quantity c, MayHaveUnit c) => c -> e -> QDefinition e
mkQuantDef QuantityDict
qdDerivativeControlFD Expr
ddDerivCtrlEqn
ddDerivCtrlEqn :: Expr
ddDerivCtrlEqn :: Expr
ddDerivCtrlEqn
= QuantityDict -> Expr
forall c. (HasUID c, HasSymbol c) => c -> Expr
forall r c. (ExprC r, HasUID c, HasSymbol c) => c -> r
sy QuantityDict
qdDerivGain Expr -> Expr -> Expr
forall r. ExprC r => r -> r -> r
$* QuantityDict -> Expr
forall c. (HasUID c, HasSymbol c) => c -> Expr
forall r c. (ExprC r, HasUID c, HasSymbol c) => c -> r
sy QuantityDict
qdProcessErrorFD Expr -> Expr -> Expr
forall r. ExprC r => r -> r -> r
$* QuantityDict -> Expr
forall c. (HasUID c, HasSymbol c) => c -> Expr
forall r c. (ExprC r, HasUID c, HasSymbol c) => c -> r
sy QuantityDict
qdFreqDomain
ddDerivCtrlNote :: Sentence
ddDerivCtrlNote :: Sentence
ddDerivCtrlNote
= [Sentence] -> Sentence
foldlSent
[String -> Sentence
S String
"The Derivative Controller" Sentence -> Sentence -> Sentence
`S.is` String -> Sentence
S String
"the product" Sentence -> Sentence -> Sentence
`S.ofThe` ConceptChunk -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase ConceptChunk
derGain
Sentence -> Sentence -> Sentence
`S.andThe` String -> Sentence
S String
"differential" Sentence -> Sentence -> Sentence
`S.ofThe` ConceptChunk -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase ConceptChunk
processError Sentence -> Sentence -> Sentence
+:+. DataDefinition -> Sentence
forall r. (Referable r, HasShortName r) => r -> Sentence
fromSource DataDefinition
ddErrSig,
NP -> Sentence
forall n. NounPhrase n => n -> Sentence
atStartNP (ConceptChunk -> NP
forall t. NamedIdea t => t -> NP
the ConceptChunk
equation), String -> Sentence
S String
"is converted" Sentence -> Sentence -> Sentence
`S.toThe` ConceptChunk -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase ConceptChunk
ccFrequencyDomain,
String -> Sentence
S String
"by applying the", ConceptChunk -> Sentence
forall n. NamedIdea n => n -> Sentence
atStart ConceptChunk
ccLaplaceTransform Sentence -> Sentence -> Sentence
+:+. TheoryModel -> Sentence
forall r. (Referable r, HasShortName r) => r -> Sentence
fromSource TheoryModel
tmLaplace,
String -> Sentence
S String
"A pure form" Sentence -> Sentence -> Sentence
`S.ofThe` String -> Sentence
S String
"Derivative controller" Sentence -> Sentence -> Sentence
`S.is` String -> Sentence
S String
"used in this",
String -> Sentence
S String
"application", ConceptInstance -> Sentence
forall r. (Referable r, HasShortName r) => r -> Sentence
fromSource ConceptInstance
aUnfilteredDerivative]
ddCtrlVar :: DataDefinition
ddCtrlVar :: DataDefinition
ddCtrlVar
= SimpleQDef
-> [DecRef]
-> Maybe Derivation
-> String
-> [Sentence]
-> DataDefinition
ddE SimpleQDef
ddCtrlVarDefn [Citation -> DecRef
forall r.
(HasUID r, HasRefAddress r, HasShortName r) =>
r -> DecRef
dRef Citation
johnson2008] Maybe Derivation
forall a. Maybe a
Nothing String
"ddCtrlVar" [Sentence
ddCtrlNote]
ddCtrlVarDefn :: SimpleQDef
ddCtrlVarDefn :: SimpleQDef
ddCtrlVarDefn = QuantityDict -> Expr -> SimpleQDef
forall c e. (Quantity c, MayHaveUnit c) => c -> e -> QDefinition e
mkQuantDef QuantityDict
qdCtrlVarFD Expr
ddCtrlEqn
ddCtrlEqn :: Expr
ddCtrlEqn :: Expr
ddCtrlEqn
= QuantityDict -> Expr
forall c. (HasUID c, HasSymbol c) => c -> Expr
forall r c. (ExprC r, HasUID c, HasSymbol c) => c -> r
sy QuantityDict
qdProcessErrorFD Expr -> Expr -> Expr
forall r. ExprC r => r -> r -> r
$* (QuantityDict -> Expr
forall c. (HasUID c, HasSymbol c) => c -> Expr
forall r c. (ExprC r, HasUID c, HasSymbol c) => c -> r
sy QuantityDict
qdPropGain Expr -> Expr -> Expr
forall r. ExprC r => r -> r -> r
$+
(QuantityDict -> Expr
forall c. (HasUID c, HasSymbol c) => c -> Expr
forall r c. (ExprC r, HasUID c, HasSymbol c) => c -> r
sy QuantityDict
qdDerivGain Expr -> Expr -> Expr
forall r. ExprC r => r -> r -> r
$* QuantityDict -> Expr
forall c. (HasUID c, HasSymbol c) => c -> Expr
forall r c. (ExprC r, HasUID c, HasSymbol c) => c -> r
sy QuantityDict
qdFreqDomain))
ddCtrlNote :: Sentence
ddCtrlNote :: Sentence
ddCtrlNote
= [Sentence] -> Sentence
foldlSent
[NP -> Sentence
forall n. NounPhrase n => n -> Sentence
atStartNP (ConceptChunk -> NP
forall t. NamedIdea t => t -> NP
the ConceptChunk
controlVariable) Sentence -> Sentence -> Sentence
+:+. (String -> Sentence
S String
"is the output" Sentence -> Sentence -> Sentence
`S.ofThe` String -> Sentence
S String
"controller"),
String -> Sentence
S String
"In this case" Sentence -> Sentence -> Sentence
`sC` String -> Sentence
S String
"it is the sum" Sentence -> Sentence -> Sentence
`S.ofThe` String -> Sentence
S String
"Proportional", DataDefinition -> Sentence
forall r. (Referable r, HasShortName r) => r -> Sentence
fromSource DataDefinition
ddPropCtrl,
String -> Sentence
S String
"and Derivative", DataDefinition -> Sentence
forall r. (Referable r, HasShortName r) => r -> Sentence
fromSource DataDefinition
ddDerivCtrl Sentence -> Sentence -> Sentence
+:+.
String -> Sentence
S String
"controllers",
String -> Sentence
S String
"The parallel", ConceptInstance -> Sentence
forall r. (Referable r, HasShortName r) => r -> Sentence
fromSource ConceptInstance
aParallelEq,
String -> Sentence
S String
"and de-coupled", ConceptInstance -> Sentence
forall r. (Referable r, HasShortName r) => r -> Sentence
fromSource ConceptInstance
aDecoupled,
String -> Sentence
S String
"form of the PD equation" Sentence -> Sentence -> Sentence
`S.is` String -> Sentence
S String
"used in this document"]