module Drasil.Projectile.Lesson.Body where
import Data.List (nub)
import Language.Drasil hiding (Notebook)
import Language.Drasil.Printers (PrintingInformation(..), defaultConfiguration)
import Database.Drasil
import Database.Drasil.ChunkDB (cdb)
import Drasil.System
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.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) -> System -> 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) System
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 :: System
si :: System
si = CI
-> SystemKind
-> People
-> Purpose
-> Purpose
-> Purpose
-> Purpose
-> [DefinedQuantityDict]
-> [TheoryModel]
-> [GenDefn]
-> [DataDefinition]
-> [InstanceModel]
-> [String]
-> [DefinedQuantityDict]
-> [DefinedQuantityDict]
-> [ConstrConcept]
-> [ConstQDef]
-> ChunkDB
-> System
forall a e h i j.
(CommonIdea a, Idea a, Quantity e, Eq e, MayHaveUnit e, Concept e,
Quantity h, MayHaveUnit h, Concept h, Quantity i, MayHaveUnit i,
Concept i, HasUID j, Constrained j) =>
a
-> SystemKind
-> People
-> Purpose
-> Purpose
-> Purpose
-> Purpose
-> [e]
-> [TheoryModel]
-> [GenDefn]
-> [DataDefinition]
-> [InstanceModel]
-> [String]
-> [h]
-> [i]
-> [j]
-> [ConstQDef]
-> ChunkDB
-> System
mkSystem
CI
projectileMotion SystemKind
Notebook [Person
spencerSmith]
[] [] [] []
([] :: [DefinedQuantityDict])
[] [] [] [] []
([] :: [DefinedQuantityDict]) ([] :: [DefinedQuantityDict]) ([] :: [ConstrConcept]) []
ChunkDB
symbMap
symbMap :: ChunkDB
symbMap :: ChunkDB
symbMap = [DefinedQuantityDict]
-> [IdeaDict]
-> [ConceptChunk]
-> [UnitDefn]
-> [DataDefinition]
-> [InstanceModel]
-> [GenDefn]
-> [TheoryModel]
-> [ConceptInstance]
-> [LabelledContent]
-> [Reference]
-> [Citation]
-> ChunkDB
forall q c u.
(Quantity q, MayHaveUnit q, Concept q, Concept c, IsUnit u) =>
[q]
-> [IdeaDict]
-> [c]
-> [u]
-> [DataDefinition]
-> [InstanceModel]
-> [GenDefn]
-> [TheoryModel]
-> [ConceptInstance]
-> [LabelledContent]
-> [Reference]
-> [Citation]
-> ChunkDB
cdb ((UnitalChunk -> DefinedQuantityDict)
-> [UnitalChunk] -> [DefinedQuantityDict]
forall a b. (a -> b) -> [a] -> [b]
map UnitalChunk -> DefinedQuantityDict
forall c.
(Quantity c, Concept c, MayHaveUnit c) =>
c -> DefinedQuantityDict
dqdWr [UnitalChunk]
physicscon [DefinedQuantityDict]
-> [DefinedQuantityDict] -> [DefinedQuantityDict]
forall a. [a] -> [a] -> [a]
++ [DefinedQuantityDict]
symbols) (CI -> IdeaDict
forall c. Idea c => c -> IdeaDict
nw CI
projectileMotion 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)
([] :: [ConceptChunk]) ([] :: [UnitDefn]) [] [] [] [] [] [] [Reference]
allRefs []
usedDB :: ChunkDB
usedDB :: ChunkDB
usedDB = [DefinedQuantityDict]
-> [IdeaDict]
-> [ConceptChunk]
-> [UnitDefn]
-> [DataDefinition]
-> [InstanceModel]
-> [GenDefn]
-> [TheoryModel]
-> [ConceptInstance]
-> [LabelledContent]
-> [Reference]
-> [Citation]
-> ChunkDB
forall q c u.
(Quantity q, MayHaveUnit q, Concept q, Concept c, IsUnit u) =>
[q]
-> [IdeaDict]
-> [c]
-> [u]
-> [DataDefinition]
-> [InstanceModel]
-> [GenDefn]
-> [TheoryModel]
-> [ConceptInstance]
-> [LabelledContent]
-> [Reference]
-> [Citation]
-> ChunkDB
cdb' ([] :: [DefinedQuantityDict]) ((DefinedQuantityDict -> IdeaDict)
-> [DefinedQuantityDict] -> [IdeaDict]
forall a b. (a -> b) -> [a] -> [b]
map DefinedQuantityDict -> IdeaDict
forall c. Idea c => c -> IdeaDict
nw [DefinedQuantityDict]
symbols :: [IdeaDict]) ([] :: [ConceptChunk])
([] :: [UnitDefn]) [] [] [] [] ([] :: [ConceptInstance])
([] :: [LabelledContent]) ([] :: [Reference]) []
symbols :: [DefinedQuantityDict]
symbols :: [DefinedQuantityDict]
symbols = [UnitalChunk -> DefinedQuantityDict
forall c.
(Quantity c, Concept c, MayHaveUnit c) =>
c -> DefinedQuantityDict
dqdWr UnitalChunk
horiz_velo]
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)