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, LsnDecl, LsnChapter(BibSec, LearnObj, Review, CaseProb, Example),
LearnObj(..), Review(..), CaseProb(..), Example(..))
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)
import Drasil.Projectile.Expressions (eqnRefs)
import Drasil.Projectile.Lesson.LearnObj (learnObjContext)
import Drasil.Projectile.Lesson.Review (reviewContent)
import Drasil.Projectile.Lesson.CaseProb (caseProbCont, figRefs)
import Drasil.Projectile.Lesson.Example (exampleContent, horiz_velo)
nb :: Document
nb :: Document
nb = LsnDecl
-> (IdeaDict -> IdeaDict -> Sentence)
-> SystemInformation
-> Document
mkNb LsnDecl
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. NamedIdea n => n -> Sentence
phrase) SystemInformation
si
printSetting :: PrintingInformation
printSetting :: PrintingInformation
printSetting = ChunkDB -> Stage -> PrintingConfiguration -> PrintingInformation
PI ChunkDB
symbMap Stage
Equational PrintingConfiguration
defaultConfiguration
mkNB :: LsnDecl
mkNB :: LsnDecl
mkNB = [
LearnObj -> LsnChapter
LearnObj (LearnObj -> LsnChapter) -> LearnObj -> LsnChapter
forall a b. (a -> b) -> a -> b
$ [Contents] -> LearnObj
LrnObjProg [Contents
learnObjContext],
Review -> LsnChapter
Review (Review -> LsnChapter) -> Review -> LsnChapter
forall a b. (a -> b) -> a -> b
$ [Contents] -> Review
ReviewProg [Contents]
reviewContent,
CaseProb -> LsnChapter
CaseProb (CaseProb -> LsnChapter) -> CaseProb -> LsnChapter
forall a b. (a -> b) -> a -> b
$ [Contents] -> CaseProb
CaseProbProg [Contents]
caseProbCont,
Example -> LsnChapter
Example (Example -> LsnChapter) -> Example -> LsnChapter
forall a b. (a -> b) -> a -> b
$ [Contents] -> Example
ExampleProg [Contents]
exampleContent,
LsnChapter
BibSec
]
si :: SystemInformation
si :: SystemInformation
si = SI {
_sys :: CI
_sys = CI
projectileMotion,
_kind :: CI
_kind = CI
Doc.notebook,
_authors :: People
_authors = [Person
spencerSmith],
_purpose :: Purpose
_purpose = [],
_background :: Purpose
_background = [],
_motivation :: Purpose
_motivation = [],
_scope :: Purpose
_scope = [],
_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 [QuantityDict] -> [QuantityDict] -> [QuantityDict]
forall a. [a] -> [a] -> [a]
++ [QuantityDict]
symbols) (CI -> IdeaDict
forall c. Idea c => c -> IdeaDict
nw CI
projectileMotion IdeaDict -> [IdeaDict] -> [IdeaDict]
forall a. a -> [a] -> [a]
: (IdeaDict -> IdeaDict) -> [IdeaDict] -> [IdeaDict]
forall a b. (a -> b) -> [a] -> [b]
map IdeaDict -> IdeaDict
forall c. Idea c => c -> IdeaDict
nw [IdeaDict]
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 [IdeaDict] -> [IdeaDict] -> [IdeaDict]
forall a. [a] -> [a] -> [a]
++ (QuantityDict -> IdeaDict) -> [QuantityDict] -> [IdeaDict]
forall a b. (a -> b) -> [a] -> [b]
map QuantityDict -> IdeaDict
forall c. Idea c => c -> IdeaDict
nw [QuantityDict]
symbols)
([] :: [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]) ((QuantityDict -> IdeaDict) -> [QuantityDict] -> [IdeaDict]
forall a b. (a -> b) -> [a] -> [b]
map QuantityDict -> IdeaDict
forall c. Idea c => c -> IdeaDict
nw [QuantityDict]
symbols :: [IdeaDict]) ([] :: [ConceptChunk])
([] :: [UnitDefn]) [] [] [] [] ([] :: [ConceptInstance])
([] :: [Section]) ([] :: [LabelledContent]) ([] :: [Reference])
symbols :: [QuantityDict]
symbols :: [QuantityDict]
symbols = [UnitalChunk -> QuantityDict
forall q. (Quantity q, MayHaveUnit q) => q -> QuantityDict
qw UnitalChunk
horiz_velo]
refDB :: ReferenceDB
refDB :: ReferenceDB
refDB = BibRef -> [ConceptInstance] -> ReferenceDB
rdb [] []
projectileMotion :: CI
projectileMotion :: CI
projectileMotion = String -> NP -> String -> [UID] -> CI
commonIdea String
"projectileMotion" (String -> NP
pn String
"Projectile Motion Lesson") String
"Projectile Motion" []
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)