module Drasil.PDController.Changes where

import Data.Drasil.Concepts.Documentation (likeChgDom)
import Data.Drasil.Concepts.PhysicalProperties (mass)

import Drasil.PDController.Assumptions
import Drasil.PDController.Concepts
import Language.Drasil
import Language.Drasil.Chunk.Concept.NamedCombinators

likelyChgs :: [ConceptInstance]
likelyChgs :: [ConceptInstance]
likelyChgs = [ConceptInstance
likeChgPP]

likeChgPP :: ConceptInstance
likeChgPP :: ConceptInstance
likeChgPP = forall c.
Concept c =>
String -> Sentence -> String -> c -> ConceptInstance
cic String
"likeChgPP" Sentence
likeChgPPDesc String
"DC Gain and Time Constant" ConceptChunk
likeChgDom

likeChgPPDesc :: Sentence
likeChgPPDesc :: Sentence
likeChgPPDesc
  = [Sentence] -> Sentence
foldlSent
      [forall n. NounPhrase n => n -> Sentence
atStartNP (forall t. NamedIdea t => t -> NP
the ConceptChunk
mass) Sentence -> Sentence -> Sentence
`sC` forall n. NounPhrase n => n -> Sentence
phraseNP (ConceptChunk
ccDampingCoeff forall c d. (NamedIdea c, NamedIdea d) => c -> d -> NP
`andThe` ConceptChunk
ccStiffCoeff),
       String -> Sentence
S String
"may be changed to be supplied by the user", 
       forall r. (Referable r, HasShortName r) => [r] -> Sentence
fromSources [ConceptInstance
aMass, ConceptInstance
aDampingCoeff, ConceptInstance
aStiffnessCoeff]]