module Drasil.PDController.Body (pidODEInfo, printSetting, si, srs, fullSI) where
import Language.Drasil
import Language.Drasil.Code (ODEInfo(..))
import Drasil.Metadata (dataDefn)
import Drasil.SRSDocument
import Database.Drasil.ChunkDB (cdb)
import qualified Drasil.DocLang.SRS as SRS (inModel)
import qualified Language.Drasil.Sentence.Combinators as S
import Data.Drasil.Concepts.Math (mathcon', ode)
import Data.Drasil.ExternalLibraries.ODELibraries
(apacheODESymbols, arrayVecDepVar, odeintSymbols, osloSymbols,
scipyODESymbols, diffCodeChunk)
import Data.Drasil.Quantities.Physics (physicscon)
import Data.Drasil.Concepts.PhysicalProperties (physicalcon)
import Data.Drasil.Concepts.Physics (angular, linear)
import Data.Drasil.Quantities.PhysicalProperties (mass)
import Data.Drasil.Quantities.Math (posInf, negInf)
import Drasil.PDController.Assumptions (assumptions)
import Drasil.PDController.Changes (likelyChgs)
import Drasil.PDController.Concepts (acronyms, pidC, concepts, defs)
import Drasil.PDController.DataDefs (dataDefinitions)
import Drasil.PDController.GenDefs (genDefns)
import Drasil.PDController.MetaConcepts (progName)
import Drasil.PDController.GenSysDesc
(gsdSysContextFig, gsdSysContextList, gsdSysContextP1, gsdSysContextP2,
gsduserCharacteristics)
import Drasil.PDController.IModel (instanceModels, imPD)
import Drasil.PDController.IntroSection (introPara, introPurposeOfDoc, externalLinkRef,
introUserChar1, introUserChar2, introscopeOfReq, scope)
import Drasil.PDController.References (citations)
import Drasil.PDController.Requirements (funcReqs, nonfuncReqs)
import Drasil.PDController.SpSysDesc (goals, sysFigure, sysGoalInput, sysParts)
import Drasil.PDController.TModel (theoreticalModels)
import Drasil.PDController.Unitals (symbols, inputs, outputs, inputsUC,
inpConstrained, pidConstants)
import Drasil.PDController.ODEs (pidODEInfo)
import Drasil.System (SystemKind(Specification), mkSystem)
naveen :: Person
naveen :: Person
naveen = String -> String -> Person
person String
"Naveen Ganesh" String
"Muralidharan"
srs :: Document
srs :: Document
srs = SRSDecl -> (IdeaDict -> IdeaDict -> Sentence) -> System -> Document
mkDoc SRSDecl
mkSRS ((IdeaDict -> Sentence)
-> (IdeaDict -> Sentence) -> IdeaDict -> IdeaDict -> Sentence
forall c d.
(c -> Sentence) -> (d -> Sentence) -> c -> d -> Sentence
S.forGen IdeaDict -> Sentence
forall n. NamedIdea n => n -> Sentence
titleize IdeaDict -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase) System
si
fullSI :: System
fullSI :: System
fullSI = SRSDecl -> System -> System
fillcdbSRS SRSDecl
mkSRS System
si
printSetting :: PrintingInformation
printSetting :: PrintingInformation
printSetting = System -> Stage -> PrintingConfiguration -> PrintingInformation
piSys System
fullSI Stage
Equational PrintingConfiguration
defaultConfiguration
mkSRS :: SRSDecl
mkSRS :: SRSDecl
mkSRS
= [DocSection
TableOfContents,
RefSec -> DocSection
RefSec (RefSec -> DocSection) -> RefSec -> DocSection
forall a b. (a -> b) -> a -> b
$ Contents -> [RefTab] -> RefSec
RefProg Contents
intro [RefTab
TUnits, [TSIntro] -> RefTab
tsymb [TSIntro
TSPurpose, TSIntro
SymbOrder], [IdeaDict] -> RefTab
TAandA [IdeaDict]
abbreviationsList],
IntroSec -> DocSection
IntroSec (IntroSec -> DocSection) -> IntroSec -> DocSection
forall a b. (a -> b) -> a -> b
$
Sentence -> Sentence -> [IntroSub] -> IntroSec
IntroProg Sentence
introPara (CI -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase CI
progName)
[[Sentence] -> IntroSub
IPurpose [Sentence
introPurposeOfDoc], Sentence -> IntroSub
IScope Sentence
introscopeOfReq,
[Sentence] -> [Sentence] -> [Sentence] -> IntroSub
IChar [Sentence]
introUserChar1 [Sentence]
introUserChar2 [],
CI -> Section -> Sentence -> IntroSub
IOrgSec CI
dataDefn ([Contents] -> [Section] -> Section
SRS.inModel [] [])
(String -> Sentence
S String
"The instance model referred as" Sentence -> Sentence -> Sentence
+:+ InstanceModel -> Sentence
forall r.
(HasUID r, HasRefAddress r, HasShortName r) =>
r -> Sentence
refS InstanceModel
imPD Sentence -> Sentence -> Sentence
+:+
String -> Sentence
S String
"provides an"
Sentence -> Sentence -> Sentence
+:+ CI -> Sentence
forall n. NamedIdea n => n -> Sentence
titleize CI
ode Sentence -> Sentence -> Sentence
+:+ Sentence -> Sentence
sParen (CI -> Sentence
forall c. Idea c => c -> Sentence
short CI
ode)
Sentence -> Sentence -> Sentence
+:+ String -> Sentence
S String
"that models the"
Sentence -> Sentence -> Sentence
+:+ ConceptChunk -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase ConceptChunk
pidC)],
GSDSec -> DocSection
GSDSec (GSDSec -> DocSection) -> GSDSec -> DocSection
forall a b. (a -> b) -> a -> b
$
[GSDSub] -> GSDSec
GSDProg
[[Contents] -> GSDSub
SysCntxt
[Contents
gsdSysContextP1, LabelledContent -> Contents
LlC LabelledContent
gsdSysContextFig, Contents
gsdSysContextP2,
Contents
gsdSysContextList],
[Contents] -> GSDSub
UsrChars [Contents
gsduserCharacteristics], [Contents] -> [Section] -> GSDSub
SystCons [] []],
SSDSec -> DocSection
SSDSec (SSDSec -> DocSection) -> SSDSec -> DocSection
forall a b. (a -> b) -> a -> b
$
[SSDSub] -> SSDSec
SSDProg
[ProblemDescription -> SSDSub
SSDProblem (ProblemDescription -> SSDSub) -> ProblemDescription -> SSDSub
forall a b. (a -> b) -> a -> b
$
Sentence -> [Section] -> [PDSub] -> ProblemDescription
PDProg Sentence
purp []
[Maybe Sentence -> [ConceptChunk] -> PDSub
forall c. Concept c => Maybe Sentence -> [c] -> PDSub
TermsAndDefs Maybe Sentence
forall a. Maybe a
Nothing [ConceptChunk]
defs,
CI -> [Sentence] -> LabelledContent -> [Contents] -> PDSub
forall a.
Idea a =>
a -> [Sentence] -> LabelledContent -> [Contents] -> PDSub
PhySysDesc CI
progName [Sentence]
sysParts LabelledContent
sysFigure [],
[Sentence] -> PDSub
Goals [Sentence]
sysGoalInput],
SolChSpec -> SSDSub
SSDSolChSpec (SolChSpec -> SSDSub) -> SolChSpec -> SSDSub
forall a b. (a -> b) -> a -> b
$
[SCSSub] -> SolChSpec
SCSProg
[SCSSub
Assumptions, [Sentence] -> Fields -> SCSSub
TMs [] (Field
Label Field -> Fields -> Fields
forall a. a -> [a] -> [a]
: Fields
stdFields),
[Sentence] -> Fields -> DerivationDisplay -> SCSSub
GDs [] (Field
Label Field -> Fields -> Fields
forall a. a -> [a] -> [a]
: Fields
stdFields) DerivationDisplay
HideDerivation,
[Sentence] -> Fields -> DerivationDisplay -> SCSSub
DDs [] ([Field
Label, Field
Symbol, Field
Units] Fields -> Fields -> Fields
forall a. [a] -> [a] -> [a]
++ Fields
stdFields) DerivationDisplay
ShowDerivation,
[Sentence] -> Fields -> DerivationDisplay -> SCSSub
IMs []
([Field
Label, Field
Input, Field
Output, Field
InConstraints, Field
OutConstraints] Fields -> Fields -> Fields
forall a. [a] -> [a] -> [a]
++
Fields
stdFields)
DerivationDisplay
ShowDerivation,
Sentence -> [UncertQ] -> SCSSub
forall c.
(HasUncertainty c, Quantity c, Constrained c, HasReasVal c,
MayHaveUnit c) =>
Sentence -> [c] -> SCSSub
Constraints Sentence
EmptyS [UncertQ]
inputsUC]],
ReqrmntSec -> DocSection
ReqrmntSec (ReqrmntSec -> DocSection) -> ReqrmntSec -> DocSection
forall a b. (a -> b) -> a -> b
$ [ReqsSub] -> ReqrmntSec
ReqsProg [Sentence -> [LabelledContent] -> ReqsSub
FReqsSub Sentence
EmptyS [], ReqsSub
NonFReqsSub], DocSection
LCsSec,
TraceabilitySec -> DocSection
TraceabilitySec (TraceabilitySec -> DocSection) -> TraceabilitySec -> DocSection
forall a b. (a -> b) -> a -> b
$ [TraceConfig] -> TraceabilitySec
TraceabilityProg ([TraceConfig] -> TraceabilitySec)
-> [TraceConfig] -> TraceabilitySec
forall a b. (a -> b) -> a -> b
$ System -> [TraceConfig]
traceMatStandard System
si, DocSection
Bibliography]
si :: System
si :: System
si = CI
-> SystemKind
-> People
-> [Sentence]
-> [Sentence]
-> [Sentence]
-> [Sentence]
-> [DefinedQuantityDict]
-> [TheoryModel]
-> [GenDefn]
-> [DataDefinition]
-> [InstanceModel]
-> [String]
-> [DefinedQuantityDict]
-> [DefinedQuantityDict]
-> [ConstrConcept]
-> [ConstQDef]
-> ChunkDB
-> System
forall a e h i j.
(CommonIdea a, Idea a, Quantity e, Eq e, MayHaveUnit e, Concept e,
Quantity h, MayHaveUnit h, Concept h, Quantity i, MayHaveUnit i,
Concept i, HasUID j, Constrained j) =>
a
-> SystemKind
-> People
-> [Sentence]
-> [Sentence]
-> [Sentence]
-> [Sentence]
-> [e]
-> [TheoryModel]
-> [GenDefn]
-> [DataDefinition]
-> [InstanceModel]
-> [String]
-> [h]
-> [i]
-> [j]
-> [ConstQDef]
-> ChunkDB
-> System
mkSystem
CI
progName SystemKind
Specification [Person
naveen]
[Sentence
purp] [Sentence
background] [Sentence
scope] [Sentence
motivation]
[DefinedQuantityDict]
symbolsAll
[TheoryModel]
theoreticalModels [GenDefn]
genDefns [DataDefinition]
dataDefinitions [InstanceModel]
instanceModels
[]
[DefinedQuantityDict]
inputs [DefinedQuantityDict]
outputs ((ConstrConcept -> ConstrConcept)
-> [ConstrConcept] -> [ConstrConcept]
forall a b. (a -> b) -> [a] -> [b]
map ConstrConcept -> ConstrConcept
forall c.
(Quantity c, Concept c, Constrained c, HasReasVal c,
MayHaveUnit c) =>
c -> ConstrConcept
cnstrw' [ConstrConcept]
inpConstrained)
[ConstQDef]
pidConstants ChunkDB
symbMap
purp :: Sentence
purp :: Sentence
purp = [Sentence] -> Sentence
foldlSent_ [String -> Sentence
S String
"provide a model" Sentence -> Sentence -> Sentence
`S.ofA` ConceptChunk -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase ConceptChunk
pidC,
String -> Sentence
S String
"that can be used for the tuning" Sentence -> Sentence -> Sentence
`S.ofThe` String -> Sentence
S String
"gain constants before",
String -> Sentence
S String
"the deployment" Sentence -> Sentence -> Sentence
`S.ofThe` String -> Sentence
S String
"controller"]
motivation :: Sentence
motivation :: Sentence
motivation = [Sentence] -> Sentence
foldlSent_ [String -> Sentence
S String
"The gains of a controller in an application" Sentence -> Sentence -> Sentence
+:+
String -> Sentence
S String
"must be tuned before the controller is ready for production"]
background :: Sentence
background :: Sentence
background = [Sentence] -> Sentence
foldlSent_ [String -> Sentence
S String
"Automatic process control with a controller (P/PI/PD/PID) is used",
String -> Sentence
S String
"in a variety of applications such as thermostats, automobile",
String -> Sentence
S String
"cruise-control, etc"]
symbolsAll :: [DefinedQuantityDict]
symbolsAll :: [DefinedQuantityDict]
symbolsAll = [DefinedQuantityDict]
symbols [DefinedQuantityDict]
-> [DefinedQuantityDict] -> [DefinedQuantityDict]
forall a. [a] -> [a] -> [a]
++ (ConstQDef -> DefinedQuantityDict)
-> [ConstQDef] -> [DefinedQuantityDict]
forall a b. (a -> b) -> [a] -> [b]
map ConstQDef -> DefinedQuantityDict
forall c.
(Quantity c, Concept c, MayHaveUnit c) =>
c -> DefinedQuantityDict
dqdWr [ConstQDef]
pidConstants
[DefinedQuantityDict]
-> [DefinedQuantityDict] -> [DefinedQuantityDict]
forall a. [a] -> [a] -> [a]
++ [DefinedQuantityDict]
scipyODESymbols [DefinedQuantityDict]
-> [DefinedQuantityDict] -> [DefinedQuantityDict]
forall a. [a] -> [a] -> [a]
++ [DefinedQuantityDict]
osloSymbols [DefinedQuantityDict]
-> [DefinedQuantityDict] -> [DefinedQuantityDict]
forall a. [a] -> [a] -> [a]
++ [DefinedQuantityDict]
apacheODESymbols [DefinedQuantityDict]
-> [DefinedQuantityDict] -> [DefinedQuantityDict]
forall a. [a] -> [a] -> [a]
++ [DefinedQuantityDict]
odeintSymbols
[DefinedQuantityDict]
-> [DefinedQuantityDict] -> [DefinedQuantityDict]
forall a. [a] -> [a] -> [a]
++ (CodeVarChunk -> DefinedQuantityDict)
-> [CodeVarChunk] -> [DefinedQuantityDict]
forall a b. (a -> b) -> [a] -> [b]
map CodeVarChunk -> DefinedQuantityDict
forall c.
(Quantity c, Concept c, MayHaveUnit c) =>
c -> DefinedQuantityDict
dqdWr [CodeVarChunk -> CodeVarChunk
listToArray CodeVarChunk
dp, ODEInfo -> CodeVarChunk
arrayVecDepVar ODEInfo
pidODEInfo,
CodeVarChunk -> CodeVarChunk
listToArray (CodeVarChunk -> CodeVarChunk) -> CodeVarChunk -> CodeVarChunk
forall a b. (a -> b) -> a -> b
$ CodeVarChunk -> CodeVarChunk
diffCodeChunk CodeVarChunk
dp, CodeVarChunk -> CodeVarChunk
diffCodeChunk CodeVarChunk
dp]
where dp :: CodeVarChunk
dp = ODEInfo -> CodeVarChunk
depVar ODEInfo
pidODEInfo
ideaDicts :: [IdeaDict]
ideaDicts :: [IdeaDict]
ideaDicts =
[IdeaDict]
concepts [IdeaDict] -> [IdeaDict] -> [IdeaDict]
forall a. [a] -> [a] -> [a]
++
CI -> IdeaDict
forall c. Idea c => c -> IdeaDict
nw CI
progName IdeaDict -> [IdeaDict] -> [IdeaDict]
forall a. a -> [a] -> [a]
: (CI -> IdeaDict) -> [CI] -> [IdeaDict]
forall a b. (a -> b) -> [a] -> [b]
map CI -> IdeaDict
forall c. Idea c => c -> IdeaDict
nw [CI]
mathcon'
conceptChunks :: [ConceptChunk]
conceptChunks :: [ConceptChunk]
conceptChunks =
[ConceptChunk]
physicalcon [ConceptChunk] -> [ConceptChunk] -> [ConceptChunk]
forall a. [a] -> [a] -> [a]
++ [ConceptChunk
linear, ConceptChunk
angular]
symbMap :: ChunkDB
symbMap :: ChunkDB
symbMap = [DefinedQuantityDict]
-> [IdeaDict]
-> [ConceptChunk]
-> [UnitDefn]
-> [DataDefinition]
-> [InstanceModel]
-> [GenDefn]
-> [TheoryModel]
-> [ConceptInstance]
-> [LabelledContent]
-> [Reference]
-> [Citation]
-> ChunkDB
forall q c u.
(Quantity q, MayHaveUnit q, Concept q, Concept c, IsUnit u) =>
[q]
-> [IdeaDict]
-> [c]
-> [u]
-> [DataDefinition]
-> [InstanceModel]
-> [GenDefn]
-> [TheoryModel]
-> [ConceptInstance]
-> [LabelledContent]
-> [Reference]
-> [Citation]
-> ChunkDB
cdb ((UnitalChunk -> DefinedQuantityDict)
-> [UnitalChunk] -> [DefinedQuantityDict]
forall a b. (a -> b) -> [a] -> [b]
map UnitalChunk -> DefinedQuantityDict
forall c.
(Quantity c, Concept c, MayHaveUnit c) =>
c -> DefinedQuantityDict
dqdWr [UnitalChunk]
physicscon [DefinedQuantityDict]
-> [DefinedQuantityDict] -> [DefinedQuantityDict]
forall a. [a] -> [a] -> [a]
++ [DefinedQuantityDict]
symbolsAll [DefinedQuantityDict]
-> [DefinedQuantityDict] -> [DefinedQuantityDict]
forall a. [a] -> [a] -> [a]
++ [UnitalChunk -> DefinedQuantityDict
forall c.
(Quantity c, Concept c, MayHaveUnit c) =>
c -> DefinedQuantityDict
dqdWr UnitalChunk
mass, DefinedQuantityDict -> DefinedQuantityDict
forall c.
(Quantity c, Concept c, MayHaveUnit c) =>
c -> DefinedQuantityDict
dqdWr DefinedQuantityDict
posInf, DefinedQuantityDict -> DefinedQuantityDict
forall c.
(Quantity c, Concept c, MayHaveUnit c) =>
c -> DefinedQuantityDict
dqdWr DefinedQuantityDict
negInf])
[IdeaDict]
ideaDicts
[ConceptChunk]
conceptChunks
([] :: [UnitDefn])
[DataDefinition]
dataDefinitions
[InstanceModel]
instanceModels
[GenDefn]
genDefns
[TheoryModel]
theoreticalModels
[ConceptInstance]
conceptInstances
([] :: [LabelledContent])
[Reference]
allRefs
[Citation]
citations
allRefs :: [Reference]
allRefs :: [Reference]
allRefs = [Reference
externalLinkRef]
abbreviationsList :: [IdeaDict]
abbreviationsList :: [IdeaDict]
abbreviationsList =
(CI -> IdeaDict) -> [CI] -> [IdeaDict]
forall a b. (a -> b) -> [a] -> [b]
map CI -> IdeaDict
forall c. Idea c => c -> IdeaDict
nw [CI]
acronyms [IdeaDict] -> [IdeaDict] -> [IdeaDict]
forall a. [a] -> [a] -> [a]
++
(DefinedQuantityDict -> IdeaDict)
-> [DefinedQuantityDict] -> [IdeaDict]
forall a b. (a -> b) -> [a] -> [b]
map DefinedQuantityDict -> IdeaDict
forall c. Idea c => c -> IdeaDict
nw [DefinedQuantityDict]
symbolsAll
conceptInstances :: [ConceptInstance]
conceptInstances :: [ConceptInstance]
conceptInstances = [ConceptInstance]
assumptions [ConceptInstance] -> [ConceptInstance] -> [ConceptInstance]
forall a. [a] -> [a] -> [a]
++ [ConceptInstance]
goals [ConceptInstance] -> [ConceptInstance] -> [ConceptInstance]
forall a. [a] -> [a] -> [a]
++ [ConceptInstance]
funcReqs [ConceptInstance] -> [ConceptInstance] -> [ConceptInstance]
forall a. [a] -> [a] -> [a]
++ [ConceptInstance]
nonfuncReqs [ConceptInstance] -> [ConceptInstance] -> [ConceptInstance]
forall a. [a] -> [a] -> [a]
++ [ConceptInstance]
likelyChgs
stdFields :: Fields
stdFields :: Fields
stdFields
= [Field
DefiningEquation, Verbosity -> InclUnits -> Field
Description Verbosity
Verbose InclUnits
IncludeUnits, Field
Notes, Field
Source, Field
RefBy]