module Drasil.PDController.Concepts where

import Data.Drasil.Concepts.Documentation
       (assumption, goalStmt, physSyst, requirement, srs, typUnc)
import Data.Drasil.TheoryConcepts
import Language.Drasil

acronyms :: [CI]
acronyms :: [CI]
acronyms
  = [CI
assumption, CI
dataDefn, CI
genDefn, CI
goalStmt, CI
inModel, CI
physSyst, CI
requirement,
     CI
srs, CI
thModel, CI
typUnc, CI
pdControllerCI, CI
proportionalCI, CI
derivativeCI,
     CI
integralCI, CI
pidCI]

pidControllerSystem, pdControllerCI, proportionalCI, derivativeCI, integralCI,
                     pidCI :: CI

pidControllerSystem :: CI
pidControllerSystem = String -> NP -> String -> [IdeaDict] -> CI
commonIdeaWithDict "pdControllerApp" (String -> NP
pn "PD Controller")                    "PD Controller" []
pdControllerCI :: CI
pdControllerCI      = String -> NP -> String -> [IdeaDict] -> CI
commonIdeaWithDict "pdControllerCI"  (String -> NP
pn "Proportional Derivative")          "PD"            []
proportionalCI :: CI
proportionalCI      = String -> NP -> String -> [IdeaDict] -> CI
commonIdeaWithDict "proportionalCI"  (String -> NP
pn "Proportional")                     "P"             []
derivativeCI :: CI
derivativeCI        = String -> NP -> String -> [IdeaDict] -> CI
commonIdeaWithDict "derivativeCI"    (String -> NP
pn "Derivative")                       "D"             []
integralCI :: CI
integralCI          = String -> NP -> String -> [IdeaDict] -> CI
commonIdeaWithDict "integralCI"      (String -> NP
pn "Integral")                         "I"             []
pidCI :: CI
pidCI               = String -> NP -> String -> [IdeaDict] -> CI
commonIdeaWithDict "pidCI"           (String -> NP
pn "Proportional Integral Derivative") "PID"           []

pidC, pidCL, summingPt, powerPlant, secondOrderSystem, processError,
      simulationTime, processVariable, setPoint, propGain, derGain, 
      propControl, derControl, simulation,ccFrequencyDomain, ccTimeDomain,
      ccLaplaceTransform, controlVariable, stepTime, ccAbsTolerance, 
      ccRelTolerance, ccTransferFxn, ccDampingCoeff, ccStiffCoeff :: ConceptChunk
pidCL :: ConceptChunk
pidCL
  = String -> NP -> String -> ConceptChunk
dcc "pdCtrlLoop" (String -> NP
nounPhraseSP "PD Control Loop") ("Closed-Loop control " String -> String -> String
forall a. [a] -> [a] -> [a]
++
        "system with PD Controller, Summing Point and Power Plant")

pidC :: ConceptChunk
pidC
  = String -> NP -> String -> ConceptChunk
dcc "pdController" (String -> NP
nounPhraseSP "PD Controller") 
        "Proportional-Derivative Controller"

summingPt :: ConceptChunk
summingPt
  = String -> NP -> String -> ConceptChunk
dcc "summingPoint" (String -> NP
nounPhraseSP "Summing Point") ("Control block where " String -> String -> String
forall a. [a] -> [a] -> [a]
++
        "the difference between the Set-Point and the Process Variable " String -> String -> String
forall a. [a] -> [a] -> [a]
++
        "is computed")

powerPlant :: ConceptChunk
powerPlant
  = String -> NP -> String -> ConceptChunk
dcc "powerPlant" (String -> NP
nounPhraseSP "Power Plant") 
      "A second order system to be controlled"

secondOrderSystem :: ConceptChunk
secondOrderSystem
  = String -> NP -> String -> ConceptChunk
dcc "secondOrderSystem" (String -> NP
nounPhraseSP "Second Order System") 
      ("A system whose input-output relationship is denoted by a second-order "
         String -> String -> String
forall a. [a] -> [a] -> [a]
++ "differential equation")

processError :: ConceptChunk
processError
  = String -> NP -> String -> ConceptChunk
dcc "processError" (String -> NP
nounPhraseSP "Process Error") 
      ("Input to the PID controller. Process Error is the difference between the "
         String -> String -> String
forall a. [a] -> [a] -> [a]
++ "Set-Point and the Process Variable")

stepTime :: ConceptChunk
stepTime = String -> NP -> String -> ConceptChunk
dcc "stepTime" (String -> NP
nounPhraseSP "Step Time") "Simulation step time"

simulationTime :: ConceptChunk
simulationTime
  = String -> NP -> String -> ConceptChunk
dcc "simulationTime" (String -> NP
nounPhraseSP "Simulation Time") 
      "Total execution time of the PD simulation"

processVariable :: ConceptChunk
processVariable
  = String -> NP -> String -> ConceptChunk
dcc "processVariable" (String -> NP
nounPhraseSP "Process Variable") 
      "The output value from the power plant"

controlVariable :: ConceptChunk
controlVariable
  = String -> NP -> String -> ConceptChunk
dcc "controlVariable" (String -> NP
nounPhraseSP "Control Variable") 
      "The Control Variable is the output of the PD controller"

setPoint :: ConceptChunk
setPoint
  = String -> NP -> String -> ConceptChunk
