module Drasil.SWHSNoPCM.Body (si, mkSRS, noPCMODEInfo) where
import Data.List ((\\))
import Language.Drasil hiding (section)
import Language.Drasil.Chunk.Concept.NamedCombinators
import qualified Language.Drasil.Development as D
import qualified Language.Drasil.Sentence.Combinators as S
import Drasil.System (SystemKind(Specification), mkSystem)
import Drasil.Metadata (inModel)
import Drasil.SRSDocument
import qualified Drasil.DocLang.SRS as SRS (inModel)
import Drasil.Generator (cdb)
import Data.Drasil.People (thulasi)
import Data.Drasil.Concepts.Documentation as Doc (material_)
import Data.Drasil.Concepts.Math (mathcon', ode)
import Data.Drasil.Concepts.PhysicalProperties (materialProprty, physicalcon)
import qualified Data.Drasil.Concepts.Physics as CP (physicCon', energy, mechEnergy, pressure)
import Data.Drasil.Concepts.Software (softwarecon)
import Data.Drasil.Concepts.Thermodynamics (heatCapSpec, htFlux, phaseChange,
temp, thermalAnalysis, thermalConduction, thermocon, boilPt, latentHeat, meltPt)
import Data.Drasil.ExternalLibraries.ODELibraries (scipyODESymbols, osloSymbols,
apacheODESymbols, odeintSymbols, odeInfoChunks)
import qualified Data.Drasil.Quantities.Thermodynamics as QT (temp,
heatCapSpec, htFlux, sensHeat)
import Data.Drasil.Quantities.Math (gradient, pi_, piConst, surface,
uNormalVect, surArea, area)
import Data.Drasil.Quantities.PhysicalProperties (vol, mass, density)
import Data.Drasil.Quantities.Physics (time, energy)
import Theory.Drasil (TheoryModel)
import Drasil.SWHS.Body (charsOfReader, dataContMid, motivation,
introStart, externalLinkRef, physSyst1, physSyst2, sysCntxtDesc,
systContRespBullets, sysCntxtRespIntro, userChars)
import Drasil.SWHS.Changes (likeChgTCVOD, likeChgTCVOL, likeChgTLH)
import Drasil.SWHS.Concepts (acronyms, coil, sWHT, tank, transient, water, con, phsChgMtrl)
import Drasil.SWHS.Requirements (nfRequirements)
import Drasil.SWHS.TMods (PhaseChange(Liquid), consThermE, nwtnCooling, sensHtETemplate)
import Drasil.SWHS.Unitals (deltaT, htFluxC, htFluxIn,
htFluxOut, htCapL, htTransCoeff, inSA, outSA, tankVol, tau, tauW,
tempEnv, tempW, thFluxVect, volHtGen, watE,
wMass, wVol, absTol, relTol)
import Drasil.SWHS.References (uriReferences)
import Drasil.SWHSNoPCM.Assumptions
import Drasil.SWHSNoPCM.Changes (likelyChgs, unlikelyChgs)
import qualified Drasil.SWHSNoPCM.DataDefs as NoPCM (dataDefs)
import Drasil.SWHSNoPCM.Definitions (htTrans)
import Drasil.SWHSNoPCM.GenDefs (genDefs)
import Drasil.SWHSNoPCM.Goals (goals)
import Drasil.SWHSNoPCM.IMods (eBalanceOnWtr, instModIntro)
import Drasil.SWHSNoPCM.LabelledContent (labelledContent, figTank, sysCntxtFig)
import Drasil.SWHSNoPCM.MetaConcepts (progName)
import qualified Drasil.SWHSNoPCM.IMods as NoPCM (iMods)
import Drasil.SWHSNoPCM.ODEs
import Drasil.SWHSNoPCM.Requirements (funcReqs, funcReqsTables)
import Drasil.SWHSNoPCM.References (citations)
import Drasil.SWHSNoPCM.Unitals (inputs, constrained, unconstrained,
specParamValList, outputs)
symbols :: [DefinedQuantityDict]
symbols :: [DefinedQuantityDict]
symbols = ConstrConcept -> DefinedQuantityDict
forall c.
(Quantity c, Concept c, MayHaveUnit c) =>
c -> DefinedQuantityDict
dqdWr ConstrConcept
watE DefinedQuantityDict
-> [DefinedQuantityDict] -> [DefinedQuantityDict]
forall a. a -> [a] -> [a]
: (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]
concepts [DefinedQuantityDict]
-> [DefinedQuantityDict] -> [DefinedQuantityDict]
forall a. [a] -> [a] -> [a]
++ (UncertQ -> DefinedQuantityDict)
-> [UncertQ] -> [DefinedQuantityDict]
forall a b. (a -> b) -> [a] -> [b]
map UncertQ -> DefinedQuantityDict
forall c.
(Quantity c, Concept c, MayHaveUnit c) =>
c -> DefinedQuantityDict
dqdWr [UncertQ]
constrained
symbolsAll :: [DefinedQuantityDict]
symbolsAll :: [DefinedQuantityDict]
symbolsAll = [DefinedQuantityDict
gradient, DefinedQuantityDict
pi_, DefinedQuantityDict
uNormalVect, UnitalChunk -> DefinedQuantityDict
forall c.
(Quantity c, Concept c, MayHaveUnit c) =>
c -> DefinedQuantityDict
dqdWr UnitalChunk
surface] [DefinedQuantityDict]
-> [DefinedQuantityDict] -> [DefinedQuantityDict]
forall a. [a] -> [a] -> [a]
++ [DefinedQuantityDict]
symbols [DefinedQuantityDict]
-> [DefinedQuantityDict] -> [DefinedQuantityDict]
forall a. [a] -> [a] -> [a]
++
(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]
symbolConcepts [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]
specParamValList [DefinedQuantityDict]
-> [DefinedQuantityDict] -> [DefinedQuantityDict]
forall a. [a] -> [a] -> [a]
++ (UncertQ -> DefinedQuantityDict)
-> [UncertQ] -> [DefinedQuantityDict]
forall a b. (a -> b) -> [a] -> [b]
map UncertQ -> DefinedQuantityDict
forall c.
(Quantity c, Concept c, MayHaveUnit c) =>
c -> DefinedQuantityDict
dqdWr [UncertQ
absTol, UncertQ
relTol] [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]
++
ODEInfo -> [DefinedQuantityDict]
odeInfoChunks ODEInfo
noPCMODEInfo
concepts :: [UnitalChunk]
concepts :: [UnitalChunk]
concepts = (UnitalChunk -> UnitalChunk) -> [UnitalChunk] -> [UnitalChunk]
forall a b. (a -> b) -> [a] -> [b]
map UnitalChunk -> UnitalChunk
forall c. (Unitary c, Concept c, MayHaveUnit c) => c -> UnitalChunk
ucw [UnitalChunk
tau, UnitalChunk
inSA, UnitalChunk
outSA, UnitalChunk
htCapL, UnitalChunk
htFluxIn, UnitalChunk
htFluxOut, UnitalChunk
volHtGen,
UnitalChunk
htTransCoeff, UnitalChunk
tankVol, UnitalChunk
deltaT, UnitalChunk
tempEnv, UnitalChunk
thFluxVect, UnitalChunk
htFluxC, UnitalChunk
wMass, UnitalChunk
wVol, UnitalChunk
tauW]
symbolConcepts :: [UnitalChunk]
symbolConcepts :: [UnitalChunk]
symbolConcepts = (UnitalChunk -> UnitalChunk) -> [UnitalChunk] -> [UnitalChunk]
forall a b. (a -> b) -> [a] -> [b]
map UnitalChunk -> UnitalChunk
forall c. (Unitary c, Concept c, MayHaveUnit c) => c -> UnitalChunk
ucw [UnitalChunk
density, UnitalChunk
mass, UnitalChunk
time, UnitalChunk
vol,
UnitalChunk
QT.temp, UnitalChunk
QT.heatCapSpec, UnitalChunk
QT.htFlux, UnitalChunk
QT.sensHeat]
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, [Literature] -> TSIntro
SymbConvention [IdeaDict -> Literature
Lit (IdeaDict -> Literature) -> IdeaDict -> Literature
forall a b. (a -> b) -> a -> b
$ IdeaDict -> IdeaDict
forall c. Idea c => c -> IdeaDict
nw IdeaDict
htTrans, IdeaDict -> Literature
Doc' (IdeaDict -> Literature) -> IdeaDict -> Literature
forall a b. (a -> b) -> a -> b
$ CI -> IdeaDict
forall c. Idea c => c -> IdeaDict
nw CI
progName], TSIntro
SymbOrder, TSIntro
VectorUnits],
[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
introStart Sentence -> Sentence -> Sentence
+:+ Sentence
introStartNoPCM) (Sentence -> CI -> Sentence
introEnd (CI -> Sentence
forall n. NamedIdea n => n -> Sentence
plural CI
progName) CI
progName)
[ [Sentence] -> IntroSub
IPurpose ([Sentence] -> IntroSub) -> [Sentence] -> IntroSub
forall a b. (a -> b) -> a -> b
$ CI -> Verbosity -> [Sentence]
purpDoc CI
progName Verbosity
Verbose
, Sentence -> IntroSub
IScope Sentence
scope
, [Sentence] -> [Sentence] -> [Sentence] -> IntroSub
IChar [] [Sentence]
charsOfReader []
, CI -> Section -> Sentence -> IntroSub
IOrgSec CI
inModel ([Contents] -> [Section] -> Section
SRS.inModel [] []) Sentence
orgDocEnd
],
GSDSec -> DocSection
GSDSec (GSDSec -> DocSection) -> GSDSec -> DocSection
forall a b. (a -> b) -> a -> b
$
[GSDSub] -> GSDSec
GSDProg
[ [Contents] -> GSDSub
SysCntxt [CI -> Contents
sysCntxtDesc CI
progName, LabelledContent -> Contents
LlC LabelledContent
sysCntxtFig, CI -> Contents
sysCntxtRespIntro CI
progName, CI -> Contents
systContRespBullets CI
progName]
, [Contents] -> GSDSub
UsrChars [CI -> Contents
userChars CI
progName]
, [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]
terms
, CI -> [Sentence] -> LabelledContent -> [Contents] -> PDSub
forall a.
Idea a =>
a -> [Sentence] -> LabelledContent -> [Contents] -> PDSub
PhySysDesc CI
progName [Sentence]
physSystParts LabelledContent
figTank []
, [Sentence] -> PDSub
Goals [Sentence]
goalInputs]
, 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
Units] Fields -> Fields -> Fields
forall a. [a] -> [a] -> [a]
++ Fields
stdFields) DerivationDisplay
ShowDerivation
, [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 [Sentence
instModIntro] ([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
dataContMid [UncertQ]
constrained
, [ConstrConcept] -> [Contents] -> SCSSub
forall c.
(Quantity c, Constrained c) =>
[c] -> [Contents] -> SCSSub
CorrSolnPpties [ConstrConcept]
dataConstListOut []
]
],
ReqrmntSec -> DocSection
ReqrmntSec (ReqrmntSec -> DocSection) -> ReqrmntSec -> DocSection
forall a b. (a -> b) -> a -> b
$ [ReqsSub] -> ReqrmntSec
ReqsProg [
[LabelledContent] -> ReqsSub
FReqsSub [LabelledContent]
funcReqsTables,
ReqsSub
NonFReqsSub
],
DocSection
LCsSec,
DocSection
UCsSec,
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,
AuxConstntSec -> DocSection
AuxConstntSec (AuxConstntSec -> DocSection) -> AuxConstntSec -> DocSection
forall a b. (a -> b) -> a -> b
$ CI -> [ConstQDef] -> AuxConstntSec
AuxConsProg CI
progName [ConstQDef]
specParamValList,
DocSection
Bibliography]
concIns :: [ConceptInstance]
concIns :: [ConceptInstance]
concIns = [ConceptInstance]
goals [ConceptInstance] -> [ConceptInstance] -> [ConceptInstance]
forall a. [a] -> [a] -> [a]
++ [ConceptInstance]
funcReqs [ConceptInstance] -> [ConceptInstance] -> [ConceptInstance]
forall a. [a] -> [a] -> [a]
++ [ConceptInstance]
nfRequirements [ConceptInstance] -> [ConceptInstance] -> [ConceptInstance]
forall a. [a] -> [a] -> [a]
++ [ConceptInstance]
assumptions [ConceptInstance] -> [ConceptInstance] -> [ConceptInstance]
forall a. [a] -> [a] -> [a]
++
[ConceptInstance
likeChgTCVOD, ConceptInstance
likeChgTCVOL] [ConceptInstance] -> [ConceptInstance] -> [ConceptInstance]
forall a. [a] -> [a] -> [a]
++ [ConceptInstance]
likelyChgs [ConceptInstance] -> [ConceptInstance] -> [ConceptInstance]
forall a. [a] -> [a] -> [a]
++ [ConceptInstance
likeChgTLH] [ConceptInstance] -> [ConceptInstance] -> [ConceptInstance]
forall a. [a] -> [a] -> [a]
++ [ConceptInstance]
unlikelyChgs
stdFields :: Fields
stdFields :: Fields
stdFields = [Field
DefiningEquation, Verbosity -> InclUnits -> Field
Description Verbosity
Verbose InclUnits
IncludeUnits, Field
Notes, Field
Source, Field
RefBy]
si :: System
si :: System
si = CI
-> SystemKind
-> People
-> [Sentence]
-> [Sentence]
-> [Sentence]
-> [Sentence]
-> [DefinedQuantityDict]
-> [TheoryModel]
-> [GenDefn]
-> [DataDefinition]
-> [InstanceModel]
-> [String]
-> [DefinedQuantityDict]
-> [ConstrConcept]
-> [ConstrConcept]
-> [ConstQDef]
-> ChunkDB
-> [Reference]
-> 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
-> [Reference]
-> System
mkSystem
CI
progName SystemKind
Specification [Person
thulasi]
[Sentence
purp] [Sentence
introStartNoPCM] [Sentence
scope] [Sentence
motivation]
(((UncertQ -> DefinedQuantityDict)
-> [UncertQ] -> [DefinedQuantityDict]
forall a b. (a -> b) -> [a] -> [b]
map UncertQ -> DefinedQuantityDict
forall c.
(Quantity c, Concept c, MayHaveUnit c) =>
c -> DefinedQuantityDict
dqdWr [UncertQ]
unconstrained [DefinedQuantityDict]
-> [DefinedQuantityDict] -> [DefinedQuantityDict]
forall a. [a] -> [a] -> [a]
++ [DefinedQuantityDict]
symbolsAll) [DefinedQuantityDict]
-> [DefinedQuantityDict] -> [DefinedQuantityDict]
forall a. Eq a => [a] -> [a] -> [a]
\\ [UnitalChunk -> DefinedQuantityDict
forall c.
(Quantity c, Concept c, MayHaveUnit c) =>
c -> DefinedQuantityDict
dqdWr UnitalChunk
tau])
[TheoryModel]
tMods [GenDefn]
genDefs [DataDefinition]
NoPCM.dataDefs [InstanceModel]
NoPCM.iMods
[]
[DefinedQuantityDict]
inputs [ConstrConcept]
outputs
((UncertQ -> ConstrConcept) -> [UncertQ] -> [ConstrConcept]
forall a b. (a -> b) -> [a] -> [b]
map UncertQ -> ConstrConcept
forall c.
(Quantity c, Concept c, Constrained c, HasReasVal c,
MayHaveUnit c) =>
c -> ConstrConcept
cnstrw' [UncertQ]
constrained [ConstrConcept] -> [ConstrConcept] -> [ConstrConcept]
forall a. [a] -> [a] -> [a]
++ (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
tempW, ConstrConcept
watE]) (ConstQDef
piConst ConstQDef -> [ConstQDef] -> [ConstQDef]
forall a. a -> [a] -> [a]
: [ConstQDef]
specParamValList)
ChunkDB
symbMap [Reference]
allRefs
purp :: Sentence
purp :: Sentence
purp = [Sentence] -> Sentence
foldlSent_ [String -> Sentence
S String
"investigate the heating" Sentence -> Sentence -> Sentence
`S.of_` NPStruct -> Sentence
D.toSent (NP -> NPStruct
forall n. NounPhrase n => n -> NPStruct
phraseNP (ConceptChunk
water ConceptChunk -> ConceptChunk -> NP
forall c d. (NamedIdea c, NamedIdea d) => c -> d -> NP
`inA` ConceptChunk
sWHT))]
ideaDicts :: [IdeaDict]
ideaDicts :: [IdeaDict]
ideaDicts =
[IdeaDict
htTrans, IdeaDict
materialProprty] [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
progName, CI
phsChgMtrl] [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]
CP.physicCon' [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]
softwarecon [ConceptChunk] -> [ConceptChunk] -> [ConceptChunk]
forall a. [a] -> [a] -> [a]
++ [ConceptChunk]
thermocon [ConceptChunk] -> [ConceptChunk] -> [ConceptChunk]
forall a. [a] -> [a] -> [a]
++ [ConceptChunk]
con [ConceptChunk] -> [ConceptChunk] -> [ConceptChunk]
forall a. [a] -> [a] -> [a]
++ [ConceptChunk]
physicalcon [ConceptChunk] -> [ConceptChunk] -> [ConceptChunk]
forall a. [a] -> [a] -> [a]
++ [ConceptChunk
boilPt, ConceptChunk
latentHeat,
ConceptChunk
meltPt] [ConceptChunk] -> [ConceptChunk] -> [ConceptChunk]
forall a. [a] -> [a] -> [a]
++ [ConceptChunk
CP.energy, ConceptChunk
CP.mechEnergy, ConceptChunk
CP.pressure] [ConceptChunk] -> [ConceptChunk] -> [ConceptChunk]
forall a. [a] -> [a] -> [a]
++
(UnitalChunk -> ConceptChunk) -> [UnitalChunk] -> [ConceptChunk]
forall a b. (a -> b) -> [a] -> [b]
map UnitalChunk -> ConceptChunk
forall c. Concept c => c -> ConceptChunk
cw [UnitalChunk
surArea, UnitalChunk
area]
symbMap :: ChunkDB
symbMap :: ChunkDB
symbMap = [DefinedQuantityDict]
-> [IdeaDict]
-> [ConceptChunk]
-> [UnitDefn]
-> [DataDefinition]
-> [InstanceModel]
-> [GenDefn]
-> [TheoryModel]
-> [ConceptInstance]
-> [Citation]
-> [LabelledContent]
-> ChunkDB
cdb [DefinedQuantityDict]
symbolsAll [IdeaDict]
ideaDicts [ConceptChunk]
conceptChunks ([] :: [UnitDefn]) [DataDefinition]
NoPCM.dataDefs
[InstanceModel]
NoPCM.iMods [GenDefn]
genDefs [TheoryModel]
tMods [ConceptInstance]
concIns [Citation]
citations
([LabelledContent]
labelledContent [LabelledContent] -> [LabelledContent] -> [LabelledContent]
forall a. [a] -> [a] -> [a]
++ [LabelledContent]
funcReqsTables)
abbreviationsList :: [IdeaDict]
abbreviationsList :: [IdeaDict]
abbreviationsList =
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]
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]
symbols
allRefs :: [Reference]
allRefs :: [Reference]
allRefs = [Reference
externalLinkRef, Reference
externalLinkRef'] [Reference] -> [Reference] -> [Reference]
forall a. [a] -> [a] -> [a]
++ [Reference]
uriReferences
introStartNoPCM :: Sentence
introStartNoPCM :: Sentence
introStartNoPCM = CI -> Sentence
forall n. NamedIdea n => n -> Sentence
atStart' CI
progName Sentence -> Sentence -> Sentence
+:+ String -> Sentence
S String
"provide a novel way of storing" Sentence -> Sentence -> Sentence
+:+. UnitalChunk -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase UnitalChunk
energy
introEnd :: Sentence -> CI -> Sentence
introEnd :: Sentence -> CI -> Sentence
introEnd Sentence
progSent CI
pro = [Sentence] -> Sentence
foldlSent_ [Sentence
progSent Sentence -> Sentence -> Sentence
+:+ String -> Sentence
S String
"The developed program",
String -> Sentence
S String
"will be referred to as", CI -> Sentence
forall n. NamedIdea n => n -> Sentence
titleize CI
pro, Sentence -> Sentence
sParen (CI -> Sentence
forall c. Idea c => c -> Sentence
short CI
pro),
String -> Sentence
S String
"based on the original" Sentence -> Sentence -> Sentence
`sC` String -> Sentence
S String
"manually created version" Sentence -> Sentence -> Sentence
`S.of_` Reference -> Sentence -> Sentence
forall r.
(HasUID r, HasRefAddress r, HasShortName r) =>
r -> Sentence -> Sentence
namedRef Reference
externalLinkRef' (String -> Sentence
S String
"SWHSNoPCM")]
externalLinkRef' :: Reference
externalLinkRef' :: Reference
externalLinkRef' = String -> String -> ShortName -> Reference
makeURI String
"SWHSNoPCM_SRSLink"
String
"https://github.com/smiths/caseStudies/blob/master/CaseStudies/noPCM"
(Sentence -> ShortName
shortname' (Sentence -> ShortName) -> Sentence -> ShortName
forall a b. (a -> b) -> a -> b
$ String -> Sentence
S String
"SWHSNoPCM_SRSLink")
scope :: Sentence
scope :: Sentence
scope = ConceptChunk -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase ConceptChunk
thermalAnalysis Sentence -> Sentence -> Sentence
`S.of_` String -> Sentence
S String
"a single" Sentence -> Sentence -> Sentence
+:+ ConceptChunk -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase ConceptChunk
sWHT
orgDocEnd :: Sentence
orgDocEnd :: Sentence
orgDocEnd = [Sentence] -> Sentence
foldlSent_ [NPStruct -> Sentence
D.toSent (NP -> NPStruct
forall n. NounPhrase n => n -> NPStruct
atStartNP (CI -> NP
forall t. NamedIdea t => t -> NP
the CI
inModel)),
String -> Sentence
S String
"to be solved" Sentence -> Sentence -> Sentence
`S.is` String -> Sentence
S String
"referred to as" Sentence -> Sentence -> Sentence
+:+. InstanceModel -> Sentence
forall r.
(HasUID r, HasRefAddress r, HasShortName r) =>
r -> Sentence
refS InstanceModel
eBalanceOnWtr,
NPStruct -> Sentence
D.toSent (NP -> NPStruct
forall n. NounPhrase n => n -> NPStruct
atStartNP (CI -> NP
forall t. NamedIdea t => t -> NP
the CI
inModel)), String -> Sentence
S String
"provides the", CI -> Sentence
forall n. NamedIdea n => n -> Sentence
titleize CI
ode,
Sentence -> Sentence
sParen (CI -> Sentence
forall c. Idea c => c -> Sentence
short CI
ode), String -> Sentence
S String
"that models the" Sentence -> Sentence -> Sentence
+:+. CI -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase CI
progName,
CI -> Sentence
forall c. Idea c => c -> Sentence
short CI
progName, String -> Sentence
S String
"solves this", CI -> Sentence
forall c. Idea c => c -> Sentence
short CI
ode]
terms :: [ConceptChunk]
terms :: [ConceptChunk]
terms = [ConceptChunk
htFlux, ConceptChunk
heatCapSpec, ConceptChunk
thermalConduction, ConceptChunk
transient]
physSystParts :: [Sentence]
physSystParts :: [Sentence]
physSystParts = ([Sentence] -> Sentence) -> [[Sentence]] -> [Sentence]
forall a b. (a -> b) -> [a] -> [b]
map [Sentence] -> Sentence
foldlSent_ [ConceptChunk -> ConceptChunk -> [Sentence]
physSyst1 ConceptChunk
tank ConceptChunk
water, ConceptChunk -> ConceptChunk -> UnitalChunk -> [Sentence]
physSyst2 ConceptChunk
coil ConceptChunk
tank UnitalChunk
htFluxC]
goalInputs :: [Sentence]
goalInputs :: [Sentence]
goalInputs = [NPStruct -> Sentence
D.toSent (NP -> NPStruct
forall n. NounPhrase n => n -> NPStruct
phraseNP (ConceptChunk
temp ConceptChunk -> ConceptChunk -> NP
forall c d. (NamedIdea c, NamedIdea d) => c -> d -> NP
`the_ofThe` ConceptChunk
coil)),
String -> Sentence
S String
"the initial" Sentence -> Sentence -> Sentence
+:+ ConstrConcept -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase ConstrConcept
tempW, NPStruct -> Sentence
D.toSent (NP -> NPStruct
forall n. NounPhrase n => n -> NPStruct
pluralNP (IdeaDict -> NP
forall t. NamedIdea t => t -> NP
the IdeaDict
materialProprty))]
tMods :: [TheoryModel]
tMods :: [TheoryModel]
tMods = [TheoryModel
consThermE, TheoryModel
sensHtE, TheoryModel
nwtnCooling]
sensHtE :: TheoryModel
sensHtE :: TheoryModel
sensHtE = PhaseChange -> Sentence -> TheoryModel
sensHtETemplate PhaseChange
Liquid Sentence
sensHtEdesc
sensHtEdesc :: Sentence
sensHtEdesc :: Sentence
sensHtEdesc = [Sentence] -> Sentence
foldlSent [UnitalChunk -> Sentence
forall c. (HasUID c, HasSymbol c) => c -> Sentence
ch UnitalChunk
QT.sensHeat, String -> Sentence
S String
"occurs as long as the", IdeaDict -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase IdeaDict
material_, String -> Sentence
S String
"does not reach a",
ConceptChunk -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase ConceptChunk
temp, String -> Sentence
S String
"where a", ConceptChunk -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase ConceptChunk
phaseChange, String -> Sentence
S String
"occurs" Sentence -> Sentence -> Sentence
`sC` String -> Sentence
S String
"as assumed in", ConceptInstance -> Sentence
forall r.
(HasUID r, HasRefAddress r, HasShortName r) =>
r -> Sentence
refS ConceptInstance
assumpWAL]
dataConstListOut :: [ConstrConcept]
dataConstListOut :: [ConstrConcept]
dataConstListOut = [ConstrConcept
tempW, ConstrConcept
watE]