module Drasil.PDController.Assumptions where

import Data.Drasil.Concepts.Documentation (assumpDom)

import Data.Drasil.Concepts.PhysicalProperties (mass)
import Data.Drasil.SI_Units (kilogram)
import Drasil.PDController.Concepts
import Language.Drasil
import Language.Drasil.Chunk.Concept.NamedCombinators
import qualified Language.Drasil.Sentence.Combinators as S

assumptions :: [ConceptInstance]
assumptions :: [ConceptInstance]
assumptions
  = [ConceptInstance
aPwrPlant, ConceptInstance
aDecoupled, ConceptInstance
aSP, ConceptInstance
aExtDisturb, ConceptInstance
aInitialValue, ConceptInstance
aParallelEq,
     ConceptInstance
aUnfilteredDerivative, ConceptInstance
apwrPlantTxFnx, ConceptInstance
aMass, ConceptInstance
aDampingCoeff,
     ConceptInstance
aStiffnessCoeff]

aPwrPlant, aDecoupled, aSP, aExtDisturb, aInitialValue, aParallelEq,
           aUnfilteredDerivative, apwrPlantTxFnx, aMass, aDampingCoeff,
           aStiffnessCoeff :: ConceptInstance

aPwrPlant :: ConceptInstance
aPwrPlant = forall c.
Concept c =>
String -> Sentence -> String -> c -> ConceptInstance
cic String
"pwrPlant" Sentence
pwrPlantDesc String
"Power plant" ConceptChunk
assumpDom

aDecoupled :: ConceptInstance
aDecoupled = forall c.
Concept c =>
String -> Sentence -> String -> c -> ConceptInstance
cic String
"decoupled" Sentence
aDecoupledDesc String
"Decoupled equation" ConceptChunk
assumpDom

aSP :: ConceptInstance
aSP = forall c.
Concept c =>
String -> Sentence -> String -> c -> ConceptInstance
cic String
"setPoint" Sentence
aSPDesc String
"Set-Point" ConceptChunk
assumpDom

aExtDisturb :: ConceptInstance
aExtDisturb
  = forall c.
Concept c =>
String -> Sentence -> String -> c -> ConceptInstance
cic String
"externalDisturb" Sentence
aExtDisturbDesc String
"External disturbance" ConceptChunk
assumpDom

aInitialValue :: ConceptInstance
aInitialValue = forall c.
Concept c =>
String -> Sentence -> String -> c -> ConceptInstance
cic String
"initialValue" Sentence
aInitialValueDesc String
"Initial Value" ConceptChunk
assumpDom

aParallelEq :: ConceptInstance
aParallelEq = forall c.
Concept c =>
String -> Sentence -> String -> c -> ConceptInstance
cic String
"parallelEq" Sentence
aParallelEqDesc String
"Parallel Equation" ConceptChunk
assumpDom

apwrPlantTxFnx :: ConceptInstance
apwrPlantTxFnx
  = forall c.
Concept c =>
String -> Sentence -> String -> c -> ConceptInstance
cic String
"pwrPlantTxFnx" Sentence
apwrPlantTxFnxDesc String
"Transfer Function" ConceptChunk
assumpDom

aUnfilteredDerivative :: ConceptInstance
aUnfilteredDerivative
  = forall c.
Concept c =>
String -> Sentence -> String -> c -> ConceptInstance
cic String
"unfilteredDerivative" Sentence
aUnfilteredDerivativeDesc String
"Unfiltered Derivative"
      ConceptChunk
assumpDom

aMass :: ConceptInstance
aMass = forall c.
Concept c =>
String -> Sentence -> String -> c -> ConceptInstance
cic String
"massSpring" Sentence
aMassDesc String
"Spring Mass" ConceptChunk
assumpDom

aDampingCoeff :: ConceptInstance
aDampingCoeff
  = forall c.
Concept c =>
String -> Sentence -> String -> c -> ConceptInstance
cic String
"dampingCoeffSpring" Sentence
aDampingCoeffDesc String
"Spring Damping Coefficient"
      ConceptChunk
assumpDom

aStiffnessCoeff :: ConceptInstance
aStiffnessCoeff
  = forall c.
Concept c =>
String -> Sentence -> String -> c -> ConceptInstance
cic String
"stiffnessCoeffSpring" Sentence
aStiffnessCoeffDesc String
"Spring Stiffness Coefficient"
      ConceptChunk
assumpDom

pwrPlantDesc, aDecoupledDesc, aSPDesc, aExtDisturbDesc, aManualTuningDesc,
              aInitialValueDesc, aParallelEqDesc, apwrPlantTxFnxDesc,
              aUnfilteredDerivativeDesc, aMassDesc, aDampingCoeffDesc,
              aStiffnessCoeffDesc :: Sentence
pwrPlantDesc :: Sentence
pwrPlantDesc
  = [Sentence] -> Sentence
foldlSent
      [forall n. NounPhrase n => n -> Sentence
atStartNP (forall t. NamedIdea t => t -> NP
the ConceptChunk
powerPlant) Sentence -> Sentence -> Sentence
`S.andThe` String -> Sentence
S String
"Sensor are coupled as a single unit"]

