module Drasil.PDController.Concepts where

import Drasil.Metadata
import Language.Drasil

import Data.Drasil.Concepts.Documentation
       (assumption, goalStmt, physSyst, requirement, refBy, refName, srs, typUnc)

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

pdControllerCI :: CI
pdControllerCI  = String -> NP -> String -> [IdeaDict] -> CI
commonIdeaWithDict String
"pdControllerCI"  (String -> NP
pn String
"proportional derivative")          String
"PD"            []
proportionalCI :: CI
proportionalCI  = String -> NP -> String -> [IdeaDict] -> CI
commonIdeaWithDict String
"proportionalCI"  (String -> NP
pn String
"proportional")                     String
"P"             []
derivativeCI :: CI
derivativeCI    = String -> NP -> String -> [IdeaDict] -> CI
commonIdeaWithDict String
"derivativeCI"    (String -> NP
pn String
"derivative")                       String
"D"             []
integralCI :: CI
integralCI      = String -> NP -> String -> [IdeaDict] -> CI
commonIdeaWithDict String
"integralCI"      (String -> NP
pn String
"integral")                         String
"I"             []
pidCI :: CI
pidCI           = String -> NP -> String -> [IdeaDict] -> CI
commonIdeaWithDict String
"pidCI"           (String -> NP
pn String
"proportional integral derivative") String
"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 String
"pdCtrlLoop" (String -> NP
nounPhraseSP String
"PD Control Loop") (String
"Closed-Loop control " String -> String -> String
forall a. [a] -> [a] -> [a]
++
        String
"system with PD Controller, Summing Point and Power Plant")

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

ccStiffCoeff :: ConceptChunk
ccStiffCoeff
  = String -> NP -> String -> ConceptChunk
dcc String
"ccStiffnessCoeff" (String -> NP
nounPhraseSP String
"Stiffness coefficient")
      String
"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]
termDefs

defs :: [ConceptChunk]
defs :: [ConceptChunk]
defs
  = [ConceptChunk]
termDefs [ConceptChunk] -> [ConceptChunk] -> [ConceptChunk]
forall a. [a] -> [a] -> [a]
++ [ConceptChunk
simulationTime, ConceptChunk
processVariable, ConceptChunk
setPoint, ConceptChunk
propGain, ConceptChunk
derGain,
     ConceptChunk
ccLaplaceTransform, ConceptChunk
stepTime,
     ConceptChunk
ccAbsTolerance, ConceptChunk
ccRelTolerance]

termDefs :: [ConceptChunk]
termDefs :: [ConceptChunk]
termDefs
  = [ConceptChunk
pidC, ConceptChunk
pidCL, ConceptChunk
summingPt, ConceptChunk
powerPlant, ConceptChunk
secondOrderSystem, ConceptChunk
processError,
     ConceptChunk
propControl, ConceptChunk
derControl, ConceptChunk
ccFrequencyDomain, ConceptChunk
ccTimeDomain,
     ConceptChunk
controlVariable, ConceptChunk
ccTransferFxn, ConceptChunk
ccDampingCoeff, ConceptChunk
ccStiffCoeff]