{-# LANGUAGE PostfixOperators #-}
module Drasil.SWHS.Body where
import Language.Drasil hiding (organization, section, variable)
import Drasil.SRSDocument
import qualified Drasil.DocLang.SRS as SRS (inModel)
import Theory.Drasil (GenDefn, InstanceModel)
import Language.Drasil.Chunk.Concept.NamedCombinators
import qualified Language.Drasil.NounPhrase.Combinators as NP
import qualified Language.Drasil.Sentence.Combinators as S
import Control.Lens ((^.))
import qualified Data.Drasil.Concepts.Documentation as Doc (srs)
import Data.Drasil.TheoryConcepts as Doc (inModel)
import Data.Drasil.Concepts.Computation (algorithm, compcon)
import Data.Drasil.Concepts.Documentation as Doc (assumption, column, condition,
constraint, corSol, datum, document, environment,input_, model, organization,
output_, physical, physics, property, quantity, software, softwareSys, solution,
srsDomains, sysCont, system, user, value, variable, doccon, doccon')
import Data.Drasil.Concepts.Education (calculus, educon, engineering)
import Data.Drasil.Concepts.Math (de, equation, ode, rightSide, unit_, mathcon, mathcon')
import Data.Drasil.Concepts.PhysicalProperties (materialProprty, physicalcon)
import Data.Drasil.Concepts.Physics (physicCon)
import Data.Drasil.Concepts.Software (program, softwarecon, correctness,
understandability, reusability, maintainability, verifiability)
import Data.Drasil.Concepts.Thermodynamics (enerSrc, heatTrans, htFlux,
htTransTheo, lawConsEnergy, thermalAnalysis, thermalConduction, thermalEnergy,
thermocon)
import Data.Drasil.Quantities.Math (surArea, surface, uNormalVect)
import Data.Drasil.Quantities.PhysicalProperties (vol)
import Data.Drasil.Quantities.Physics (energy, time, physicscon)
import Data.Drasil.Quantities.Thermodynamics (heatCapSpec, latentHeat)
import Data.Drasil.Software.Products (sciCompS, prodtcon)
import Data.Drasil.People (brooks, spencerSmith, thulasi)
import Data.Drasil.SI_Units (metre, kilogram, second, centigrade, joule, watt,
fundamentals, derived, m_2, m_3)
import Drasil.SWHS.Assumptions (assumpPIS, assumptions)
import Drasil.SWHS.Changes (likelyChgs, unlikelyChgs)
import Drasil.SWHS.Concepts (acronymsFull, coil, con, phaseChangeMaterial,
phsChgMtrl, progName, sWHT, swhsPCM, tank, tankPCM, transient, water)
import qualified Drasil.SWHS.DataDefs as SWHS (dataDefs)
import Drasil.SWHS.GenDefs (genDefs, htFluxWaterFromCoil, htFluxPCMFromWater)
import Drasil.SWHS.Goals (goals)
import Drasil.SWHS.IMods (eBalanceOnWtr, eBalanceOnPCM, heatEInWtr, heatEInPCM,
iMods, instModIntro)
import Drasil.SWHS.References (citations, koothoor2013, smithLai2005)
import Drasil.SWHS.Requirements (funcReqs, inReqDesc, nfRequirements, verifyEnergyOutput)
import Drasil.SWHS.TMods (tMods)
import Drasil.SWHS.Unitals (absTol, coilHTC, coilSA, consTol, constrained,
htFluxC, htFluxP, inputs, inputConstraints, outputs, pcmE, pcmHTC, pcmSA,
relTol, simTime, specParamValList, symbols, symbolsAll, tempC, tempPCM,
tempW, thickness, unitalChuncks, watE)
srs :: Document
srs :: Document
srs = SRSDecl
-> (IdeaDict -> IdeaDict -> Sentence)
-> SystemInformation
-> Document
mkDoc SRSDecl
mkSRS IdeaDict -> IdeaDict -> Sentence
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 = "../../../../datafiles/swhs/"
units :: [UnitDefn]
units :: [UnitDefn]
units = (UnitDefn -> UnitDefn) -> [UnitDefn] -> [UnitDefn]
forall a b. (a -> b) -> [a] -> [b]
map UnitDefn -> UnitDefn
forall u. IsUnit u => u -> UnitDefn
unitWrapper [UnitDefn
metre, UnitDefn
kilogram, UnitDefn
second] [UnitDefn] -> [UnitDefn] -> [UnitDefn]
forall a. [a] -> [a] -> [a]
++
(UnitDefn -> UnitDefn) -> [UnitDefn] -> [UnitDefn]
forall a b. (a -> b) -> [a] -> [b]
map UnitDefn -> UnitDefn
forall u. IsUnit u => u -> UnitDefn
unitWrapper [UnitDefn
centigrade, UnitDefn
joule, UnitDefn
watt]
si :: SystemInformation
si :: SystemInformation
si = SI :: forall a b c e f h i j d.
(CommonIdea a, Idea a, Idea b, HasName c, Quantity e, Eq e,
MayHaveUnit e, Quantity f, MayHaveUnit f, Concept f, Eq f,
Quantity h, MayHaveUnit h, Quantity i, MayHaveUnit i, HasUID j,
Constrained j) =>
a
-> b
-> [c]
-> d
-> [e]
-> [f]
-> [InstanceModel]
-> [DataDefinition]
-> [String]
-> [h]
-> [i]
-> [Block SimpleQDef]
-> [j]
-> [ConstQDef]
-> ChunkDB
-> ChunkDB
-> ReferenceDB
-> SystemInformation
SI {
_sys :: CommonConcept
_sys = CommonConcept
swhsPCM,
_kind :: CI
_kind = CI
Doc.srs,
_authors :: [Person]
_authors = [Person
thulasi, Person
brooks, Person
spencerSmith],
_purpose :: [Sentence]
_purpose = CI -> Verbosity -> [Sentence]
purpDoc CI
progName Verbosity
Verbose,
_quants :: [DefinedQuantityDict]
_quants = [DefinedQuantityDict]
symbols,
_concepts :: [DefinedQuantityDict]
_concepts = [] :: [DefinedQuantityDict],
_instModels :: [InstanceModel]
_instModels = [],
_datadefs :: [DataDefinition]
_datadefs = [DataDefinition]
SWHS.dataDefs,
_configFiles :: [String]
_configFiles = [],
_inputs :: [QuantityDict]
_inputs = [QuantityDict]
inputs,
_outputs :: [QuantityDict]
_outputs = (ConstrConcept -> QuantityDict)
-> [ConstrConcept] -> [QuantityDict]
forall a b. (a -> b) -> [a] -> [b]
map ConstrConcept -> QuantityDict
forall q. (Quantity q, MayHaveUnit q) => q -> QuantityDict
qw [ConstrConcept]
outputs,
_defSequence :: [Block SimpleQDef]
_defSequence = [] :: [Block SimpleQDef],
_constraints :: [ConstrConcept]
_constraints = [ConstrConcept]
constrained,
_constants :: [ConstQDef]
_constants = [ConstQDef]
specParamValList,
_sysinfodb :: ChunkDB
_sysinfodb = ChunkDB
symbMap,
_usedinfodb :: ChunkDB
_usedinfodb = ChunkDB
usedDB,
refdb :: ReferenceDB
refdb = ReferenceDB
refDB
}
symbMap :: ChunkDB
symbMap :: ChunkDB
symbMap = [QuantityDict]
-> [IdeaDict]
-> [ConceptChunk]
-> [UnitDefn]
-> [DataDefinition]
-> [InstanceModel]
-> [GenDefn]
-> [TheoryModel]
-> [ConceptInstance]
-> [Section]
-> [LabelledContent]
-> [Reference]
-> ChunkDB
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 (InstanceModel -> QuantityDict
forall q. (Quantity q, MayHaveUnit q) => q -> QuantityDict
qw InstanceModel
heatEInPCM QuantityDict -> [QuantityDict] -> [QuantityDict]
forall a. a -> [a] -> [a]
: [QuantityDict]
symbolsAll)
(InstanceModel -> IdeaDict
forall c. Idea c => c -> IdeaDict
nw InstanceModel
heatEInPCM 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 [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]
acronymsFull
[IdeaDict] -> [IdeaDict] -> [IdeaDict]
forall a. [a] -> [a] -> [a]
++ (ConceptChunk -> IdeaDict) -> [ConceptChunk] -> [IdeaDict]
forall a b. (a -> b) -> [a] -> [b]
map ConceptChunk -> IdeaDict
forall c. Idea c => c -> IdeaDict
nw [ConceptChunk]
thermocon [IdeaDict] -> [IdeaDict] -> [IdeaDict]
forall a. [a] -> [a] -> [a]
++ (UnitDefn -> IdeaDict) -> [UnitDefn] -> [IdeaDict]
forall a b. (a -> b) -> [a] -> [b]
map UnitDefn -> IdeaDict
forall c. Idea c => c -> IdeaDict
nw [UnitDefn]
units [IdeaDict] -> [IdeaDict] -> [IdeaDict]
forall a. [a] -> [a] -> [a]
++ (UnitDefn -> IdeaDict) -> [UnitDefn] -> [IdeaDict]
forall a b. (a -> b) -> [a] -> [b]
map UnitDefn -> IdeaDict
forall c. Idea c => c -> IdeaDict
nw [UnitDefn
m_2, UnitDefn
m_3] [IdeaDict] -> [IdeaDict] -> [IdeaDict]
forall a. [a] -> [a] -> [a]
++ (UncertainChunk -> IdeaDict) -> [UncertainChunk] -> [IdeaDict]
forall a b. (a -> b) -> [a] -> [b]
map UncertainChunk -> IdeaDict
forall c. Idea c => c -> IdeaDict
nw [UncertainChunk
absTol, UncertainChunk
relTol]
[IdeaDict] -> [IdeaDict] -> [IdeaDict]
forall a. [a] -> [a] -> [a]
++ (UnitalChunk -> IdeaDict) -> [UnitalChunk] -> [IdeaDict]
forall a b. (a -> b) -> [a] -> [b]
map UnitalChunk -> IdeaDict
forall c. Idea c => c -> IdeaDict
nw [UnitalChunk]
physicscon [IdeaDict] -> [IdeaDict] -> [IdeaDict]
forall a. [a] -> [a] -> [a]
++ (NamedChunk -> IdeaDict) -> [NamedChunk] -> [IdeaDict]
forall a b. (a -> b) -> [a] -> [b]
map NamedChunk -> IdeaDict
forall c. Idea c => c -> IdeaDict
nw [NamedChunk]
doccon [IdeaDict] -> [IdeaDict] -> [IdeaDict]
forall a. [a] -> [a] -> [a]
++ (ConceptChunk -> IdeaDict) -> [ConceptChunk] -> [IdeaDict]
forall a b. (a -> b) -> [a] -> [b]
map ConceptChunk -> IdeaDict
forall c. Idea c => c -> IdeaDict
nw [ConceptChunk]
softwarecon [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]
doccon' [IdeaDict] -> [IdeaDict] -> [IdeaDict]
forall a. [a] -> [a] -> [a]
++ (ConceptChunk -> IdeaDict) -> [ConceptChunk] -> [IdeaDict]
forall a b. (a -> b) -> [a] -> [b]
map ConceptChunk -> IdeaDict
forall c. Idea c => c -> IdeaDict
nw [ConceptChunk]
con
[IdeaDict] -> [IdeaDict] -> [IdeaDict]
forall a. [a] -> [a] -> [a]
++ (NamedChunk -> IdeaDict) -> [NamedChunk] -> [IdeaDict]
forall a b. (a -> b) -> [a] -> [b]
map NamedChunk -> IdeaDict
forall c. Idea c => c -> IdeaDict
nw [NamedChunk]
prodtcon [IdeaDict] -> [IdeaDict] -> [IdeaDict]
forall a. [a] -> [a] -> [a]
++ (ConceptChunk -> IdeaDict) -> [ConceptChunk] -> [IdeaDict]
forall a b. (a -> b) -> [a] -> [b]
map ConceptChunk -> IdeaDict
forall c. Idea c => c -> IdeaDict
nw [ConceptChunk]
physicCon [IdeaDict] -> [IdeaDict] -> [IdeaDict]
forall a. [a] -> [a] -> [a]
++ (ConceptChunk -> IdeaDict) -> [ConceptChunk] -> [IdeaDict]
forall a b. (a -> b) -> [a] -> [b]
map ConceptChunk -> IdeaDict
forall c. Idea c => c -> IdeaDict
nw [ConceptChunk]
mathcon [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' [IdeaDict] -> [IdeaDict] -> [IdeaDict]
forall a. [a] -> [a] -> [a]
++ (ConstQDef -> IdeaDict) -> [ConstQDef] -> [IdeaDict]
forall a b. (a -> b) -> [a] -> [b]
map ConstQDef -> IdeaDict
forall c. Idea c => c -> IdeaDict
nw [ConstQDef]
specParamValList
[IdeaDict] -> [IdeaDict] -> [IdeaDict]
forall a. [a] -> [a] -> [a]
++ (UnitDefn -> IdeaDict) -> [UnitDefn] -> [IdeaDict]
forall a b. (a -> b) -> [a] -> [b]
map UnitDefn -> IdeaDict
forall c. Idea c => c -> IdeaDict
nw [UnitDefn]
fundamentals [IdeaDict] -> [IdeaDict] -> [IdeaDict]
forall a. [a] -> [a] -> [a]
++ (NamedChunk -> IdeaDict) -> [NamedChunk] -> [IdeaDict]
forall a b. (a -> b) -> [a] -> [b]
map NamedChunk -> IdeaDict
forall c. Idea c => c -> IdeaDict
nw [NamedChunk]
educon [IdeaDict] -> [IdeaDict] -> [IdeaDict]
forall a. [a] -> [a] -> [a]
++ (UnitDefn -> IdeaDict) -> [UnitDefn] -> [IdeaDict]
forall a b. (a -> b) -> [a] -> [b]
map UnitDefn -> IdeaDict
forall c. Idea c => c -> IdeaDict
nw [UnitDefn]
derived [IdeaDict] -> [IdeaDict] -> [IdeaDict]
forall a. [a] -> [a] -> [a]
++ (ConceptChunk -> IdeaDict) -> [ConceptChunk] -> [IdeaDict]
forall a b. (a -> b) -> [a] -> [b]
map ConceptChunk -> IdeaDict
forall c. Idea c => c -> IdeaDict
nw [ConceptChunk]
physicalcon [IdeaDict] -> [IdeaDict] -> [IdeaDict]
forall a. [a] -> [a] -> [a]
++ (UnitalChunk -> IdeaDict) -> [UnitalChunk] -> [IdeaDict]
forall a b. (a -> b) -> [a] -> [b]
map UnitalChunk -> IdeaDict
forall c. Idea c => c -> IdeaDict
nw [UnitalChunk]
unitalChuncks
[IdeaDict] -> [IdeaDict] -> [IdeaDict]
forall a. [a] -> [a] -> [a]
++ [CommonConcept -> IdeaDict
forall c. Idea c => c -> IdeaDict
nw CommonConcept
swhsPCM, ConceptChunk -> IdeaDict
forall c. Idea c => c -> IdeaDict
nw ConceptChunk
algorithm] [IdeaDict] -> [IdeaDict] -> [IdeaDict]
forall a. [a] -> [a] -> [a]
++ (NamedChunk -> IdeaDict) -> [NamedChunk] -> [IdeaDict]
forall a b. (a -> b) -> [a] -> [b]
map NamedChunk -> IdeaDict
forall c. Idea c => c -> IdeaDict
nw [NamedChunk]
compcon [IdeaDict] -> [IdeaDict] -> [IdeaDict]
forall a. [a] -> [a] -> [a]
++ [NamedChunk -> IdeaDict
forall c. Idea c => c -> IdeaDict
nw NamedChunk
materialProprty])
(InstanceModel -> ConceptChunk
forall c. Concept c => c -> ConceptChunk
cw InstanceModel
heatEInPCM ConceptChunk -> [ConceptChunk] -> [ConceptChunk]
forall a. a -> [a] -> [a]
: (DefinedQuantityDict -> ConceptChunk)
-> [DefinedQuantityDict] -> [ConceptChunk]
forall a b. (a -> b) -> [a] -> [b]
map DefinedQuantityDict -> ConceptChunk
forall c. Concept c => c -> ConceptChunk
cw [DefinedQuantityDict]
symbols [ConceptChunk] -> [ConceptChunk] -> [ConceptChunk]
forall a. [a] -> [a] -> [a]
++ [ConceptChunk]
srsDomains [ConceptChunk] -> [ConceptChunk] -> [ConceptChunk]
forall a. [a] -> [a] -> [a]
++ (ConstQDef -> ConceptChunk) -> [ConstQDef] -> [ConceptChunk]
forall a b. (a -> b) -> [a] -> [b]
map ConstQDef -> ConceptChunk
forall c. Concept c => c -> ConceptChunk
cw [ConstQDef]
specParamValList)
([UnitDefn]
units [UnitDefn] -> [UnitDefn] -> [UnitDefn]
forall a. [a] -> [a] -> [a]
++ [UnitDefn
m_2, UnitDefn
m_3]) [DataDefinition]
SWHS.dataDefs [InstanceModel]
insModel [GenDefn]
genDefs [TheoryModel]
tMods [ConceptInstance]
concIns [Section]
section [] []
usedDB :: ChunkDB
usedDB :: ChunkDB
usedDB = [QuantityDict]
-> [IdeaDict]
-> [ConceptChunk]
-> [UnitDefn]
-> [DataDefinition]
-> [InstanceModel]
-> [GenDefn]
-> [TheoryModel]
-> [ConceptInstance]
-> [Section]
-> [LabelledContent]
-> [Reference]
-> ChunkDB
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]) ((DefinedQuantityDict -> IdeaDict)
-> [DefinedQuantityDict] -> [IdeaDict]
forall a b. (a -> b) -> [a] -> [b]
map DefinedQuantityDict -> IdeaDict
forall c. Idea c => c -> IdeaDict
nw [DefinedQuantityDict]
symbols [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]
acronymsFull)
([] :: [ConceptChunk]) ([] :: [UnitDefn]) [] [] [] [] [] [] [] ([] :: [Reference])
refDB :: ReferenceDB
refDB :: ReferenceDB
refDB = BibRef -> [ConceptInstance] -> ReferenceDB
rdb BibRef
citations [ConceptInstance]
concIns
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] -> LFunc -> RefTab
tsymb'' [TSIntro]
tSymbIntro (LFunc -> RefTab) -> LFunc -> RefTab
forall a b. (a -> b) -> a -> b
$ [DefinedQuantityDict] -> LFunc
TermExcept [DefinedQuantityDict
uNormalVect],
RefTab
TAandA],
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
introStartSWHS) (Sentence -> CI -> Sentence
introEnd (CommonConcept -> Sentence
forall n. (HasUID n, NamedIdea n) => n -> Sentence
plural CommonConcept
swhsPCM) 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 [],
Sentence -> CI -> Section -> Sentence -> IntroSub
IOrgSec Sentence
orgDocIntro 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, Contents
systContRespBullets]
, [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
probDescIntro []
[ 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
dataConTail [UncertQ]
inputConstraints
, [ConstrConcept] -> [Contents] -> SCSSub
forall c.
(Quantity c, Constrained c) =>
[c] -> [Contents] -> SCSSub
CorrSolnPpties [ConstrConcept]
outputConstraints [Contents]
propsDeriv
]
],
ReqrmntSec -> DocSection
ReqrmntSec (ReqrmntSec -> DocSection) -> ReqrmntSec -> DocSection
forall a b. (a -> b) -> a -> b
$ [ReqsSub] -> ReqrmntSec
ReqsProg [
Sentence -> [LabelledContent] -> ReqsSub
FReqsSub Sentence
inReqDesc [],
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
$ SystemInformation -> [TraceConfig]
traceMatStandard SystemInformation
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]
tSymbIntro :: [TSIntro]
tSymbIntro :: [TSIntro]
tSymbIntro = [TSIntro
TSPurpose, [Literature] -> TSIntro
SymbConvention
[IdeaDict -> Literature
Lit (ConceptChunk -> IdeaDict
forall c. Idea c => c -> IdeaDict
nw ConceptChunk
heatTrans), IdeaDict -> Literature
Doc' (CI -> IdeaDict
forall c. Idea c => c -> IdeaDict
nw CI
progName)], TSIntro
SymbOrder, TSIntro
VectorUnits]
insModel :: [InstanceModel]
insModel :: [InstanceModel]
insModel = [InstanceModel
eBalanceOnWtr, InstanceModel
eBalanceOnPCM, InstanceModel
heatEInWtr, InstanceModel
heatEInPCM]
concIns :: [ConceptInstance]
concIns :: [ConceptInstance]
concIns = [ConceptInstance]
goals [ConceptInstance] -> [ConceptInstance] -> [ConceptInstance]
forall a. [a] -> [a] -> [a]
++ [ConceptInstance]
assumptions [ConceptInstance] -> [ConceptInstance] -> [ConceptInstance]
forall a. [a] -> [a] -> [a]
++ [ConceptInstance]
likelyChgs [ConceptInstance] -> [ConceptInstance] -> [ConceptInstance]
forall a. [a] -> [a] -> [a]
++ [ConceptInstance]
unlikelyChgs [ConceptInstance] -> [ConceptInstance] -> [ConceptInstance]
forall a. [a] -> [a] -> [a]
++ [ConceptInstance]
funcReqs
[ConceptInstance] -> [ConceptInstance] -> [ConceptInstance]
forall a. [a] -> [a] -> [a]
++ [ConceptInstance]
nfRequirements
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]
priorityNFReqs :: [ConceptChunk]
priorityNFReqs :: [ConceptChunk]
priorityNFReqs = [ConceptChunk
correctness, ConceptChunk
verifiability, ConceptChunk
understandability, ConceptChunk
reusability,
ConceptChunk
maintainability]
introStart :: Sentence
introStart :: Sentence
introStart = [Sentence] -> Sentence
foldlSent [String -> Sentence
S "Due to", SepType -> FoldType -> [Sentence] -> Sentence
foldlList SepType
Comma FoldType
List ((String -> Sentence) -> [String] -> [Sentence]
forall a b. (a -> b) -> [a] -> [b]
map String -> Sentence
S
["increasing costs", "diminishing availability", "negative environmental impact"]) Sentence -> Sentence -> Sentence
`S.of_`
String -> Sentence
S "fossil fuels" Sentence -> Sentence -> Sentence
`sC` String -> Sentence
S "the demand is high for renewable", NP -> Sentence
forall n. NounPhrase n => n -> Sentence
pluralNP (ConceptChunk
enerSrc ConceptChunk -> UnitalChunk -> NP
forall c d. (NamedIdea c, NamedIdea d) => c -> d -> NP
`and_PS`
UnitalChunk
energy), String -> Sentence
S "storage technology"]
introStartSWHS :: Sentence
introStartSWHS :: Sentence
introStartSWHS = [Sentence] -> Sentence
foldlSent [Sentence -> Sentence
capSent (CommonConcept
swhsPCM CommonConcept
-> Getting Sentence CommonConcept Sentence -> Sentence
forall s a. s -> Getting a s a -> a
^. Getting Sentence CommonConcept Sentence
forall c. Definition c => Lens' c Sentence
defn), Sentence -> Sentence
sParen (CI -> Sentence
forall c. (Idea c, HasUID c) => c -> Sentence
short CI
phsChgMtrl),
String -> Sentence
S "use a renewable", ConceptChunk -> Sentence
forall n. (HasUID n, NamedIdea n) => n -> Sentence
phrase ConceptChunk
enerSrc Sentence -> Sentence -> Sentence
`S.and_` String -> Sentence
S "provide a novel way of storing" Sentence -> Sentence -> Sentence
+:+.
UnitalChunk -> Sentence
forall n. (HasUID n, NamedIdea n) => n -> Sentence
phrase UnitalChunk
energy, CommonConcept -> Sentence
forall n. NamedIdea n => n -> Sentence
atStart CommonConcept
swhsPCM, String -> Sentence
S "improve over the traditional", CI -> Sentence
forall n. (HasUID n, NamedIdea n) => n -> Sentence
plural CI
progName,
String -> Sentence
S "because of their smaller size. The smaller size is possible because of the ability" Sentence -> Sentence -> Sentence
`S.of_`
CI -> Sentence
forall c. (Idea c, HasUID c) => c -> Sentence
short CI
phsChgMtrl, String -> Sentence
S "to store", ConceptChunk -> Sentence
forall n. (HasUID n, NamedIdea n) => n -> Sentence
phrase ConceptChunk
thermalEnergy, String -> Sentence
S "as", UnitalChunk -> Sentence
forall n. (HasUID n, NamedIdea n) => n -> Sentence
phrase UnitalChunk
latentHeat Sentence -> Sentence -> Sentence
`sC`
String -> Sentence
S "which allows higher", ConceptChunk -> Sentence
forall n. (HasUID n, NamedIdea n) => n -> Sentence
phrase ConceptChunk
thermalEnergy, String -> Sentence
S "storage capacity per",
ConceptChunk -> Sentence
forall n. (HasUID n, NamedIdea n) => n -> Sentence
phrase ConceptChunk
unit_, String -> Sentence
S "weight"]
introEnd :: Sentence -> CI -> Sentence
introEnd :: Sentence -> CI -> Sentence
introEnd progSent :: Sentence
progSent pro :: CI
pro = [Sentence] -> Sentence
foldlSent_ [(Sentence
progSent Sentence -> Sentence
!.), String -> Sentence
S "The developed",
ConceptChunk -> Sentence
forall n. (HasUID n, NamedIdea n) => n -> Sentence
phrase ConceptChunk
program, String -> Sentence
S "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, HasUID c) => c -> Sentence
short CI
pro)]
scope :: Sentence
scope :: Sentence
scope = [Sentence] -> Sentence
foldlSent_ [ConceptChunk -> Sentence
forall n. (HasUID n, NamedIdea n) => n -> Sentence
phrase ConceptChunk
thermalAnalysis Sentence -> Sentence -> Sentence
`S.of_` String -> Sentence
S "a single" Sentence -> Sentence -> Sentence
+:+. ConceptChunk -> Sentence
forall n. (HasUID n, NamedIdea n) => n -> Sentence
phrase ConceptChunk
tankPCM,
String -> Sentence
S "This entire", NamedChunk -> Sentence
forall n. (HasUID n, NamedIdea n) => n -> Sentence
phrase NamedChunk
document Sentence -> Sentence -> Sentence
`S.is` String -> Sentence
S "written assuming that the substances inside the",
ConceptChunk -> Sentence
forall n. (HasUID n, NamedIdea n) => n -> Sentence
phrase ConceptChunk
sWHT Sentence -> Sentence -> Sentence
`S.are` NP -> Sentence
forall n. NounPhrase n => n -> Sentence
phraseNP ((ConceptChunk -> Sentence)
-> (CI -> Sentence) -> ConceptChunk -> CI -> NP
forall c d. (c -> Sentence) -> (d -> Sentence) -> c -> d -> NP
and_Gen ConceptChunk -> Sentence
forall n. (HasUID n, NamedIdea n) => n -> Sentence
phrase CI -> Sentence
forall c. (Idea c, HasUID c) => c -> Sentence
short ConceptChunk
water CI
phsChgMtrl)]
charsOfReader :: [Sentence]
charsOfReader :: [Sentence]
charsOfReader = [Sentence
charReaderHTT, Sentence
charReaderDE]
charReaderHTT :: Sentence
charReaderHTT :: Sentence
charReaderHTT = [Sentence] -> Sentence
foldlSent_ [ConceptChunk -> Sentence
forall n. (HasUID n, NamedIdea n) => n -> Sentence
phrase ConceptChunk
htTransTheo, String -> Sentence
S "from level 3 or 4",
String -> Sentence
S "mechanical", NamedChunk -> Sentence
forall n. (HasUID n, NamedIdea n) => n -> Sentence
phrase NamedChunk
engineering]
charReaderDE :: Sentence
charReaderDE :: Sentence
charReaderDE = CI -> Sentence
forall n. (HasUID n, NamedIdea n) => n -> Sentence
plural CI
de Sentence -> Sentence -> Sentence
+:+ String -> Sentence
S "from level 1 and 2" Sentence -> Sentence -> Sentence
+:+ NamedChunk -> Sentence
forall n. (HasUID n, NamedIdea n) => n -> Sentence
phrase NamedChunk
calculus
orgDocIntro :: Sentence
orgDocIntro :: Sentence
orgDocIntro = [Sentence] -> Sentence
foldlSent [NP -> Sentence
forall n. NounPhrase n => n -> Sentence
atStartNP (NamedChunk -> NP
forall t. NamedIdea t => t -> NP
the NamedChunk
organization), String -> Sentence
S "of this",
NamedChunk -> Sentence
forall n. (HasUID n, NamedIdea n) => n -> Sentence
phrase NamedChunk
document, String -> Sentence
S "follows the template for an", CI -> Sentence
forall c. (Idea c, HasUID c) => c -> Sentence
short CI
Doc.srs
Sentence -> Sentence -> Sentence
`S.for` NamedChunk -> Sentence
forall n. (HasUID n, NamedIdea n) => n -> Sentence
phrase NamedChunk
sciCompS, String -> Sentence
S "proposed by", Citation -> Sentence
forall r.
(HasUID r, HasRefAddress r, HasShortName r) =>
r -> Sentence
refS Citation
koothoor2013 Sentence -> Sentence -> Sentence
`S.and_`
Citation -> Sentence
forall r.
(HasUID r, HasRefAddress r, HasShortName r) =>
r -> Sentence
refS Citation
smithLai2005]
orgDocEnd :: Sentence
orgDocEnd :: Sentence
orgDocEnd = [Sentence] -> Sentence
foldlSent_ [NP -> Sentence
forall n. NounPhrase n => n -> Sentence
atStartNP' (CI -> NP
forall t. NamedIdea t => t -> NP
the CI
inModel),
String -> Sentence
S "to be solved are referred to as" Sentence -> Sentence -> Sentence
+:+.
SepType -> FoldType -> [Sentence] -> Sentence
foldlList SepType
Comma FoldType
List ((InstanceModel -> Sentence) -> [InstanceModel] -> [Sentence]
forall a b. (a -> b) -> [a] -> [b]
map InstanceModel -> Sentence
forall r.
(HasUID r, HasRefAddress r, HasShortName r) =>
r -> Sentence
refS [InstanceModel]
iMods), String -> Sentence
S "The", CI -> Sentence
forall n. (HasUID n, NamedIdea n) => n -> Sentence
plural CI
inModel,
String -> Sentence
S "provide the", CI -> Sentence
forall n. (HasUID n, NamedIdea n) => n -> Sentence
plural CI
ode, Sentence -> Sentence
sParen (CI -> Sentence
forall c. (Idea c, HasUID c) => c -> Sentence
short CI
ode Sentence -> Sentence -> Sentence
:+: String -> Sentence
S "s") Sentence -> Sentence -> Sentence
`S.and_`
String -> Sentence
S "algebraic", ConceptChunk -> Sentence
forall n. (HasUID n, NamedIdea n) => n -> Sentence
plural ConceptChunk
equation, String -> Sentence
S "that", NamedChunk -> Sentence
forall n. (HasUID n, NamedIdea n) => n -> Sentence
phrase NamedChunk
model,
(NP -> Sentence
forall n. NounPhrase n => n -> Sentence
phraseNP (CommonConcept -> NP
forall t. NamedIdea t => t -> NP
the CommonConcept
swhsPCM) Sentence -> Sentence
!.), CI -> Sentence
forall c. (Idea c, HasUID c) => c -> Sentence
short CI
progName, String -> Sentence
S "solves these", CI -> Sentence
forall c. (Idea c, HasUID c) => c -> Sentence
short CI
ode Sentence -> Sentence -> Sentence
:+: String -> Sentence
S "s"]
sysCntxtDesc :: CI -> Contents
sysCntxtDesc :: CI -> Contents
sysCntxtDesc pro :: CI
pro = [Sentence] -> Contents
foldlSP [LabelledContent -> Sentence
forall r.
(HasUID r, HasRefAddress r, HasShortName r) =>
r -> Sentence
refS LabelledContent
sysCntxtFig, String -> Sentence
S "shows the" Sentence -> Sentence -> Sentence
+:+.
NamedChunk -> Sentence
forall n. (HasUID n, NamedIdea n) => n -> Sentence
phrase NamedChunk
sysCont, String -> Sentence
S "A circle represents an external entity outside the",
NamedChunk -> Sentence
forall n. (HasUID n, NamedIdea n) => n -> Sentence
phrase NamedChunk
software Sentence -> Sentence -> Sentence
`sC` NP -> Sentence
forall n. NounPhrase n => n -> Sentence
phraseNP (NamedChunk -> NP
forall t. NamedIdea t => t -> NP
the NamedChunk
user) Sentence -> Sentence -> Sentence
+:+. String -> Sentence
S "in this case",
String -> Sentence
S "A rectangle represents the", NamedChunk -> Sentence
forall n. (HasUID n, NamedIdea n) => n -> Sentence
phrase NamedChunk
softwareSys, String -> Sentence
S "itself" Sentence -> Sentence -> Sentence
+:+.
Sentence -> Sentence
sParen (CI -> Sentence
forall c. (Idea c, HasUID c) => c -> Sentence
short CI
pro), String -> Sentence
S "Arrows are used to show the", NamedChunk -> Sentence
forall n. (HasUID n, NamedIdea n) => n -> Sentence
plural NamedChunk
datum,
String -> Sentence
S "flow between the", NP -> Sentence
forall n. NounPhrase n => n -> Sentence
phraseNP (NamedChunk
system NamedChunk -> NamedChunk -> NP
forall c d. (NamedIdea c, NamedIdea d) => c -> d -> NP
`andIts` NamedChunk
environment)]
sysCntxtFig :: LabelledContent
sysCntxtFig :: LabelledContent
sysCntxtFig = Reference -> RawContent -> LabelledContent
llcc (String -> Reference
makeFigRef "SysCon") (RawContent -> LabelledContent) -> RawContent -> LabelledContent
forall a b. (a -> b) -> a -> b
$ Sentence -> String -> RawContent
fig ([Sentence] -> Sentence
foldlSent_
[LabelledContent -> Sentence
forall r.
(HasUID r, HasRefAddress r, HasShortName r) =>
r -> Sentence
refS LabelledContent
sysCntxtFig Sentence -> Sentence -> Sentence
+: Sentence
EmptyS, NamedChunk -> Sentence
forall n. NamedIdea n => n -> Sentence
titleize NamedChunk
sysCont])
(String -> RawContent) -> String -> RawContent
forall a b. (a -> b) -> a -> b
$ String
resourcePath String -> String -> String
forall a. [a] -> [a] -> [a]
++ "SystemContextFigure.png"
sysCntxtRespIntro :: CI -> Contents
sysCntxtRespIntro :: CI -> Contents
sysCntxtRespIntro pro :: CI
pro = [Sentence] -> Contents
foldlSPCol [CI -> Sentence
forall c. (Idea c, HasUID c) => c -> Sentence
short CI
pro Sentence -> Sentence -> Sentence
+:+. String -> Sentence
S "is mostly self-contained",
String -> Sentence
S "The only external interaction is through the", NamedChunk -> Sentence
forall n. (HasUID n, NamedIdea n) => n -> Sentence
phrase NamedChunk
user Sentence -> Sentence -> Sentence
+:+.
String -> Sentence
S "interface", String -> Sentence
S "responsibilities" Sentence -> Sentence -> Sentence
`S.the_ofTheC` NP -> Sentence
forall n. NounPhrase n => n -> Sentence
phraseNP (NamedChunk
user NamedChunk -> NamedChunk -> NP
forall c d. (NamedIdea c, NamedIdea d) => c -> d -> NP
`andThe`
NamedChunk
system) Sentence -> Sentence -> Sentence
`S.are` String -> Sentence
S "as follows"]
systContRespBullets :: Contents
systContRespBullets :: Contents
systContRespBullets = UnlabelledContent -> Contents
UlC (UnlabelledContent -> Contents) -> UnlabelledContent -> Contents
forall a b. (a -> b) -> a -> b
$ RawContent -> UnlabelledContent
ulcc (RawContent -> UnlabelledContent)
-> RawContent -> UnlabelledContent
forall a b. (a -> b) -> a -> b
$ ListType -> RawContent
Enumeration (ListType -> RawContent) -> ListType -> RawContent
forall a b. (a -> b) -> a -> b
$ [Sentence] -> [ListType] -> ListType
bulletNested
[NamedChunk -> Sentence
forall n. NamedIdea n => n -> Sentence
titleize NamedChunk
user Sentence -> Sentence -> Sentence
+: String -> Sentence
S "Responsibilities", CI -> Sentence
forall c. (Idea c, HasUID c) => c -> Sentence
short CI
progName Sentence -> Sentence -> Sentence
+: String -> Sentence
S "Responsibilities"]
([ListType] -> ListType) -> [ListType] -> ListType
forall a b. (a -> b) -> a -> b
$ ([Sentence] -> ListType) -> [[Sentence]] -> [ListType]
forall a b. (a -> b) -> [a] -> [b]
map [Sentence] -> ListType
bulletFlat [[Sentence]
userResp, [Sentence]
swhsResp]
userResp :: [Sentence]
userResp :: [Sentence]
userResp = ([Sentence] -> Sentence) -> [[Sentence]] -> [Sentence]
forall a b. (a -> b) -> [a] -> [b]
map [Sentence] -> Sentence
foldlSent_ [
[String -> Sentence
S "Provide the", NamedChunk -> Sentence
forall n. (HasUID n, NamedIdea n) => n -> Sentence
phrase NamedChunk
input_, NamedChunk -> Sentence
forall n. (HasUID n, NamedIdea n) => n -> Sentence
plural NamedChunk
datum Sentence -> Sentence -> Sentence
`S.toThe`
NamedChunk -> Sentence
forall n. (HasUID n, NamedIdea n) => n -> Sentence
phrase NamedChunk
system Sentence -> Sentence -> Sentence
`sC` String -> Sentence
S "ensuring no errors in the", NamedChunk -> Sentence
forall n. (HasUID n, NamedIdea n) => n -> Sentence
plural NamedChunk
datum, String -> Sentence
S "entry"],
[String -> Sentence
S "Take care that consistent", ConceptChunk -> Sentence
forall n. (HasUID n, NamedIdea n) => n -> Sentence
plural ConceptChunk
unit_, String -> Sentence
S "are used for",
NamedChunk -> Sentence
forall n. (HasUID n, NamedIdea n) => n -> Sentence
phrase NamedChunk
input_, NamedChunk -> Sentence
forall n. (HasUID n, NamedIdea n) => n -> Sentence
plural NamedChunk
variable]
]
swhsResp :: [Sentence]
swhsResp :: [Sentence]
swhsResp = ([Sentence] -> Sentence) -> [[Sentence]] -> [Sentence]
forall a b. (a -> b) -> [a] -> [b]
map [Sentence] -> Sentence
foldlSent_ [
[String -> Sentence
S "Detect", NamedChunk -> Sentence
forall n. (HasUID n, NamedIdea n) => n -> Sentence
plural NamedChunk
datum, String -> Sentence
S "type mismatch, such as a string" Sentence -> Sentence -> Sentence
`S.of_`
String -> Sentence
S "characters instead of a floating point number"],
[String -> Sentence
S "Determine if the", NamedChunk -> Sentence
forall n. (HasUID n, NamedIdea n) => n -> Sentence
plural NamedChunk
input_, String -> Sentence
S "satisfy the required",
NP -> Sentence
forall n. NounPhrase n => n -> Sentence
phraseNP (NamedChunk
physical NamedChunk -> NamedChunk -> NP
forall c d. (NamedIdea c, NamedIdea d) => c -> d -> NP
`and_` NamedChunk
software), NamedChunk -> Sentence
forall n. (HasUID n, NamedIdea n) => n -> Sentence
plural NamedChunk
constraint],
[String -> Sentence
S "Calculate the required", NamedChunk -> Sentence
forall n. (HasUID n, NamedIdea n) => n -> Sentence
plural NamedChunk
output_]
]
userChars :: CI -> Contents
userChars :: CI -> Contents
userChars pro :: CI
pro = [Sentence] -> Contents
foldlSP [String -> Sentence
S "The end", NamedChunk -> Sentence
forall n. (HasUID n, NamedIdea n) => n -> Sentence
phrase NamedChunk
user Sentence -> Sentence -> Sentence
`S.of_` CI -> Sentence
forall c. (Idea c, HasUID c) => c -> Sentence
short CI
pro,
String -> Sentence
S "should have an understanding of undergraduate Level 1 Calculus" Sentence -> Sentence -> Sentence
`S.and_`
NamedChunk -> Sentence
forall n. NamedIdea n => n -> Sentence
titleize NamedChunk
Doc.physics]
probDescIntro :: Sentence
probDescIntro :: Sentence
probDescIntro = [Sentence] -> Sentence
foldlSent_ [String -> Sentence
S "investigate the effect" Sentence -> Sentence -> Sentence
`S.of_` String -> Sentence
S "employing",
CI -> Sentence
forall c. (Idea c, HasUID c) => c -> Sentence
short CI
phsChgMtrl, String -> Sentence
S "within a", ConceptChunk -> Sentence
forall n. (HasUID n, NamedIdea n) => n -> Sentence
phrase ConceptChunk
sWHT]
terms :: [ConceptChunk]
terms :: [ConceptChunk]
terms = (ConceptChunk -> ConceptChunk) -> [ConceptChunk] -> [ConceptChunk]
forall a b. (a -> b) -> [a] -> [b]
map ConceptChunk -> ConceptChunk
forall c. Concept c => c -> ConceptChunk
cw [ConceptChunk
htFlux, ConceptChunk
phaseChangeMaterial, UnitalChunk -> ConceptChunk
forall c. Concept c => c -> ConceptChunk
cw UnitalChunk
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,
[CI -> Sentence
forall c. (Idea c, HasUID c) => c -> Sentence
short CI
phsChgMtrl, String -> Sentence
S "suspended in" Sentence -> Sentence -> Sentence
+:+. ConceptChunk -> Sentence
forall n. (HasUID n, NamedIdea n) => n -> Sentence
phrase ConceptChunk
tank,
Sentence -> Sentence
sParen (UnitalChunk -> Sentence
forall c. (HasUID c, HasSymbol c) => c -> Sentence
ch UnitalChunk
htFluxP Sentence -> Sentence -> Sentence
+:+ String -> Sentence
S "represents the" Sentence -> Sentence -> Sentence
+:+. UnitalChunk -> Sentence
forall n. (HasUID n, NamedIdea n) => n -> Sentence
phrase UnitalChunk
htFluxP)]]
physSyst1 :: ConceptChunk -> ConceptChunk -> [Sentence]
physSyst1 :: ConceptChunk -> ConceptChunk -> [Sentence]
physSyst1 ta :: ConceptChunk
ta wa :: ConceptChunk
wa = [ConceptChunk -> Sentence
forall n. NamedIdea n => n -> Sentence
atStart ConceptChunk
ta, String -> Sentence
S "containing" Sentence -> Sentence -> Sentence
+:+. ConceptChunk -> Sentence
forall n. (HasUID n, NamedIdea n) => n -> Sentence
phrase ConceptChunk
wa]
physSyst2 :: ConceptChunk -> ConceptChunk -> UnitalChunk -> [Sentence]
physSyst2 :: ConceptChunk -> ConceptChunk -> UnitalChunk -> [Sentence]
physSyst2 co :: ConceptChunk
co ta :: ConceptChunk
ta hfc :: UnitalChunk
hfc = [ConceptChunk -> Sentence
forall n. NamedIdea n => n -> Sentence
atStart ConceptChunk
co, String -> Sentence
S "at bottom of" Sentence -> Sentence -> Sentence
+:+. ConceptChunk -> Sentence
forall n. (HasUID n, NamedIdea n) => n -> Sentence
phrase ConceptChunk
ta,
Sentence -> Sentence
sParen (UnitalChunk -> Sentence
forall c. (HasUID c, HasSymbol c) => c -> Sentence
ch UnitalChunk
hfc Sentence -> Sentence -> Sentence
+:+ String -> Sentence
S "represents the" Sentence -> Sentence -> Sentence
+:+. UnitalChunk -> Sentence
forall n. (HasUID n, NamedIdea n) => n -> Sentence
phrase UnitalChunk
hfc)]
figTank :: LabelledContent
figTank :: LabelledContent
figTank = Reference -> RawContent -> LabelledContent
llcc (String -> Reference
makeFigRef "Tank") (RawContent -> LabelledContent) -> RawContent -> LabelledContent
forall a b. (a -> b) -> a -> b
$ Sentence -> String -> RawContent
fig (
[Sentence] -> Sentence
foldlSent_ [ConceptChunk -> Sentence
forall n. NamedIdea n => n -> Sentence
atStart ConceptChunk
sWHT Sentence -> Sentence -> Sentence
`sC` String -> Sentence
S "with", UnitalChunk -> Sentence
forall n. (HasUID n, NamedIdea n) => n -> Sentence
phrase UnitalChunk
htFluxC Sentence -> Sentence -> Sentence
`S.of_`
UnitalChunk -> Sentence
forall c. (HasUID c, HasSymbol c) => c -> Sentence
ch UnitalChunk
htFluxC Sentence -> Sentence -> Sentence
`S.and_` UnitalChunk -> Sentence
forall n. (HasUID n, NamedIdea n) => n -> Sentence
phrase UnitalChunk
htFluxP Sentence -> Sentence -> Sentence
`S.of_` UnitalChunk -> Sentence
forall c. (HasUID c, HasSymbol c) => c -> Sentence
ch UnitalChunk
htFluxP])
(String -> RawContent) -> String -> RawContent
forall a b. (a -> b) -> a -> b
$ String
resourcePath String -> String -> String
forall a. [a] -> [a] -> [a]
++ "Tank.png"
goalInputs :: [Sentence]
goalInputs :: [Sentence]
goalInputs = [NP -> Sentence
forall n. NounPhrase n => n -> Sentence
phraseNP (UncertQ -> NP
forall t. NamedIdea t => t -> NP
the UncertQ
tempC),
String -> Sentence
S "the initial" Sentence -> Sentence -> Sentence
+:+ NamedChunk -> Sentence
forall n. (HasUID n, NamedIdea n) => n -> Sentence
plural NamedChunk
condition Sentence -> Sentence -> Sentence
+:+ String -> Sentence
S "for the" Sentence -> Sentence -> Sentence
+:+ NP -> Sentence
forall n. NounPhrase n => n -> Sentence
phraseNP (ConstrConcept
tempW ConstrConcept -> ConstrConcept -> NP
forall c d. (NamedIdea c, NamedIdea d) => c -> d -> NP
`andThe` ConstrConcept
tempPCM),
String -> Sentence
S "the material" Sentence -> Sentence -> Sentence
+:+ NamedChunk -> Sentence
forall n. (HasUID n, NamedIdea n) => n -> Sentence
plural NamedChunk
property]
dataConTail :: Sentence
dataConTail :: Sentence
dataConTail = Sentence
dataContMid Sentence -> Sentence -> Sentence
+:+ Sentence
dataContFooter
dataContMid :: Sentence
dataContMid :: Sentence
dataContMid = [Sentence] -> Sentence
foldlSent [NP -> Sentence
forall n. NounPhrase n => n -> Sentence
atStartNP (NamedChunk -> NP
forall t. NamedIdea t => t -> NP
the NamedChunk
column) Sentence -> Sentence -> Sentence
`S.for` NP -> Sentence
forall n. NounPhrase n => n -> Sentence
pluralNP (NamedChunk -> NamedChunk -> NP
forall c d. (NamedIdea c, NamedIdea d) => c -> d -> NP
combineNINI NamedChunk
software
NamedChunk
constraint), String -> Sentence
S "restricts the range" Sentence -> Sentence -> Sentence
`S.of_` NamedChunk -> Sentence
forall n. (HasUID n, NamedIdea n) => n -> Sentence
plural NamedChunk
input_,
String -> Sentence
S "to reasonable", NamedChunk -> Sentence
forall n. (HasUID n, NamedIdea n) => n -> Sentence
plural NamedChunk
value]
dataContFooter :: Sentence
= [Sentence] -> Sentence
foldlSent_ ([Sentence] -> Sentence) -> [Sentence] -> Sentence
forall a b. (a -> b) -> a -> b
$ ([Sentence] -> Sentence) -> [[Sentence]] -> [Sentence]
forall a b. (a -> b) -> [a] -> [b]
map [Sentence] -> Sentence
foldlSent [
[Sentence -> Sentence
sParen (String -> Sentence
S "*"), String -> Sentence
S "These", NamedChunk -> Sentence
forall n. (HasUID n, NamedIdea n) => n -> Sentence
plural NamedChunk
quantity, String -> Sentence
S "cannot be equal to zero" Sentence -> Sentence -> Sentence
`sC`
String -> Sentence
S "or there will be a divide by zero in the", NamedChunk -> Sentence
forall n. (HasUID n, NamedIdea n) => n -> Sentence
phrase NamedChunk
model],
[Sentence -> Sentence
sParen (String -> Sentence
S "+"), String -> Sentence
S "These", NamedChunk -> Sentence
forall n. (HasUID n, NamedIdea n) => n -> Sentence
plural NamedChunk
quantity, String -> Sentence
S "cannot be zero" Sentence -> Sentence -> Sentence
`sC`
String -> Sentence
S "or there would be freezing", Sentence -> Sentence
sParen (ConceptInstance -> Sentence
forall r.
(HasUID r, HasRefAddress r, HasShortName r) =>
r -> Sentence
refS ConceptInstance
assumpPIS)],
[Sentence -> Sentence
sParen (String -> Sentence
S "++"), NP -> Sentence
forall n. NounPhrase n => n -> Sentence
atStartNP' (NP -> NP
NP.the (NamedChunk
constraint NamedChunk -> UnitalChunk -> NP
forall c d. (NamedIdea c, NamedIdea d) => c -> d -> NP
`onThePS` UnitalChunk
surArea)),
String -> Sentence
S "are calculated by considering the", UnitalChunk -> Sentence
forall n. (HasUID n, NamedIdea n) => n -> Sentence
phrase UnitalChunk
surArea, String -> Sentence
S "to", UnitalChunk -> Sentence
forall n. (HasUID n, NamedIdea n) => n -> Sentence
phrase UnitalChunk
vol Sentence -> Sentence -> Sentence
+:+.
String -> Sentence
S "ratio", NP -> Sentence
forall n. NounPhrase n => n -> Sentence
atStartNP (CI -> NP
forall t. NamedIdea t => t -> NP
the CI
assumption), String -> Sentence
S "is that the lowest ratio is 1" Sentence -> Sentence -> Sentence
`S.and_`
String -> Sentence
S "the highest possible is", ModelExpr -> Sentence
eS (Integer -> ModelExpr
forall r. LiteralC r => Integer -> r
exactDbl 2 ModelExpr -> ModelExpr -> ModelExpr
forall r. ExprC r => r -> r -> r
$/ UnitalChunk -> ModelExpr
forall r c. (ExprC r, HasUID c, HasSymbol c) => c -> r
sy UnitalChunk
thickness) Sentence -> Sentence -> Sentence
`sC` String -> Sentence
S "where", UnitalChunk -> Sentence
forall c. (HasUID c, HasSymbol c) => c -> Sentence
ch UnitalChunk
thickness,
String -> Sentence
S "is the thickness of a" Sentence -> Sentence -> Sentence
+:+. (Sentence -> Sentence
Quote (String -> Sentence
S "sheet") Sentence -> Sentence -> Sentence
`S.of_` CI -> Sentence
forall c. (Idea c, HasUID c) => c -> Sentence
short CI
phsChgMtrl),
String -> Sentence
S "A thin sheet has the greatest", UnitalChunk -> Sentence
forall n. (HasUID n, NamedIdea n) => n -> Sentence
phrase UnitalChunk
surArea, String -> Sentence
S "to", UnitalChunk -> Sentence
forall n. (HasUID n, NamedIdea n) => n -> Sentence
phrase UnitalChunk
vol, String -> Sentence
S "ratio"],
[Sentence -> Sentence
sParen (String -> Sentence
S "**"), NP -> Sentence
forall n. NounPhrase n => n -> Sentence
atStartNP (NamedChunk -> NP
forall t. NamedIdea t => t -> NP
the NamedChunk
constraint), String -> Sentence
S "on the maximum", UnitalChunk -> Sentence
forall n. (HasUID n, NamedIdea n) => n -> Sentence
phrase UnitalChunk
time,
String -> Sentence
S "at the end of the simulation is the total number of seconds in one day"]
]
outputConstraints :: [ConstrConcept]
outputConstraints :: [ConstrConcept]
outputConstraints = [ConstrConcept
tempW, ConstrConcept
tempPCM, ConstrConcept
watE, ConstrConcept
pcmE]
propsDeriv :: [Contents]
propsDeriv :: [Contents]
propsDeriv = [
ConceptChunk
-> ConstrConcept
-> UnitalChunk
-> ConceptChunk
-> CI
-> GenDefn
-> GenDefn
-> UnitalChunk
-> ConceptChunk
-> Contents
forall b h.
(NamedIdea b, NamedIdea h) =>
ConceptChunk
-> b
-> UnitalChunk
-> ConceptChunk
-> CI
-> GenDefn
-> GenDefn
-> h
-> ConceptChunk
-> Contents
propCorSolDeriv1 ConceptChunk
lawConsEnergy ConstrConcept
watE UnitalChunk
energy ConceptChunk
coil CI
phsChgMtrl
GenDefn
htFluxWaterFromCoil GenDefn
htFluxPCMFromWater UnitalChunk
surface ConceptChunk
heatTrans,
Contents
propCorSolDeriv2,
ConstrConcept -> UnitalChunk -> CI -> ConceptChunk -> Contents
forall a.
NamedIdea a =>
a -> UnitalChunk -> CI -> ConceptChunk -> Contents
propCorSolDeriv3 ConstrConcept
pcmE UnitalChunk
energy CI
phsChgMtrl ConceptChunk
water,
Contents
propCorSolDeriv4,
ConceptChunk -> CI -> CI -> Contents
propCorSolDeriv5 ConceptChunk
equation CI
progName CI
rightSide]
propCorSolDeriv1 :: (NamedIdea b, NamedIdea h) => ConceptChunk -> b -> UnitalChunk ->
ConceptChunk -> CI -> GenDefn -> GenDefn -> h -> ConceptChunk -> Contents
propCorSolDeriv1 :: ConceptChunk
-> b
-> UnitalChunk
-> ConceptChunk
-> CI
-> GenDefn
-> GenDefn
-> h
-> ConceptChunk
-> Contents
propCorSolDeriv1 lce :: ConceptChunk
lce ewat :: b
ewat en :: UnitalChunk
en co :: ConceptChunk
co pcmat :: CI
pcmat g1hfc :: GenDefn
g1hfc g2hfp :: GenDefn
g2hfp su :: h
su ht :: ConceptChunk
ht =
[Sentence] -> Contents
foldlSPCol [NP -> Sentence
forall n. NounPhrase n => n -> Sentence
atStartNP (NamedChunk -> NP
forall t. NamedIdea t => t -> NP
a_ NamedChunk
corSol), String -> Sentence
S "must exhibit" Sentence -> Sentence -> Sentence
+:+.
NP -> Sentence
forall n. NounPhrase n => n -> Sentence
phraseNP (ConceptChunk -> NP
forall t. NamedIdea t => t -> NP
the ConceptChunk
lce), String -> Sentence
S "This means that", NP -> Sentence
forall n. NounPhrase n => n -> Sentence
phraseNP (b -> NP
forall t. NamedIdea t => t -> NP
the b
ewat),
String -> Sentence
S "should equal the difference between the total", UnitalChunk -> Sentence
forall n. (HasUID n, NamedIdea n) => n -> Sentence
phrase UnitalChunk
en,
NamedChunk -> Sentence
forall n. (HasUID n, NamedIdea n) => n -> Sentence
phrase NamedChunk
input_, String -> Sentence
S "from", NP -> Sentence
forall n. NounPhrase n => n -> Sentence
phraseNP (ConceptChunk -> NP
forall t. NamedIdea t => t -> NP
the ConceptChunk
co NP -> NP -> NP
`NP.andThe`
UnitalChunk -> NamedChunk -> NP
forall c d. (NamedIdea c, NamedIdea d) => c -> d -> NP
combineNINI UnitalChunk
en NamedChunk
output_), String -> Sentence
S "to the" Sentence -> Sentence -> Sentence
+:+. CI -> Sentence
forall c. (Idea c, HasUID c) => c -> Sentence
short CI
pcmat,
String -> Sentence
S "This can be shown as an", ConceptChunk -> Sentence
forall n. (HasUID n, NamedIdea n) => n -> Sentence
phrase ConceptChunk
equation, String -> Sentence
S "by taking",
GenDefn -> Sentence
forall r.
(HasUID r, HasRefAddress r, HasShortName r) =>
r -> Sentence
refS GenDefn
g1hfc Sentence -> Sentence -> Sentence
`S.and_` GenDefn -> Sentence
forall r.
(HasUID r, HasRefAddress r, HasShortName r) =>
r -> Sentence
refS GenDefn
g2hfp Sentence -> Sentence -> Sentence
`sC`
String -> Sentence
S "multiplying each by their respective", h -> Sentence
forall n. (HasUID n, NamedIdea n) => n -> Sentence
phrase h
su,
String -> Sentence
S "area of", ConceptChunk -> Sentence
forall n. (HasUID n, NamedIdea n) => n -> Sentence
phrase ConceptChunk
ht Sentence -> Sentence -> Sentence
`sC` String -> Sentence
S "and integrating each",
String -> Sentence
S "over the", UnitalChunk -> Sentence
forall n. (HasUID n, NamedIdea n) => n -> Sentence
phrase UnitalChunk
simTime Sentence -> Sentence -> Sentence
`sC` String -> Sentence
S "as follows"]
propCorSolDeriv2 :: Contents
propCorSolDeriv2 :: Contents
propCorSolDeriv2 = ModelExpr -> Contents
unlbldExpr
(ConstrConcept -> ModelExpr
forall r c. (ExprC r, HasUID c, HasSymbol c) => c -> r
sy ConstrConcept
watE ModelExpr -> ModelExpr -> ModelExpr
forall r. ExprC r => r -> r -> r
$= Symbol -> ModelExpr -> ModelExpr -> ModelExpr -> ModelExpr
forall r. ExprC r => Symbol -> r -> r -> r -> r
defint (UnitalChunk -> Symbol
forall q. HasSymbol q => q -> Symbol
eqSymb UnitalChunk
time) (Integer -> ModelExpr
forall r. LiteralC r => Integer -> r
exactDbl 0) (UnitalChunk -> ModelExpr
forall r c. (ExprC r, HasUID c, HasSymbol c) => c -> r
sy UnitalChunk
time)
(UncertQ -> ModelExpr
forall r c. (ExprC r, HasUID c, HasSymbol c) => c -> r
sy UncertQ
coilHTC ModelExpr -> ModelExpr -> ModelExpr
forall r. ExprC r => r -> r -> r
`mulRe` UncertQ -> ModelExpr
forall r c. (ExprC r, HasUID c, HasSymbol c) => c -> r
sy UncertQ
coilSA ModelExpr -> ModelExpr -> ModelExpr
forall r. ExprC r => r -> r -> r
`mulRe` (UncertQ -> ModelExpr
forall r c. (ExprC r, HasUID c, HasSymbol c) => c -> r
sy UncertQ
tempC ModelExpr -> ModelExpr -> ModelExpr
forall r. ExprC r => r -> r -> r
$- ConstrConcept -> UnitalChunk -> ModelExpr
forall r f a.
(ExprC r, HasUID f, HasSymbol f, HasUID a, HasSymbol a) =>
f -> a -> r
apply1 ConstrConcept
tempW UnitalChunk
time))
ModelExpr -> ModelExpr -> ModelExpr
forall r. ExprC r => r -> r -> r
$- Symbol -> ModelExpr -> ModelExpr -> ModelExpr -> ModelExpr
forall r. ExprC r => Symbol -> r -> r -> r -> r
defint (UnitalChunk -> Symbol
forall q. HasSymbol q => q -> Symbol
eqSymb UnitalChunk
time) (Integer -> ModelExpr
forall r. LiteralC r => Integer -> r
exactDbl 0) (UnitalChunk -> ModelExpr
forall r c. (ExprC r, HasUID c, HasSymbol c) => c -> r
sy UnitalChunk
time)
(UncertQ -> ModelExpr
forall r c. (ExprC r, HasUID c, HasSymbol c) => c -> r
sy UncertQ
pcmHTC ModelExpr -> ModelExpr -> ModelExpr
forall r. ExprC r => r -> r -> r
`mulRe` UncertQ -> ModelExpr
forall r c. (ExprC r, HasUID c, HasSymbol c) => c -> r
sy UncertQ
pcmSA ModelExpr -> ModelExpr -> ModelExpr
forall r. ExprC r => r -> r -> r
`mulRe` (ConstrConcept -> UnitalChunk -> ModelExpr
forall r f a.
(ExprC r, HasUID f, HasSymbol f, HasUID a, HasSymbol a) =>
f -> a -> r
apply1 ConstrConcept
tempW UnitalChunk
time ModelExpr -> ModelExpr -> ModelExpr
forall r. ExprC r => r -> r -> r
$-
ConstrConcept -> UnitalChunk -> ModelExpr
forall r f a.
(ExprC r, HasUID f, HasSymbol f, HasUID a, HasSymbol a) =>
f -> a -> r
apply1 ConstrConcept
tempPCM UnitalChunk
time)))
propCorSolDeriv3 :: NamedIdea a => a -> UnitalChunk -> CI -> ConceptChunk -> Contents
propCorSolDeriv3 :: a -> UnitalChunk -> CI -> ConceptChunk -> Contents
propCorSolDeriv3 epcm :: a
epcm en :: UnitalChunk
en pcmat :: CI
pcmat wa :: ConceptChunk
wa =
[Sentence] -> Contents
foldlSP_ [String -> Sentence
S "In addition, the", a -> Sentence
forall n. (HasUID n, NamedIdea n) => n -> Sentence
phrase a
epcm, String -> Sentence
S "should equal the",
UnitalChunk -> Sentence
forall n. (HasUID n, NamedIdea n) => n -> Sentence
phrase UnitalChunk
en, NamedChunk -> Sentence
forall n. (HasUID n, NamedIdea n) => n -> Sentence
phrase NamedChunk
input_, String -> Sentence
S "to the", CI -> Sentence
forall c. (Idea c, HasUID c) => c -> Sentence
short CI
pcmat,
String -> Sentence
S "from the" Sentence -> Sentence -> Sentence
+:+. ConceptChunk -> Sentence
forall n. (HasUID n, NamedIdea n) => n -> Sentence
phrase ConceptChunk
wa, String -> Sentence
S "This can be expressed as"]
propCorSolDeriv4 :: Contents
propCorSolDeriv4 :: Contents
propCorSolDeriv4 = ModelExpr -> Contents
unlbldExpr
(ConstrConcept -> ModelExpr
forall r c. (ExprC r, HasUID c, HasSymbol c) => c -> r
sy ConstrConcept
pcmE ModelExpr -> ModelExpr -> ModelExpr
forall r. ExprC r => r -> r -> r
$= Symbol -> ModelExpr -> ModelExpr -> ModelExpr -> ModelExpr
forall r. ExprC r => Symbol -> r -> r -> r -> r
defint (UnitalChunk -> Symbol
forall q. HasSymbol q => q -> Symbol
eqSymb UnitalChunk
time) (Integer -> ModelExpr
forall r. LiteralC r => Integer -> r
exactDbl 0) (UnitalChunk -> ModelExpr
forall r c. (ExprC r, HasUID c, HasSymbol c) => c -> r
sy UnitalChunk
time)
(UncertQ -> ModelExpr
forall r c. (ExprC r, HasUID c, HasSymbol c) => c -> r
sy UncertQ
pcmHTC ModelExpr -> ModelExpr -> ModelExpr
forall r. ExprC r => r -> r -> r
`mulRe` UncertQ -> ModelExpr
forall r c. (ExprC r, HasUID c, HasSymbol c) => c -> r
sy UncertQ
pcmSA ModelExpr -> ModelExpr -> ModelExpr
forall r. ExprC r => r -> r -> r
`mulRe` (ConstrConcept -> UnitalChunk -> ModelExpr
forall r f a.
(ExprC r, HasUID f, HasSymbol f, HasUID a, HasSymbol a) =>
f -> a -> r
apply1 ConstrConcept
tempW UnitalChunk
time ModelExpr -> ModelExpr -> ModelExpr
forall r. ExprC r => r -> r -> r
$-
ConstrConcept -> UnitalChunk -> ModelExpr
forall r f a.
(ExprC r, HasUID f, HasSymbol f, HasUID a, HasSymbol a) =>
f -> a -> r
apply1 ConstrConcept
tempPCM UnitalChunk
time)))
propCorSolDeriv5 :: ConceptChunk -> CI -> CI -> Contents
propCorSolDeriv5 :: ConceptChunk -> CI -> CI -> Contents
propCorSolDeriv5 eq :: ConceptChunk
eq pro :: CI
pro rs :: CI
rs = [Sentence] -> Contents
foldlSP [ConceptChunk -> Sentence
forall n. NamedIdea n => n -> Sentence
titleize' ConceptChunk
eq, String -> Sentence
S "(FIXME: Equation 7)"
Sentence -> Sentence -> Sentence
`S.and_` String -> Sentence
S "(FIXME: Equation 8) can be used as", Sentence -> Sentence
Quote (String -> Sentence
S "sanity") Sentence -> Sentence -> Sentence
+:+
String -> Sentence
S "checks to gain confidence in any", NamedChunk -> Sentence
forall n. (HasUID n, NamedIdea n) => n -> Sentence
phrase NamedChunk
solution,
String -> Sentence
S "computed by" Sentence -> Sentence -> Sentence
+:+. CI -> Sentence
forall c. (Idea c, HasUID c) => c -> Sentence
short CI
pro, String -> Sentence
S "The relative",
String -> Sentence
S "error between the results computed by", CI -> Sentence
forall c. (Idea c, HasUID c) => c -> Sentence
short CI
pro Sentence -> Sentence -> Sentence
`S.and_`
String -> Sentence
S "the results calculated from the", CI -> Sentence
forall c. (Idea c, HasUID c) => c -> Sentence
short CI
rs, String -> Sentence
S "of these",
ConceptChunk -> Sentence
forall n. (HasUID n, NamedIdea n) => n -> Sentence
plural ConceptChunk
eq, String -> Sentence
S "should be less than", DefinedQuantityDict -> Sentence
forall c. (HasUID c, HasSymbol c) => c -> Sentence
ch DefinedQuantityDict
consTol, ConceptInstance -> Sentence
forall r.
(HasUID r, HasRefAddress r, HasShortName r) =>
r -> Sentence
refS ConceptInstance
verifyEnergyOutput]