module Drasil.SWHSNoPCM.Body (si, srs, printSetting, noPCMODEInfo, fullSI) where
import Language.Drasil hiding (section)
import Drasil.SRSDocument
import qualified Drasil.DocLang.SRS as SRS (inModel)
import Theory.Drasil (TheoryModel)
import Language.Drasil.Chunk.Concept.NamedCombinators
import qualified Language.Drasil.Sentence.Combinators as S
import Language.Drasil.Code (quantvar)
import Data.List ((\\))
import Data.Drasil.People (thulasi)
import Data.Drasil.Concepts.Computation (algorithm, inValue)
import Data.Drasil.Concepts.Documentation as Doc (doccon, doccon', material_, srsDomains, sysCont)
import qualified Data.Drasil.Concepts.Documentation as Doc (srs)
import Data.Drasil.TheoryConcepts as Doc (inModel)
import Data.Drasil.Concepts.Education (educon)
import Data.Drasil.Concepts.Math (mathcon, mathcon', ode)
import Data.Drasil.Concepts.PhysicalProperties (materialProprty, physicalcon)
import Data.Drasil.Concepts.Physics (physicCon, physicCon')
import Data.Drasil.Concepts.Software (softwarecon)
import Data.Drasil.Concepts.Thermodynamics (heatCapSpec, htFlux, phaseChange,
temp, thermalAnalysis, thermalConduction, thermocon)
import Data.Drasil.ExternalLibraries.ODELibraries (scipyODESymbols, osloSymbols,
arrayVecDepVar, apacheODESymbols, odeintSymbols)
import qualified Data.Drasil.Quantities.Thermodynamics as QT (temp,
heatCapSpec, htFlux, sensHeat)
import Data.Drasil.Quantities.Math (gradient, pi_, piConst, surface,
uNormalVect)
import Data.Drasil.Quantities.PhysicalProperties (vol, mass, density)
import Data.Drasil.Quantities.Physics (time, energy, physicscon)
import Data.Drasil.Software.Products (prodtcon)
import Data.Drasil.Domains (materialEng)
import Data.Drasil.SI_Units (metre, kilogram, second, centigrade, joule, watt,
fundamentals, derived)
import Drasil.SWHS.Body (charsOfReader, dataContMid, introEnd, introStart,
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 (coilSAMax, deltaT, htFluxC, htFluxIn,
htFluxOut, htCapL, htTransCoeff, inSA, outSA, tankVol, tau, tauW,
tempEnv, tempW, thFluxVect, volHtGen, watE,
wMass, wVol, unitalChuncks, absTol, relTol)
import Drasil.SWHSNoPCM.Assumptions
import Drasil.SWHSNoPCM.Changes (likelyChgs, unlikelyChgs)
import Drasil.SWHSNoPCM.DataDefs (qDefs)
import qualified Drasil.SWHSNoPCM.DataDefs as NoPCM (dataDefs)
import Drasil.SWHSNoPCM.Definitions (srsSWHS, htTrans)
import Drasil.SWHSNoPCM.GenDefs (genDefs)
import Drasil.SWHSNoPCM.Goals (goals)
import Drasil.SWHSNoPCM.IMods (eBalanceOnWtr, instModIntro)
import qualified Drasil.SWHSNoPCM.IMods as NoPCM (iMods)
import Drasil.SWHSNoPCM.ODEs
import Drasil.SWHSNoPCM.Requirements (funcReqs, inputInitValsTable)
import Drasil.SWHSNoPCM.References (citations)
import Drasil.SWHSNoPCM.Unitals (inputs, constrained, unconstrained,
specParamValList)
srs :: Document
srs :: Document
srs = SRSDecl
-> (IdeaDict -> IdeaDict -> Sentence)
-> SystemInformation
-> Document
mkDoc SRSDecl
mkSRS forall c d. (NamedIdea c, NamedIdea d) => c -> d -> Sentence
S.forT SystemInformation
si
fullSI :: SystemInformation
fullSI :: SystemInformation
fullSI = SRSDecl -> SystemInformation -> SystemInformation
fillcdbSRS SRSDecl
mkSRS SystemInformation
si
printSetting :: PrintingInformation
printSetting :: PrintingInformation
printSetting = SystemInformation
-> Stage -> PrintingConfiguration -> PrintingInformation
piSys SystemInformation
fullSI Stage
Equational PrintingConfiguration
defaultConfiguration
resourcePath :: String
resourcePath :: String
resourcePath = String
"../../../../datafiles/swhsnopcm/"
units :: [UnitDefn]
units :: [UnitDefn]
units = forall a b. (a -> b) -> [a] -> [b]
map forall u. IsUnit u => u -> UnitDefn
unitWrapper [UnitDefn
metre, UnitDefn
kilogram, UnitDefn
second] forall a. [a] -> [a] -> [a]
++ forall a b. (a -> b) -> [a] -> [b]
map forall u. IsUnit u => u -> UnitDefn
unitWrapper [UnitDefn
centigrade, UnitDefn
joule, UnitDefn
watt]
symbols :: [DefinedQuantityDict]
symbols :: [DefinedQuantityDict]
symbols = DefinedQuantityDict
pi_ forall a. a -> [a] -> [a]
: forall a b. (a -> b) -> [a] -> [b]
map forall c.
(Quantity c, Concept c, MayHaveUnit c) =>
c -> DefinedQuantityDict
dqdWr [UnitalChunk]
concepts forall a. [a] -> [a] -> [a]
++ forall a b. (a -> b) -> [a] -> [b]
map forall c.
(Quantity c, Concept c, MayHaveUnit c) =>
c -> DefinedQuantityDict
dqdWr [UncertQ]
constrained
forall a. [a] -> [a] -> [a]
++ forall a b. (a -> b) -> [a] -> [b]
map forall c.
(Quantity c, Concept c, MayHaveUnit c) =>
c -> DefinedQuantityDict
dqdWr [ConstrConcept
tempW, ConstrConcept
watE]
forall a. [a] -> [a] -> [a]
++ [DefinedQuantityDict
gradient, DefinedQuantityDict
uNormalVect] forall a. [a] -> [a] -> [a]
++ [forall c.
(Quantity c, Concept c, MayHaveUnit c) =>
c -> DefinedQuantityDict
dqdWr UnitalChunk
surface]
symbolsAll :: [QuantityDict]
symbolsAll :: [QuantityDict]
symbolsAll = forall a b. (a -> b) -> [a] -> [b]
map forall q. (Quantity q, MayHaveUnit q) => q -> QuantityDict
qw [DefinedQuantityDict]
symbols forall a. [a] -> [a] -> [a]
++ forall a b. (a -> b) -> [a] -> [b]
map forall q. (Quantity q, MayHaveUnit q) => q -> QuantityDict
qw [ConstQDef]
specParamValList forall a. [a] -> [a] -> [a]
++
[forall q. (Quantity q, MayHaveUnit q) => q -> QuantityDict
qw ConstQDef
coilSAMax, forall q. (Quantity q, MayHaveUnit q) => q -> QuantityDict
qw UnitalChunk
tauW] forall a. [a] -> [a] -> [a]
++ forall a b. (a -> b) -> [a] -> [b]
map forall q. (Quantity q, MayHaveUnit q) => q -> QuantityDict
qw [UncertainChunk
absTol, UncertainChunk
relTol] forall a. [a] -> [a] -> [a]
++
[QuantityDict]
scipyODESymbols forall a. [a] -> [a] -> [a]
++ [QuantityDict]
osloSymbols forall a. [a] -> [a] -> [a]
++ [QuantityDict]
apacheODESymbols forall a. [a] -> [a] -> [a]
++ [QuantityDict]
odeintSymbols
forall a. [a] -> [a] -> [a]
++ forall a b. (a -> b) -> [a] -> [b]
map forall q. (Quantity q, MayHaveUnit q) => q -> QuantityDict
qw [CodeVarChunk -> CodeVarChunk
listToArray forall a b. (a -> b) -> a -> b
$ forall c. (Quantity c, MayHaveUnit c) => c -> CodeVarChunk
quantvar ConstrConcept
tempW, ODEInfo -> CodeVarChunk
arrayVecDepVar ODEInfo
noPCMODEInfo]
concepts :: [UnitalChunk]
concepts :: [UnitalChunk]
concepts = forall a b. (a -> b) -> [a] -> [b]
map forall c. (Unitary c, Concept c, MayHaveUnit c) => c -> UnitalChunk
ucw [UnitalChunk
density, UnitalChunk
tau, UnitalChunk
inSA, UnitalChunk
outSA,
UnitalChunk
htCapL, UnitalChunk
QT.htFlux, UnitalChunk
htFluxIn, UnitalChunk
htFluxOut, UnitalChunk
volHtGen,
UnitalChunk
htTransCoeff, UnitalChunk
mass, UnitalChunk
tankVol, UnitalChunk
QT.temp, UnitalChunk
QT.heatCapSpec,
UnitalChunk
deltaT, UnitalChunk
tempEnv, UnitalChunk
thFluxVect, UnitalChunk
time, UnitalChunk
htFluxC,
UnitalChunk
vol, UnitalChunk
wMass, UnitalChunk
wVol, UnitalChunk
tauW, UnitalChunk
QT.sensHeat]
mkSRS :: SRSDecl
mkSRS :: SRSDecl
mkSRS = [DocSection
TableOfContents,
RefSec -> DocSection
RefSec 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 forall a b. (a -> b) -> a -> b
$ forall c. Idea c => c -> IdeaDict
nw IdeaDict
htTrans, IdeaDict -> Literature
Doc' forall a b. (a -> b) -> a -> b
$ forall c. Idea c => c -> IdeaDict
nw CI
progName], TSIntro
SymbOrder, TSIntro
VectorUnits],
RefTab
TAandA],
IntroSec -> DocSection
IntroSec forall a b. (a -> b) -> a -> b
$
Sentence -> Sentence -> [IntroSub] -> IntroSec
IntroProg (Sentence
introStart Sentence -> Sentence -> Sentence
+:+ Sentence
introStartNoPCM) (Sentence -> CI -> Sentence
introEnd (forall n. NamedIdea n => n -> Sentence
plural CI
progName) CI
progName)
[ [Sentence] -> IntroSub
IPurpose 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 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 forall a b. (a -> b) -> a -> b
$
[SSDSub] -> SSDSec
SSDProg
[ ProblemDescription -> SSDSub
SSDProblem forall a b. (a -> b) -> a -> b
$ Sentence -> [Section] -> [PDSub] -> ProblemDescription
PDProg Sentence
purp []
[ forall c. Concept c => Maybe Sentence -> [c] -> PDSub
TermsAndDefs forall a. Maybe a
Nothing [ConceptChunk]
terms
, forall a.
Idea a =>
a -> [Sentence] -> LabelledContent -> [Contents] -> PDSub
PhySysDesc CI
progName [Sentence]
physSystParts LabelledContent
figTank []
, [Sentence] -> PDSub
Goals [Sentence]
goalInputs]
, SolChSpec -> SSDSub
SSDSolChSpec forall a b. (a -> b) -> a -> b
$ [SCSSub] -> SolChSpec
SCSProg
[ SCSSub
Assumptions
, [Sentence] -> Fields -> SCSSub
TMs [] (Field
Label forall a. a -> [a] -> [a]
: Fields
stdFields)
, [Sentence] -> Fields -> DerivationDisplay -> SCSSub
GDs [] ([Field
Label, Field
Units] forall a. [a] -> [a] -> [a]
++ Fields
stdFields) DerivationDisplay
ShowDerivation
, [Sentence] -> Fields -> DerivationDisplay -> SCSSub
DDs [] ([Field
Label, Field
Symbol, Field
Units] 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] forall a. [a] -> [a] -> [a]
++ Fields
stdFields) DerivationDisplay
ShowDerivation
, forall c.
(HasUncertainty c, Quantity c, Constrained c, HasReasVal c,
MayHaveUnit c) =>
Sentence -> [c] -> SCSSub
Constraints Sentence
dataContMid [UncertQ]
constrained
, forall c.
(Quantity c, Constrained c) =>
[c] -> [Contents] -> SCSSub
CorrSolnPpties [ConstrConcept]
dataConstListOut []
]
],
ReqrmntSec -> DocSection
ReqrmntSec forall a b. (a -> b) -> a -> b
$ [ReqsSub] -> ReqrmntSec
ReqsProg [
[LabelledContent] -> ReqsSub
FReqsSub' [LabelledContent
inputInitValsTable],
ReqsSub
NonFReqsSub
],
DocSection
LCsSec,
DocSection
UCsSec,
TraceabilitySec -> DocSection
TraceabilitySec forall a b. (a -> b) -> a -> b
$ [TraceConfig] -> TraceabilitySec
TraceabilityProg forall a b. (a -> b) -> a -> b
$ SystemInformation -> [TraceConfig]
traceMatStandard SystemInformation
si,
AuxConstntSec -> DocSection
AuxConstntSec forall a b. (a -> b) -> a -> b
$ CI -> [ConstQDef] -> AuxConstntSec
AuxConsProg CI
progName [ConstQDef]
specParamValList,
DocSection
Bibliography]
concIns :: [ConceptInstance]
concIns :: [ConceptInstance]
concIns = [ConceptInstance]
goals forall a. [a] -> [a] -> [a]
++ [ConceptInstance]
funcReqs forall a. [a] -> [a] -> [a]
++ [ConceptInstance]
nfRequirements forall a. [a] -> [a] -> [a]
++ [ConceptInstance]
assumptions forall a. [a] -> [a] -> [a]
++
[ConceptInstance
likeChgTCVOD, ConceptInstance
likeChgTCVOL] forall a. [a] -> [a] -> [a]
++ [ConceptInstance]
likelyChgs forall a. [a] -> [a] -> [a]
++ [ConceptInstance
likeChgTLH] forall a. [a] -> [a] -> [a]
++ [ConceptInstance]
unlikelyChgs
labCon :: [LabelledContent]
labCon :: [LabelledContent]
labCon = [LabelledContent
inputInitValsTable]
section :: [Section]
section :: [Section]
section = Document -> [Section]
extractSection Document
srs
stdFields :: Fields
stdFields :: Fields
stdFields = [Field
DefiningEquation, Verbosity -> InclUnits -> Field
Description Verbosity
Verbose InclUnits
IncludeUnits, Field
Notes, Field
Source, Field
RefBy]
si :: SystemInformation
si :: SystemInformation
si = SI {
_sys :: CI
_sys = CI
srsSWHS,
_kind :: CI
_kind = CI
Doc.srs,
_authors :: [Person]
_authors = [Person
thulasi],
_purpose :: [Sentence]
_purpose = [Sentence
purp],
_background :: [Sentence]
_background = [],
_quants :: [QuantityDict]
_quants = (forall a b. (a -> b) -> [a] -> [b]
map forall q. (Quantity q, MayHaveUnit q) => q -> QuantityDict
qw [UncertainChunk]
unconstrained forall a. [a] -> [a] -> [a]
++ forall a b. (a -> b) -> [a] -> [b]
map forall q. (Quantity q, MayHaveUnit q) => q -> QuantityDict
qw [QuantityDict]
symbolsAll) forall a. Eq a => [a] -> [a] -> [a]
\\ [forall q. (Quantity q, MayHaveUnit q) => q -> QuantityDict
qw UnitalChunk
tau],
_concepts :: [DefinedQuantityDict]
_concepts = [DefinedQuantityDict]
symbols,
_instModels :: [InstanceModel]
_instModels = [InstanceModel]
NoPCM.iMods,
_datadefs :: [DataDefinition]
_datadefs = [DataDefinition]
NoPCM.dataDefs,
_configFiles :: [String]
_configFiles = [],
_inputs :: [QuantityDict]
_inputs = [QuantityDict]
inputs forall a. [a] -> [a] -> [a]
++ [forall q. (Quantity q, MayHaveUnit q) => q -> QuantityDict
qw ConstrConcept
watE],
_outputs :: [QuantityDict]
_outputs = forall a b. (a -> b) -> [a] -> [b]
map forall q. (Quantity q, MayHaveUnit q) => q -> QuantityDict
qw [ConstrConcept
tempW, ConstrConcept
watE],
_defSequence :: [Block SimpleQDef]
_defSequence = [(\[SimpleQDef]
x -> forall a. a -> [a] -> Block a
Parallel (forall a. [a] -> a
head [SimpleQDef]
x) (forall a. [a] -> [a]
tail [SimpleQDef]
x)) [SimpleQDef]
qDefs],
_constraints :: [ConstrainedChunk]
_constraints = forall a b. (a -> b) -> [a] -> [b]
map forall c.
(Quantity c, Constrained c, HasReasVal c, MayHaveUnit c) =>
c -> ConstrainedChunk
cnstrw [UncertQ]
constrained forall a. [a] -> [a] -> [a]
++ forall a b. (a -> b) -> [a] -> [b]
map forall c.
(Quantity c, Constrained c, HasReasVal c, MayHaveUnit c) =>
c -> ConstrainedChunk
cnstrw [ConstrConcept
tempW, ConstrConcept
watE],
_constants :: [ConstQDef]
_constants = ConstQDef
piConst forall a. a -> [a] -> [a]
: [ConstQDef]
specParamValList,
_sysinfodb :: ChunkDB
_sysinfodb = ChunkDB
symbMap,
_usedinfodb :: ChunkDB
_usedinfodb = ChunkDB
usedDB,
refdb :: ReferenceDB
refdb = ReferenceDB
refDB
}
progName :: CI
progName :: CI
progName = String -> NP -> String -> [IdeaDict] -> CI
commonIdeaWithDict String
"swhsNoPCM"
(String -> String -> CapitalizationRule -> NP
nounPhrase' String
"solar water heating system with no phase change material"
String
"solar water heating systems with no phase change material" forall a b. (a -> b) -> a -> b
$ Sentence -> CapitalizationRule
Replace forall a b. (a -> b) -> a -> b
$
String -> Sentence
S String
"Solar Water Heating System with no Phase Change Material") String
"SWHSNoPCM" [IdeaDict
materialEng]
purp :: Sentence
purp :: Sentence
purp = [Sentence] -> Sentence
foldlSent_ [String -> Sentence
S String
"investigate the heating" Sentence -> Sentence -> Sentence
`S.of_` forall n. NounPhrase n => n -> Sentence
phraseNP (ConceptChunk
water forall c d. (NamedIdea c, NamedIdea d) => c -> d -> NP
`inA` ConceptChunk
sWHT)]
refDB :: ReferenceDB
refDB :: ReferenceDB
refDB = BibRef -> [ConceptInstance] -> ReferenceDB
rdb BibRef
citations [ConceptInstance]
concIns
symbMap :: ChunkDB
symbMap :: ChunkDB
symbMap = forall q t c u.
(Quantity q, MayHaveUnit q, Idea t, Concept c, IsUnit u) =>
[q]
-> [t]
-> [c]
-> [u]
-> [DataDefinition]
-> [InstanceModel]
-> [GenDefn]
-> [TheoryModel]
-> [ConceptInstance]
-> [Section]
-> [LabelledContent]
-> [Reference]
-> ChunkDB
cdb [QuantityDict]
symbolsAll (forall c. Idea c => c -> IdeaDict
nw CI
progName forall a. a -> [a] -> [a]
: forall a b. (a -> b) -> [a] -> [b]
map forall c. Idea c => c -> IdeaDict
nw [DefinedQuantityDict]
symbols forall a. [a] -> [a] -> [a]
++ forall a b. (a -> b) -> [a] -> [b]
map forall c. Idea c => c -> IdeaDict
nw [CI]
acronyms forall a. [a] -> [a] -> [a]
++ forall a b. (a -> b) -> [a] -> [b]
map forall c. Idea c => c -> IdeaDict
nw [ConceptChunk]
thermocon
forall a. [a] -> [a] -> [a]
++ forall a b. (a -> b) -> [a] -> [b]
map forall c. Idea c => c -> IdeaDict
nw [UnitalChunk]
physicscon forall a. [a] -> [a] -> [a]
++ forall a b. (a -> b) -> [a] -> [b]
map forall c. Idea c => c -> IdeaDict
nw [IdeaDict]
doccon forall a. [a] -> [a] -> [a]
++ forall a b. (a -> b) -> [a] -> [b]
map forall c. Idea c => c -> IdeaDict
nw [ConceptChunk]
softwarecon forall a. [a] -> [a] -> [a]
++ forall a b. (a -> b) -> [a] -> [b]
map forall c. Idea c => c -> IdeaDict
nw [CI]
doccon' forall a. [a] -> [a] -> [a]
++ forall a b. (a -> b) -> [a] -> [b]
map forall c. Idea c => c -> IdeaDict
nw [ConceptChunk]
con
forall a. [a] -> [a] -> [a]
++ forall a b. (a -> b) -> [a] -> [b]
map forall c. Idea c => c -> IdeaDict
nw [IdeaDict]
prodtcon forall a. [a] -> [a] -> [a]
++ forall a b. (a -> b) -> [a] -> [b]
map forall c. Idea c => c -> IdeaDict
nw [ConceptChunk]
physicCon forall a. [a] -> [a] -> [a]
++ forall a b. (a -> b) -> [a] -> [b]
map forall c. Idea c => c -> IdeaDict
nw [CI]
physicCon' forall a. [a] -> [a] -> [a]
++ forall a b. (a -> b) -> [a] -> [b]
map forall c. Idea c => c -> IdeaDict
nw [ConceptChunk]
mathcon forall a. [a] -> [a] -> [a]
++ forall a b. (a -> b) -> [a] -> [b]
map forall c. Idea c => c -> IdeaDict
nw [CI]
mathcon'
forall a. [a] -> [a] -> [a]
++ forall a b. (a -> b) -> [a] -> [b]
map forall c. Idea c => c -> IdeaDict
nw [ConstQDef]
specParamValList forall a. [a] -> [a] -> [a]
++ forall a b. (a -> b) -> [a] -> [b]
map forall c. Idea c => c -> IdeaDict
nw [UnitDefn]
fundamentals forall a. [a] -> [a] -> [a]
++ forall a b. (a -> b) -> [a] -> [b]
map forall c. Idea c => c -> IdeaDict
nw [IdeaDict]
educon forall a. [a] -> [a] -> [a]
++ forall a b. (a -> b) -> [a] -> [b]
map forall c. Idea c => c -> IdeaDict
nw [UnitDefn]
derived
forall a. [a] -> [a] -> [a]
++ forall a b. (a -> b) -> [a] -> [b]
map forall c. Idea c => c -> IdeaDict
nw [ConceptChunk]
physicalcon forall a. [a] -> [a] -> [a]
++ forall a b. (a -> b) -> [a] -> [b]
map forall c. Idea c => c -> IdeaDict
nw [UnitalChunk]
unitalChuncks forall a. [a] -> [a] -> [a]
++ forall a b. (a -> b) -> [a] -> [b]
map forall c. Idea c => c -> IdeaDict
nw [UncertainChunk
absTol, UncertainChunk
relTol]
forall a. [a] -> [a] -> [a]
++ [forall c. Idea c => c -> IdeaDict
nw CI
srsSWHS, forall c. Idea c => c -> IdeaDict
nw ConceptChunk
algorithm, forall c. Idea c => c -> IdeaDict
nw IdeaDict
inValue, forall c. Idea c => c -> IdeaDict
nw IdeaDict
htTrans, forall c. Idea c => c -> IdeaDict
nw IdeaDict
materialProprty, forall c. Idea c => c -> IdeaDict
nw CI
phsChgMtrl])
(forall a b. (a -> b) -> [a] -> [b]
map forall c. Concept c => c -> ConceptChunk
cw [DefinedQuantityDict]
symbols forall a. [a] -> [a] -> [a]
++ [ConceptChunk]
srsDomains) [UnitDefn]
units [DataDefinition]
NoPCM.dataDefs [InstanceModel]
NoPCM.iMods [GenDefn]
genDefs
[TheoryModel]
tMods [ConceptInstance]
concIns [Section]
section [LabelledContent]
labCon []
usedDB :: ChunkDB
usedDB :: ChunkDB
usedDB = forall q t c u.
(Quantity q, MayHaveUnit q, Idea t, Concept c, IsUnit u) =>
[q]
-> [t]
-> [c]
-> [u]
-> [DataDefinition]
-> [InstanceModel]
-> [GenDefn]
-> [TheoryModel]
-> [ConceptInstance]
-> [Section]
-> [LabelledContent]
-> [Reference]
-> ChunkDB
cdb ([] :: [QuantityDict]) (forall c. Idea c => c -> IdeaDict
nw CI
progName forall a. a -> [a] -> [a]
: forall a b. (a -> b) -> [a] -> [b]
map forall c. Idea c => c -> IdeaDict
nw [DefinedQuantityDict]
symbols forall a. [a] -> [a] -> [a]
++ forall a b. (a -> b) -> [a] -> [b]
map forall c. Idea c => c -> IdeaDict
nw [CI]
acronyms)
([] :: [ConceptChunk]) ([] :: [UnitDefn]) [] [] [] [] [] [] [] ([] :: [Reference])
introStartNoPCM :: Sentence
introStartNoPCM :: Sentence
introStartNoPCM = 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
+:+. forall n. NamedIdea n => n -> Sentence
phrase UnitalChunk
energy
scope :: Sentence
scope :: Sentence
scope = forall n. NamedIdea n => n -> Sentence
phrase ConceptChunk
thermalAnalysis Sentence -> Sentence -> Sentence
`S.of_` String -> Sentence
S String
"a single" Sentence -> Sentence -> Sentence
+:+ forall n. NamedIdea n => n -> Sentence
phrase ConceptChunk
sWHT
orgDocEnd :: Sentence
orgDocEnd :: Sentence
orgDocEnd = [Sentence] -> Sentence
foldlSent_ [forall n. NounPhrase n => n -> Sentence
atStartNP (forall t. NamedIdea t => t -> NP
the CI
inModel),
String -> Sentence
S String
"to be solved is referred to as" Sentence -> Sentence -> Sentence
+:+. forall r.
(HasUID r, HasRefAddress r, HasShortName r) =>
r -> Sentence
refS InstanceModel
eBalanceOnWtr,
forall n. NounPhrase n => n -> Sentence
atStartNP (forall t. NamedIdea t => t -> NP
the CI
inModel), String -> Sentence
S String
"provides the", forall n. NamedIdea n => n -> Sentence
titleize CI
ode,
Sentence -> Sentence
sParen (forall c. Idea c => c -> Sentence
short CI
ode), String -> Sentence
S String
"that models the" Sentence -> Sentence -> Sentence
+:+. forall n. NamedIdea n => n -> Sentence
phrase CI
progName,
forall c. Idea c => c -> Sentence
short CI
progName, String -> Sentence
S String
"solves this", forall c. Idea c => c -> Sentence
short CI
ode]
sysCntxtFig :: LabelledContent
sysCntxtFig :: LabelledContent
sysCntxtFig = Reference -> RawContent -> LabelledContent
llcc (String -> Reference
makeFigRef String
"SysCon") forall a b. (a -> b) -> a -> b
$ Sentence -> String -> RawContent
fig ([Sentence] -> Sentence
foldlSent_
[forall r.
(HasUID r, HasRefAddress r, HasShortName r) =>
r -> Sentence
refS LabelledContent
sysCntxtFig Sentence -> Sentence -> Sentence
+: Sentence
EmptyS, forall n. NamedIdea n => n -> Sentence
titleize IdeaDict
sysCont])
forall a b. (a -> b) -> a -> b
$ String
resourcePath forall a. [a] -> [a] -> [a]
++ String
"SystemContextFigure.png"
terms :: [ConceptChunk]
terms :: [ConceptChunk]
terms = [ConceptChunk
htFlux, ConceptChunk
heatCapSpec, ConceptChunk
thermalConduction, ConceptChunk
transient]
figTank :: LabelledContent
figTank :: LabelledContent
figTank = Reference -> RawContent -> LabelledContent
llcc (String -> Reference
makeFigRef String
"Tank") forall a b. (a -> b) -> a -> b
$ Sentence -> String -> RawContent
fig (forall n. NamedIdea n => n -> Sentence
atStart ConceptChunk
sWHT Sentence -> Sentence -> Sentence
`sC` String -> Sentence
S String
"with" Sentence -> Sentence -> Sentence
+:+ forall n. NamedIdea n => n -> Sentence
phrase ConceptChunk
htFlux Sentence -> Sentence -> Sentence
+:+
String -> Sentence
S String
"from" Sentence -> Sentence -> Sentence
+:+ forall n. NamedIdea n => n -> Sentence
phrase ConceptChunk
coil Sentence -> Sentence -> Sentence
`S.of_` forall c. (HasUID c, HasSymbol c) => c -> Sentence
ch UnitalChunk
htFluxC)
forall a b. (a -> b) -> a -> b
$ String
resourcePath forall a. [a] -> [a] -> [a]
++ String
"TankWaterOnly.png"
physSystParts :: [Sentence]
physSystParts :: [Sentence]
physSystParts = 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 = [forall n. NounPhrase n => n -> Sentence
phraseNP (ConceptChunk
temp forall c d. (NamedIdea c, NamedIdea d) => c -> d -> NP
`the_ofThe` ConceptChunk
coil),
String -> Sentence
S String
"the initial" Sentence -> Sentence -> Sentence
+:+ forall n. NamedIdea n => n -> Sentence
phrase ConstrConcept
tempW, forall n. NounPhrase n => n -> Sentence
pluralNP (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 [forall c. (HasUID c, HasSymbol c) => c -> Sentence
ch UnitalChunk
QT.sensHeat, String -> Sentence
S String
"occurs as long as the", forall n. NamedIdea n => n -> Sentence
phrase IdeaDict
material_, String -> Sentence
S String
"does not reach a",
forall n. NamedIdea n => n -> Sentence
phrase ConceptChunk
temp, String -> Sentence
S String
"where a", 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", forall r.
(HasUID r, HasRefAddress r, HasShortName r) =>
r -> Sentence
refS ConceptInstance
assumpWAL]
dataConstListOut :: [ConstrConcept]
dataConstListOut :: [ConstrConcept]
dataConstListOut = [ConstrConcept
tempW, ConstrConcept
watE]