module Drasil.Projectile.Lesson.Body where
import Data.List (nub)
import Language.Drasil
import Language.Drasil.Printers (PrintingInformation(..), defaultConfiguration)
import Database.Drasil
import SysInfo.Drasil
import qualified Language.Drasil.Sentence.Combinators as S
import Drasil.DocLang (mkNb, NBDecl, NbSection(BibSec, IntrodSec, BodySec),
IntrodSec(..), BodySec(..), BodySub(..))
import Data.Drasil.Concepts.Documentation (doccon, doccon')
import Data.Drasil.Concepts.Math (mathcon)
import qualified Data.Drasil.Concepts.Documentation as Doc (notebook)
import Data.Drasil.Quantities.Physics (physicscon)
import Data.Drasil.Concepts.Physics (physicCon)
import Data.Drasil.People (spencerSmith)
import Drasil.Projectile.Concepts (concepts, projMotion)
import Drasil.Projectile.Expressions (eqnRefs)
import Drasil.Projectile.Lesson.IntroSection (introContext, reasonList, overviewParagraph)
import Drasil.Projectile.Lesson.Review (reviewContent)
import Drasil.Projectile.Lesson.Motion (motionContextP1, figCSandA, figRefs,
motionContextP2, horMotion, verMotion, summary)
import Drasil.Projectile.Lesson.Analysis (coorSyst, kinematicEq, horMotionAna, verMotionAna)
nb :: Document
nb :: Document
nb = NBDecl
-> (IdeaDict -> IdeaDict -> Sentence)
-> SystemInformation
-> Document
mkNb NBDecl
mkNB ((IdeaDict -> Sentence)
-> (IdeaDict -> Sentence) -> IdeaDict -> IdeaDict -> Sentence
forall c d.
(c -> Sentence) -> (d -> Sentence) -> c -> d -> Sentence
S.forGen IdeaDict -> Sentence
forall n. NamedIdea n => n -> Sentence
titleize IdeaDict -> Sentence
forall n. (HasUID n, NamedIdea n) => n -> Sentence
phrase) SystemInformation
si
printSetting :: PrintingInformation
printSetting :: PrintingInformation
printSetting = ChunkDB -> Stage -> PrintingConfiguration -> PrintingInformation
PI ChunkDB
symbMap Stage
Equational PrintingConfiguration
defaultConfiguration
mkNB :: NBDecl
mkNB :: NBDecl
mkNB = [
IntrodSec -> NbSection
IntrodSec (IntrodSec -> NbSection) -> IntrodSec -> NbSection
forall a b. (a -> b) -> a -> b
$
[Contents] -> [IntrodSub] -> IntrodSec
IntrodProg [Contents
introContext, Contents
reasonList, Contents
overviewParagraph] [],
BodySec -> NbSection
BodySec (BodySec -> NbSection) -> BodySec -> NbSection
forall a b. (a -> b) -> a -> b
$
[BodySub] -> BodySec
BodyProg
[[Contents] -> BodySub
Review [Contents]
reviewContent,
[Contents] -> [Section] -> BodySub
MainIdea [Contents
motionContextP1, LabelledContent -> Contents
LlC LabelledContent
figCSandA, Contents
motionContextP2] [Section
horMotion, Section
verMotion, Section
summary],
[Contents] -> [Section] -> BodySub
MethsAndAnls [Contents
mAndaintro] [Section
coorSyst, Section
kinematicEq, Section
horMotionAna, Section
verMotionAna]],
NbSection
BibSec
]
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 :: CI
_sys = CI
projectileMotion,
_kind :: CI
_kind = CI
Doc.notebook,
_authors :: [Person]
_authors = [Person
spencerSmith],
_purpose :: [Any]
_purpose = [],
_quants :: [QuantityDict]
_quants = [] :: [QuantityDict],
_concepts :: [DefinedQuantityDict]
_concepts = [] :: [DefinedQuantityDict],
_instModels :: [InstanceModel]
_instModels = [],
_datadefs :: [DataDefinition]
_datadefs = [],
_configFiles :: [String]
_configFiles = [],
_inputs :: [QuantityDict]
_inputs = [] :: [QuantityDict],
_outputs :: [QuantityDict]
_outputs = [] :: [QuantityDict],
_defSequence :: [Block SimpleQDef]
_defSequence = [] :: [Block SimpleQDef],
_constraints :: [ConstrainedChunk]
_constraints = [] :: [ConstrainedChunk],
_constants :: [ConstQDef]
_constants = [] :: [ConstQDef],
_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 ((UnitalChunk -> QuantityDict) -> [UnitalChunk] -> [QuantityDict]
forall a b. (a -> b) -> [a] -> [b]
map UnitalChunk -> QuantityDict
forall q. (Quantity q, MayHaveUnit q) => q -> QuantityDict
qw [UnitalChunk]
physicscon) (CI -> IdeaDict
forall c. Idea c => c -> IdeaDict
nw CI
projectileMotion 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]
++
(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]
physicCon [IdeaDict] -> [IdeaDict] -> [IdeaDict]
forall a. [a] -> [a] -> [a]
++ [IdeaDict]
concepts [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)
([] :: [ConceptChunk]) ([] :: [UnitDefn]) [] [] [] [] [] [] [] [Reference]
allRefs
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]) ([] :: [IdeaDict]) ([] :: [ConceptChunk])
([] :: [UnitDefn]) [] [] [] [] ([] :: [ConceptInstance])
([] :: [Section]) ([] :: [LabelledContent]) ([] :: [Reference])
refDB :: ReferenceDB
refDB :: ReferenceDB
refDB = BibRef -> [ConceptInstance] -> ReferenceDB
rdb [] []
projectileMotion :: CI
projectileMotion :: CI
projectileMotion = String -> NP -> String -> [UID] -> CI
commonIdea "projectileMotion" (String -> NP
pn "Projectile Motion") "Projectile Motion" []
mAndaintro :: Contents
mAndaintro :: Contents
mAndaintro = [Sentence] -> Contents
foldlSP
[String -> Sentence
S "Free-flight", NamedChunk -> Sentence
forall n. (HasUID n, NamedIdea n) => n -> Sentence
phrase NamedChunk
projMotion, String -> Sentence
S "problems can be solved using the following procedure"]
allRefs :: [Reference]
allRefs :: [Reference]
allRefs = [Reference] -> [Reference]
forall a. Eq a => [a] -> [a]
nub ([Reference]
figRefs [Reference] -> [Reference] -> [Reference]
forall a. [a] -> [a] -> [a]
++ [Reference]
eqnRefs)