dcc "setPoint" (String -> NP
nounPhraseSP "Set-Point") 
      ("The desired value that the control system must reach. This also knows "
         String -> String -> String
forall a. [a] -> [a] -> [a]
++ "as the reference variable")

propGain :: ConceptChunk
propGain
  = String -> NP -> String -> ConceptChunk
dcc "propGain" (String -> NP
nounPhraseSP "Proportional Gain") 
      "Gain constant of the proportional controller"

derGain :: ConceptChunk
derGain
  = String -> NP -> String -> ConceptChunk
dcc "derGain" (String -> NP
nounPhraseSP "Derivative Gain") 
      "Gain constant of the derivative controller"

propControl :: ConceptChunk
propControl
  = String -> NP -> String -> ConceptChunk
dcc "propControl" (String -> NP
nounPhraseSP "Proportional control")
      ("A linear feedback control system where correction is applied to the controlled " String -> String -> String
forall a. [a] -> [a] -> [a]
++
      "variable which is proportional to the difference between desired and measured values")

derControl :: ConceptChunk
derControl
  = String -> NP -> String -> ConceptChunk
dcc "derControl" (String -> NP
nounPhraseSP "Derivative control")
      ("Monitors the rate of change of the error signal and contributes a component " String -> String -> String
forall a. [a] -> [a] -> [a]
++ 
      "of the output signal (proportional to a derivative of the error signal)")

simulation :: ConceptChunk
simulation
  = String -> NP -> String -> ConceptChunk
dcc "simulation" (String -> NP
nounPhraseSP "simulation") 
      "Simulation of the PD controller"

ccFrequencyDomain :: ConceptChunk
ccFrequencyDomain
  = String -> NP -> String -> ConceptChunk
dcc "frequencyDomain" (String -> NP
nounPhraseSP "frequency domain") 
      ("The analysis of mathematical functions in terms of frequency, instead "
         String -> String -> String
forall a. [a] -> [a] -> [a]
++ "of time")

ccTimeDomain :: ConceptChunk
ccTimeDomain 
  = String -> NP -> String -> ConceptChunk
dcc "timeDomain" (String -> NP
nounPhraseSP "time domain")
      "The analysis of mathematical functions in terms of time"

ccLaplaceTransform :: ConceptChunk
ccLaplaceTransform
  = String -> NP -> String -> ConceptChunk
dcc "laplaceTransform" (String -> NP
cn' "Laplace transform") 
      ("An integral transform that converts a function of a real variable t " String -> String -> String
forall a. [a] -> [a] -> [a]
++
         "(often time) to a function of a complex variable s (complex frequency)")

ccAbsTolerance :: ConceptChunk
ccAbsTolerance
  = String -> NP -> String -> ConceptChunk
dcc "absoluteTolerance" (String -> NP
nounPhraseSP "Absolute Tolerance") 
      "Absolute tolerance for the integrator"

ccRelTolerance :: ConceptChunk
ccRelTolerance
  = String -> NP -> String -> ConceptChunk
dcc "relativeTolerance" (String -> NP
nounPhraseSP "Relative Tolerance") 
      "Relative tolerance for the integrator"

ccTransferFxn :: ConceptChunk
ccTransferFxn
  = String -> NP -> String -> ConceptChunk
dcc "transferFxn" (String -> NP
nounPhraseSP "Transfer Function")
      ("The Transfer Function of a system is the ratio of the output to the input"
         String -> String -> String
forall a. [a] -> [a] -> [a]
++ " functions in the frequency domain")

ccDampingCoeff :: ConceptChunk
ccDampingCoeff
  = String -> NP -> String -> ConceptChunk
dcc "dampingCoeff" (String -> NP
nounPhraseSP "Damping Coefficient")
      "Quantity that characterizes a second order system's oscillatory response"

ccStiffCoeff :: ConceptChunk
ccStiffCoeff
  = String -> NP -> String -> ConceptChunk
dcc "stiffnessCoeff" (String -> NP
nounPhraseSP "Stiffness Coefficient")
      "Quantity that characterizes a spring's stiffness"

concepts :: [IdeaDict]
concepts :: [IdeaDict]
concepts = (ConceptChunk -> IdeaDict) -> [ConceptChunk] -> [IdeaDict]
forall a b. (a -> b) -> [a] -> [b]
map ConceptChunk -> IdeaDict
forall c. Idea c => c -> IdeaDict
nw [ConceptChunk]
defs

defs :: [ConceptChunk]
defs :: [ConceptChunk]
defs
  = [ConceptChunk
pidCL, ConceptChunk
pidC, ConceptChunk
summingPt, ConceptChunk
powerPlant, ConceptChunk
secondOrderSystem, ConceptChunk
processError,
     ConceptChunk
simulationTime, ConceptChunk
processVariable, ConceptChunk
setPoint, ConceptChunk
propGain, ConceptChunk
derGain, ConceptChunk
propControl,
    ConceptChunk
derControl, ConceptChunk
ccFrequencyDomain, ConceptChunk
ccTimeDomain, ConceptChunk
ccLaplaceTransform, ConceptChunk
controlVariable, ConceptChunk
stepTime,
     ConceptChunk
ccAbsTolerance, ConceptChunk
ccRelTolerance, ConceptChunk
ccTransferFxn, ConceptChunk
ccDampingCoeff,
     ConceptChunk
ccStiffCoeff]