apwrPlantTxFnxDesc :: Sentence
apwrPlantTxFnxDesc
  = [Sentence] -> Sentence
foldlSent
      [String -> Sentence
S String
"The combined", forall n. NamedIdea n => n -> Sentence
phrase ConceptChunk
powerPlant Sentence -> Sentence -> Sentence
`S.and_` String -> Sentence
S String
"Sensor",
         Sentence -> Sentence
sParen (forall r.
(HasUID r, HasRefAddress r, HasShortName r) =>
r -> Sentence
refS ConceptInstance
aPwrPlant),        
         String -> Sentence
S String
"are characterized by a Second Order mass-spring-damper System"]

aDecoupledDesc :: Sentence
aDecoupledDesc
  = [Sentence] -> Sentence
foldlSent
      [String -> Sentence
S String
"The decoupled form of the", forall n. NamedIdea n => n -> Sentence
phrase ConceptChunk
pidC,
         String -> Sentence
S String
"equation used in this", forall n. NamedIdea n => n -> Sentence
phrase ConceptChunk
simulation]

aSPDesc :: Sentence
aSPDesc
  = [Sentence] -> Sentence
foldlSent
      [forall n. NounPhrase n => n -> Sentence
atStartNP (forall t. NamedIdea t => t -> NP
the ConceptChunk
setPoint), String -> Sentence
S String
"is constant throughout",
         forall n. NounPhrase n => n -> Sentence
phraseNP (forall t. NamedIdea t => t -> NP
the ConceptChunk
simulation)]

aExtDisturbDesc :: Sentence
aExtDisturbDesc
  = [Sentence] -> Sentence
foldlSent
      [String -> Sentence
S String
"There are no external disturbances to the", forall n. NamedIdea n => n -> Sentence
phrase ConceptChunk
powerPlant,
         String -> Sentence
S String
"during the", forall n. NamedIdea n => n -> Sentence
phrase ConceptChunk
simulation]

aManualTuningDesc :: Sentence
aManualTuningDesc
  = [Sentence] -> Sentence
foldlSent
      [String -> Sentence
S String
"This model will be used for manual tuning of the", forall n. NamedIdea n => n -> Sentence
phrase ConceptChunk
pidC]

aInitialValueDesc :: Sentence
aInitialValueDesc
  = [Sentence] -> Sentence
foldlSent
      [String -> Sentence
S String
"The initial value of the", forall n. NamedIdea n => n -> Sentence
phrase ConceptChunk
processVariable,
         String -> Sentence
S String
"is assumed to be zero"]

aParallelEqDesc :: Sentence
aParallelEqDesc
  = [Sentence] -> Sentence
foldlSent
      [String -> Sentence
S String
"The Parallel form of the equation is used for the", forall n. NamedIdea n => n -> Sentence
phrase ConceptChunk
pidC]

aUnfilteredDerivativeDesc :: Sentence
aUnfilteredDerivativeDesc
  = [Sentence] -> Sentence
foldlSent
      [String -> Sentence
S String
"A pure derivative function is used for this simulation;",
       String -> Sentence
S String
"there are no filters applied"]

aMassDesc :: Sentence
aMassDesc
  = [Sentence] -> Sentence
foldlSent
      [forall n. NounPhrase n => n -> Sentence
atStartNP (forall t. NamedIdea t => t -> NP
the ConceptChunk
mass),
       String -> Sentence
S String
"of the spring in the mass-spring-damper system",
       Sentence -> Sentence
sParen (forall r.
(HasUID r, HasRefAddress r, HasShortName r) =>
r -> Sentence
refS ConceptInstance
aPwrPlant),
       String -> Sentence
S String
"is assumed to be 1", 
       forall n. NamedIdea n => n -> Sentence
phrase UnitDefn
kilogram]

aDampingCoeffDesc :: Sentence
aDampingCoeffDesc
  = [Sentence] -> Sentence
foldlSent
      [forall n. NounPhrase n => n -> Sentence
atStartNP (forall t. NamedIdea t => t -> NP
the ConceptChunk
ccDampingCoeff),
       String -> Sentence
S String
"of the spring in the mass-spring-damper system",
       Sentence -> Sentence
sParen (forall r.
(HasUID r, HasRefAddress r, HasShortName r) =>
r -> Sentence
refS ConceptInstance
aPwrPlant), 
       String -> Sentence
S String
"is assumed to be 1"]

aStiffnessCoeffDesc :: Sentence
aStiffnessCoeffDesc
  = [Sentence] -> Sentence
foldlSent
      [forall n. NounPhrase n => n -> Sentence
atStartNP (forall t. NamedIdea t => t -> NP
the ConceptChunk
ccStiffCoeff),
       String -> Sentence
S String
"of the spring in the mass-spring-damper system",
       Sentence -> Sentence
sParen (forall r.
(HasUID r, HasRefAddress r, HasShortName r) =>
r -> Sentence
refS ConceptInstance
aPwrPlant), 
       String -> Sentence
S String
"is assumed to be 20"]