module Drasil.GamePhysics.Body where
import Control.Lens ((^.))
import Data.Maybe (mapMaybe)
import Language.Drasil hiding (organization, section)
import Drasil.SRSDocument
import qualified Drasil.DocLang.SRS as SRS
import Theory.Drasil (qdEFromDD, output)
import Language.Drasil.Chunk.Concept.NamedCombinators
import qualified Language.Drasil.Sentence.Combinators as S
import Data.Drasil.Concepts.Computation (algorithm)
import Data.Drasil.Concepts.Documentation as Doc (assumption, concept,
condition, consumer, endUser, environment, game, guide, input_, interface,
object, physical, physicalSim, physics, problem, product_, project,
quantity, realtime, section_, simulation, software, softwareSys,
srsDomains, system, systemConstraint, sysCont, task, user, doccon, doccon',
property, problemDescription)
import qualified Data.Drasil.Concepts.Documentation as Doc (srs)
import Data.Drasil.TheoryConcepts as Doc (dataDefn, inModel)
import Data.Drasil.Concepts.Education (frstYr, highSchoolCalculus,
highSchoolPhysics, educon)
import Data.Drasil.Concepts.Software (physLib, softwarecon)
import Data.Drasil.People (alex, luthfi, olu)
import Data.Drasil.SI_Units (metre, kilogram, second, newton, radian,
derived, fundamentals, joule)
import Data.Drasil.Software.Products (openSource, prodtcon, videoGame)
import qualified Data.Drasil.Concepts.PhysicalProperties as CPP (ctrOfMass, dimension)
import qualified Data.Drasil.Concepts.Physics as CP (elasticity, physicCon, rigidBody, collision, damping)
import qualified Data.Drasil.Concepts.Math as CM (cartesian, equation, law,
mathcon, mathcon', rightHand, line, point)
import qualified Data.Drasil.Quantities.Physics as QP (force, time)
import Drasil.GamePhysics.Assumptions (assumptions)
import Drasil.GamePhysics.Changes (likelyChgs, unlikelyChgs)
import Drasil.GamePhysics.Concepts (gamePhysics, acronyms, threeD, twoD)
import Drasil.GamePhysics.DataDefs (dataDefs)
import Drasil.GamePhysics.Goals (goals)
import Drasil.GamePhysics.IMods (iMods, instModIntro)
import Drasil.GamePhysics.References (citations)
import Drasil.GamePhysics.Requirements (funcReqs, nonfuncReqs)
import Drasil.GamePhysics.TMods (tMods)
import Drasil.GamePhysics.Unitals (symbolsAll, outputConstraints,
inputSymbols, outputSymbols, inputConstraints, defSymbols)
import Drasil.GamePhysics.GenDefs (generalDefns)
srs :: Document
srs :: Document
srs = SRSDecl
-> (IdeaDict -> IdeaDict -> Sentence)
-> SystemInformation
-> Document
mkDoc SRSDecl
mkSRS (forall c d.
(c -> Sentence) -> (d -> Sentence) -> c -> d -> Sentence
S.forGen forall n. NamedIdea n => n -> Sentence
titleize forall c. Idea c => c -> Sentence
short) 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/gamephysics/"
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]
tableOfSymbols, RefTab
TAandA],
IntroSec -> DocSection
IntroSec forall a b. (a -> b) -> a -> b
$ Sentence -> Sentence -> [IntroSub] -> IntroSec
IntroProg Sentence
para1_introduction_intro (forall c. Idea c => c -> Sentence
short CI
gamePhysics)
[[Sentence] -> IntroSub
IPurpose forall a b. (a -> b) -> a -> b
$ CI -> Verbosity -> [Sentence]
purpDoc CI
gamePhysics Verbosity
Verbose,
Sentence -> IntroSub
IScope Sentence
scope,
[Sentence] -> [Sentence] -> [Sentence] -> IntroSub
IChar [] [String -> Sentence
S String
"rigid body dynamics", forall n. NamedIdea n => n -> Sentence
phrase IdeaDict
highSchoolCalculus] [],
CI -> Section -> Sentence -> IntroSub
IOrgSec CI
inModel ([Contents] -> [Section] -> Section
SRS.inModel [] []) Sentence
EmptyS],
GSDSec -> DocSection
GSDSec forall a b. (a -> b) -> a -> b
$ [GSDSub] -> GSDSec
GSDProg [
[Contents] -> GSDSub
SysCntxt [Contents
sysCtxIntro, LabelledContent -> Contents
LlC LabelledContent
sysCtxFig1, Contents
sysCtxDesc, Contents
sysCtxList],
[Contents] -> GSDSub
UsrChars [Contents
userCharacteristicsIntro], [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
probDescIntro []
[ forall c. Concept c => Maybe Sentence -> [c] -> PDSub
TermsAndDefs forall a. Maybe a
Nothing [ConceptChunk]
terms
, [Sentence] -> PDSub
Goals [String -> Sentence
S String
"the kinematic" Sentence -> Sentence -> Sentence
+:+ forall n. NamedIdea n => n -> Sentence
plural IdeaDict
property Sentence -> Sentence -> Sentence
`sC` String -> Sentence
S String
"and" Sentence -> Sentence -> Sentence
+:+ forall n. NamedIdea n => n -> Sentence
plural UnitalChunk
QP.force Sentence -> Sentence -> Sentence
+:+
Sentence -> Sentence
sParen (String -> Sentence
S String
"including any" Sentence -> Sentence -> Sentence
+:+ forall n. NamedIdea n => n -> Sentence
phrase ConceptChunk
CP.collision Sentence -> Sentence -> Sentence
+:+ forall n. NamedIdea n => n -> Sentence
plural UnitalChunk
QP.force) Sentence -> Sentence -> Sentence
+:+
String -> Sentence
S String
"applied on a set of" Sentence -> Sentence -> Sentence
+:+ forall n. NamedIdea n => n -> Sentence
plural ConceptChunk
CP.rigidBody]]
, 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
EmptyS [UncertQ]
inputConstraints
, forall c.
(Quantity c, Constrained c) =>
[c] -> [Contents] -> SCSSub
CorrSolnPpties [UncertQ]
outputConstraints []
]
],
ReqrmntSec -> DocSection
ReqrmntSec forall a b. (a -> b) -> a -> b
$ [ReqsSub] -> ReqrmntSec
ReqsProg [
[LabelledContent] -> ReqsSub
FReqsSub' [],
ReqsSub
NonFReqsSub
],
DocSection
LCsSec,
DocSection
UCsSec,
OffShelfSolnsSec -> DocSection
OffShelfSolnsSec forall a b. (a -> b) -> a -> b
$ [Contents] -> OffShelfSolnsSec
OffShelfSolnsProg [Contents]
offShelfSols,
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
gamePhysics [],
DocSection
Bibliography]
where tableOfSymbols :: [TSIntro]
tableOfSymbols = [TSIntro
TSPurpose, [TConvention] -> TSIntro
TypogConvention[Emphasis -> TConvention
Vector Emphasis
Bold], TSIntro
SymbOrder, TSIntro
VectorUnits]
si :: SystemInformation
si :: SystemInformation
si = SI {
_sys :: CI
_sys = CI
gamePhysics,
_kind :: CI
_kind = CI
Doc.srs,
_authors :: [Person]
_authors = [Person
alex, Person
luthfi, Person
olu],
_purpose :: [Sentence]
_purpose = [Sentence
purp],
_background :: [Sentence]
_background = [],
_quants :: [QuantityDict]
_quants = [] :: [QuantityDict],
_concepts :: [DefinedQuantityDict]
_concepts = [] :: [DefinedQuantityDict],
_instModels :: [InstanceModel]
_instModels = [InstanceModel]
iMods,
_datadefs :: [DataDefinition]
_datadefs = [DataDefinition]
dataDefs,
_configFiles :: [String]
_configFiles = [],
_inputs :: [QuantityDict]
_inputs = [QuantityDict]
inputSymbols,
_outputs :: [QuantityDict]
_outputs = [QuantityDict]
outputSymbols,
_defSequence :: [Block SimpleQDef]
_defSequence = forall a b. (a -> b) -> [a] -> [b]
map (forall a. a -> [a] -> Block a
`Parallel` []) [SimpleQDef]
qDefs,
_constraints :: [UncertQ]
_constraints = [UncertQ]
inputConstraints,
_constants :: [ConstQDef]
_constants = [],
_sysinfodb :: ChunkDB
_sysinfodb = ChunkDB
symbMap,
_usedinfodb :: ChunkDB
_usedinfodb = ChunkDB
usedDB,
refdb :: ReferenceDB
refdb = ReferenceDB
refDB
}
where qDefs :: [SimpleQDef]
qDefs = forall a b. (a -> Maybe b) -> [a] -> [b]
mapMaybe DataDefinition -> Maybe SimpleQDef
qdEFromDD [DataDefinition]
dataDefs
purp :: Sentence
purp :: Sentence
purp = [Sentence] -> Sentence
foldlSent_ [String -> Sentence
S String
"simulate", CI -> Sentence
getAcc CI
twoD, forall n. NamedIdea n => n -> Sentence
phrase ConceptChunk
CP.rigidBody,
forall n. NamedIdea n => n -> Sentence
phrase IdeaDict
Doc.physics, String -> Sentence
S String
"for use in", forall n. NamedIdea n => n -> Sentence
phrase IdeaDict
game, String -> Sentence
S String
"development"]
concIns :: [ConceptInstance]
concIns :: [ConceptInstance]
concIns = [ConceptInstance]
assumptions forall a. [a] -> [a] -> [a]
++ [ConceptInstance]
goals forall a. [a] -> [a] -> [a]
++ [ConceptInstance]
likelyChgs forall a. [a] -> [a] -> [a]
++ [ConceptInstance]
unlikelyChgs forall a. [a] -> [a] -> [a]
++ [ConceptInstance]
funcReqs forall a. [a] -> [a] -> [a]
++ [ConceptInstance]
nonfuncReqs
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]
refDB :: ReferenceDB
refDB :: ReferenceDB
refDB = BibRef -> [ConceptInstance] -> ReferenceDB
rdb BibRef
citations [ConceptInstance]
concIns
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, UnitDefn
joule] forall a. [a] -> [a] -> [a]
++ forall a b. (a -> b) -> [a] -> [b]
map forall u. IsUnit u => u -> UnitDefn
unitWrapper [UnitDefn
newton, UnitDefn
radian]
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 (forall a b. (a -> b) -> [a] -> [b]
map (forall s a. s -> Getting a s a -> a
^. forall c. HasOutput c => Getter c QuantityDict
output) [InstanceModel]
iMods 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 c. Idea c => c -> IdeaDict
nw CI
gamePhysics forall a. a -> [a] -> [a]
:
forall a b. (a -> b) -> [a] -> [b]
map forall c. Idea c => c -> IdeaDict
nw [QuantityDict]
symbolsAll 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 [IdeaDict]
prodtcon forall a. [a] -> [a] -> [a]
++ forall a b. (a -> b) -> [a] -> [b]
map forall c. Idea c => c -> IdeaDict
nw [GenDefn]
generalDefns
forall a. [a] -> [a] -> [a]
++ forall a b. (a -> b) -> [a] -> [b]
map forall c. Idea c => c -> IdeaDict
nw [InstanceModel]
iMods forall a. [a] -> [a] -> [a]
++ forall a b. (a -> b) -> [a] -> [b]
map (forall c. Idea c => c -> IdeaDict
nw forall b c a. (b -> c) -> (a -> b) -> a -> c
. (forall s a. s -> Getting a s a -> a
^. forall c. HasOutput c => Getter c QuantityDict
output)) [InstanceModel]
iMods 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 [IdeaDict]
doccon 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]
CP.physicCon 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 c. Idea c => c -> IdeaDict
nw ConceptChunk
algorithm] 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 [UnitDefn]
fundamentals
forall a. [a] -> [a] -> [a]
++ forall a b. (a -> b) -> [a] -> [b]
map forall c. Idea c => c -> IdeaDict
nw [ConceptChunk]
CM.mathcon forall a. [a] -> [a] -> [a]
++ forall a b. (a -> b) -> [a] -> [b]
map forall c. Idea c => c -> IdeaDict
nw [CI]
CM.mathcon')
(forall a b. (a -> b) -> [a] -> [b]
map forall c. Concept c => c -> ConceptChunk
cw [DefinedQuantityDict]
defSymbols forall a. [a] -> [a] -> [a]
++ [ConceptChunk]
srsDomains forall a. [a] -> [a] -> [a]
++ forall a b. (a -> b) -> [a] -> [b]
map forall c. Concept c => c -> ConceptChunk
cw [InstanceModel]
iMods) [UnitDefn]
units [DataDefinition]
dataDefs
[InstanceModel]
iMods [GenDefn]
generalDefns [TheoryModel]
tMods [ConceptInstance]
concIns [Section]
section [] []
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 a b. (a -> b) -> [a] -> [b]
map forall c. Idea c => c -> IdeaDict
nw [QuantityDict]
symbolsAll 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])
para1_introduction_intro :: Sentence
para1_introduction_intro :: Sentence
para1_introduction_intro = [Sentence] -> Sentence
foldlSent
[String -> Sentence
S String
"Due to the rising cost of developing", forall n. NamedIdea n => n -> Sentence
plural IdeaDict
videoGame Sentence -> Sentence -> Sentence
`sC`
String -> Sentence
S String
"developers are looking for ways to save time and money for their" Sentence -> Sentence -> Sentence
+:+.
forall n. NamedIdea n => n -> Sentence
plural IdeaDict
project, String -> Sentence
S String
"Using an", forall n. NamedIdea n => n -> Sentence
phrase IdeaDict
openSource,
forall n. NamedIdea n => n -> Sentence
phrase ConceptChunk
physLib,
String -> Sentence
S String
"that is reliable and free will cut down development costs and lead",
String -> Sentence
S String
"to better quality", forall n. NamedIdea n => n -> Sentence
plural IdeaDict
product_]
scope :: Sentence
scope :: Sentence
scope = [Sentence] -> Sentence
foldlSent_ [forall n. NounPhrase n => n -> Sentence
phraseNP (forall t. NamedIdea t => t -> NP
the IdeaDict
physicalSim) Sentence -> Sentence -> Sentence
`S.of_` CI -> Sentence
getAcc CI
twoD,
forall n. NamedIdea n => n -> Sentence
plural ConceptChunk
CP.rigidBody, String -> Sentence
S String
"acted on by", forall n. NamedIdea n => n -> Sentence
plural UnitalChunk
QP.force]
sysCtxIntro :: Contents
sysCtxIntro :: Contents
sysCtxIntro = [Sentence] -> Contents
foldlSP
[forall r.
(HasUID r, HasRefAddress r, HasShortName r) =>
r -> Sentence
refS LabelledContent
sysCtxFig1, String -> Sentence
S String
"shows the" Sentence -> Sentence -> Sentence
+:+. forall n. NamedIdea n => n -> Sentence
phrase IdeaDict
sysCont,
String -> Sentence
S String
"A circle represents an entity external to the", forall n. NamedIdea n => n -> Sentence
phrase IdeaDict
software
Sentence -> Sentence -> Sentence
`sC` forall n. NounPhrase n => n -> Sentence
phraseNP (forall t. NamedIdea t => t -> NP
the IdeaDict
user), String -> Sentence
S String
"in this case. A rectangle represents the",
forall n. NamedIdea n => n -> Sentence
phrase IdeaDict
softwareSys, String -> Sentence
S String
"itself", Sentence -> Sentence
sParen (forall c. Idea c => c -> Sentence
short CI
gamePhysics) Sentence -> Sentence -> Sentence
+:+. Sentence
EmptyS,
String -> Sentence
S String
"Arrows are used to show the data flow between the", forall n. NounPhrase n => n -> Sentence
phraseNP (IdeaDict
system
forall c d. (NamedIdea c, NamedIdea d) => c -> d -> NP
`andIts` IdeaDict
environment)]
sysCtxFig1 :: LabelledContent
sysCtxFig1 :: LabelledContent
sysCtxFig1 = Reference -> RawContent -> LabelledContent
llcc (String -> Reference
makeFigRef String
"sysCtxDiag") forall a b. (a -> b) -> a -> b
$ Sentence -> String -> RawContent
fig (forall n. NamedIdea n => n -> Sentence
titleize IdeaDict
sysCont)
(String
resourcePath forall a. [a] -> [a] -> [a]
++ String
"sysctx.png")
sysCtxDesc :: Contents
sysCtxDesc :: Contents
sysCtxDesc = [Sentence] -> Contents
foldlSPCol [String -> Sentence
S String
"The interaction between the", forall n. NounPhrase n => n -> Sentence
phraseNP (IdeaDict
product_
forall c d. (NamedIdea c, NamedIdea d) => c -> d -> NP
`andThe` IdeaDict
user), String -> Sentence
S String
"is through an application programming" Sentence -> Sentence -> Sentence
+:+.
forall n. NamedIdea n => n -> Sentence
phrase IdeaDict
interface, String -> Sentence
S String
"The responsibilities of the", forall n. NounPhrase n => n -> Sentence
phraseNP (IdeaDict
user
forall c d. (NamedIdea c, NamedIdea d) => c -> d -> NP
`andThe` IdeaDict
system), String -> Sentence
S String
"are as follows"]
sysCtxUsrResp :: [Sentence]
sysCtxUsrResp :: [Sentence]
sysCtxUsrResp = [String -> Sentence
S String
"Provide initial" Sentence -> Sentence -> Sentence
+:+ forall n. NounPhrase n => n -> Sentence
pluralNP (IdeaDict
condition forall c d. (NamedIdea c, NamedIdea d) => c -> d -> NP
`ofThePS`
IdeaDict
physical) Sentence -> Sentence -> Sentence
+:+ String -> Sentence
S String
"state of the" Sentence -> Sentence -> Sentence
+:+ forall n. NamedIdea n => n -> Sentence
phrase IdeaDict
simulation Sentence -> Sentence -> Sentence
`sC`
forall n. NamedIdea n => n -> Sentence
plural ConceptChunk
CP.rigidBody Sentence -> Sentence -> Sentence
+:+ String -> Sentence
S String
"present, and" Sentence -> Sentence -> Sentence
+:+ forall n. NamedIdea n => n -> Sentence
plural UnitalChunk
QP.force Sentence -> Sentence -> Sentence
+:+.
String -> Sentence
S String
"applied to them",
String -> Sentence
S String
"Ensure application programming" Sentence -> Sentence -> Sentence
+:+ forall n. NamedIdea n => n -> Sentence
phrase IdeaDict
interface Sentence -> Sentence -> Sentence
+:+
String -> Sentence
S String
"use complies with the" Sentence -> Sentence -> Sentence
+:+ forall n. NamedIdea n => n -> Sentence
phrase IdeaDict
user Sentence -> Sentence -> Sentence
+:+. forall n. NamedIdea n => n -> Sentence
phrase IdeaDict
guide,
String -> Sentence
S String
"Ensure required" Sentence -> Sentence -> Sentence
+:+
forall r.
(HasUID r, HasRefAddress r, HasShortName r) =>
r -> Sentence -> Sentence
namedRef ([Contents] -> [Section] -> Section
SRS.assumpt ([]::[Contents]) ([]::[Section])) (forall n. NamedIdea n => n -> Sentence
phrase IdeaDict
software Sentence -> Sentence -> Sentence
+:+ forall n. NamedIdea n => n -> Sentence
plural CI
assumption) Sentence -> Sentence -> Sentence
+:+
String -> Sentence
S String
"are appropriate for any particular" Sentence -> Sentence -> Sentence
+:+
forall n. NamedIdea n => n -> Sentence
phrase IdeaDict
problem Sentence -> Sentence -> Sentence
+:+ forall n. NounPhrase n => n -> Sentence
phraseNP (forall t. NamedIdea t => t -> NP
the IdeaDict
software) Sentence -> Sentence -> Sentence
+:+. String -> Sentence
S String
"addresses"]
sysCtxSysResp :: [Sentence]
sysCtxSysResp :: [Sentence]
sysCtxSysResp = [String -> Sentence
S String
"Determine if the" Sentence -> Sentence -> Sentence
+:+ forall n. NounPhrase n => n -> Sentence
pluralNP (IdeaDict
input_ forall c d. (NamedIdea c, NamedIdea d) => c -> d -> NP
`and_PS`
IdeaDict
simulation) Sentence -> Sentence -> Sentence
+:+ String -> Sentence
S String
"state satisfy the required" Sentence -> Sentence -> Sentence
+:+.
forall r.
(HasUID r, HasRefAddress r, HasShortName r) =>
r -> Sentence -> Sentence
namedRef ([Contents] -> [Section] -> Section
SRS.datCon ([]::[Contents]) ([]::[Section])) (forall n. NamedIdea n => n -> Sentence
phrase IdeaDict
physical Sentence -> Sentence -> Sentence
`S.and_` forall n. NamedIdea n => n -> Sentence
plural IdeaDict
systemConstraint),
String -> Sentence
S String
"Calculate the new state of all" Sentence -> Sentence -> Sentence
+:+ forall n. NamedIdea n => n -> Sentence
plural ConceptChunk
CP.rigidBody Sentence -> Sentence -> Sentence
+:+
String -> Sentence
S String
"within the" Sentence -> Sentence -> Sentence
+:+ forall n. NamedIdea n => n -> Sentence
phrase IdeaDict
simulation Sentence -> Sentence -> Sentence
+:+ String -> Sentence
S String
"at each" Sentence -> Sentence -> Sentence
+:+
forall n. NamedIdea n => n -> Sentence
phrase IdeaDict
simulation Sentence -> Sentence -> Sentence
+:+. String -> Sentence
S String
"step",
String -> Sentence
S String
"Provide updated" Sentence -> Sentence -> Sentence
+:+ forall n. NamedIdea n => n -> Sentence
phrase IdeaDict
physical Sentence -> Sentence -> Sentence
+:+ String -> Sentence
S String
"state of all" Sentence -> Sentence -> Sentence
+:+
forall n. NamedIdea n => n -> Sentence
plural ConceptChunk
CP.rigidBody Sentence -> Sentence -> Sentence
+:+ String -> Sentence
S String
"at the end of a" Sentence -> Sentence -> Sentence
+:+ forall n. NamedIdea n => n -> Sentence
phrase IdeaDict
simulation Sentence -> Sentence -> Sentence
+:+.
String -> Sentence
S String
"step"]
sysCtxResp :: [Sentence]
sysCtxResp :: [Sentence]
sysCtxResp = [forall n. NamedIdea n => n -> Sentence
titleize IdeaDict
user Sentence -> Sentence -> Sentence
+:+ String -> Sentence
S String
"Responsibilities",
forall c. Idea c => c -> Sentence
short CI
gamePhysics Sentence -> Sentence -> Sentence
+:+ String -> Sentence
S String
"Responsibilities"]
sysCtxList :: Contents
sysCtxList :: Contents
sysCtxList = UnlabelledContent -> Contents
UlC forall a b. (a -> b) -> a -> b
$ RawContent -> UnlabelledContent
ulcc forall a b. (a -> b) -> a -> b
$ ListType -> RawContent
Enumeration forall a b. (a -> b) -> a -> b
$ [Sentence] -> [ListType] -> ListType
bulletNested [Sentence]
sysCtxResp forall a b. (a -> b) -> a -> b
$
forall a b. (a -> b) -> [a] -> [b]
map [Sentence] -> ListType
bulletFlat [[Sentence]
sysCtxUsrResp, [Sentence]
sysCtxSysResp]
userCharacteristicsIntro :: Contents
userCharacteristicsIntro :: Contents
userCharacteristicsIntro = [Sentence] -> Contents
foldlSP
[String -> Sentence
S String
"The", forall n. NamedIdea n => n -> Sentence
phrase IdeaDict
endUser Sentence -> Sentence -> Sentence
`S.of_` forall c. Idea c => c -> Sentence
short CI
gamePhysics,
String -> Sentence
S String
"should have an understanding of", forall n. NamedIdea n => n -> Sentence
phrase IdeaDict
frstYr, String -> Sentence
S String
"programming",
forall n. NamedIdea n => n -> Sentence
plural IdeaDict
concept Sentence -> Sentence -> Sentence
`S.and_` String -> Sentence
S String
"an understanding of", forall n. NamedIdea n => n -> Sentence
phrase IdeaDict
highSchoolPhysics]
probDescIntro :: Sentence
probDescIntro :: Sentence
probDescIntro = [Sentence] -> Sentence
foldlSent_
[Sentence
purp, String -> Sentence
S String
"in a", SepType -> FoldType -> [Sentence] -> Sentence
foldlList SepType
Comma FoldType
List forall a b. (a -> b) -> a -> b
$ forall a b. (a -> b) -> [a] -> [b]
map String -> Sentence
S [String
"simple", String
"lightweight", String
"fast", String
"portable"],
String -> Sentence
S String
"manner" Sentence -> Sentence -> Sentence
`sC` String -> Sentence
S String
"which will allow for the production of higher quality" Sentence -> Sentence -> Sentence
+:+. forall n. NamedIdea n => n -> Sentence
plural IdeaDict
product_,
String -> Sentence
S String
"Creating a gaming", forall n. NamedIdea n => n -> Sentence
phrase ConceptChunk
physLib, String -> Sentence
S String
"is a difficult" Sentence -> Sentence -> Sentence
+:+. forall n. NamedIdea n => n -> Sentence
phrase IdeaDict
task, forall n. NamedIdea n => n -> Sentence
titleize' IdeaDict
game,
String -> Sentence
S String
"need", forall n. NamedIdea n => n -> Sentence
plural ConceptChunk
physLib, String -> Sentence
S String
"that simulate", forall n. NamedIdea n => n -> Sentence
plural IdeaDict
object, String -> Sentence
S String
"acting under various", forall n. NamedIdea n => n -> Sentence
phrase IdeaDict
physical,
forall n. NamedIdea n => n -> Sentence
plural IdeaDict
condition Sentence -> Sentence -> Sentence
`sC` String -> Sentence
S String
"while simultaneously being fast and efficient enough to work in soft",
forall n. NamedIdea n => n -> Sentence
phrase IdeaDict
realtime, String -> Sentence
S String
"during the" Sentence -> Sentence -> Sentence
+:+. forall n. NamedIdea n => n -> Sentence
phrase IdeaDict
game, String -> Sentence
S String
"Developing a",
forall n. NamedIdea n => n -> Sentence
phrase ConceptChunk
physLib, String -> Sentence
S String
"from scratch takes a long period" Sentence -> Sentence -> Sentence
`S.of_` forall n. NamedIdea n => n -> Sentence
phrase UnitalChunk
QP.time Sentence -> Sentence -> Sentence
`S.and_`
String -> Sentence
S String
"is very costly" Sentence -> Sentence -> Sentence
`sC` String -> Sentence
S String
"presenting barriers of entry which make it difficult for",
forall n. NamedIdea n => n -> Sentence
phrase IdeaDict
game, String -> Sentence
S String
"developers to include", forall n. NamedIdea n => n -> Sentence
phrase IdeaDict
Doc.physics, String -> Sentence
S String
"in their" Sentence -> Sentence -> Sentence
+:+.
forall n. NamedIdea n => n -> Sentence
plural IdeaDict
product_, String -> Sentence
S String
"There are a few free" Sentence -> Sentence -> Sentence
`sC` forall n. NamedIdea n => n -> Sentence
phrase IdeaDict
openSource Sentence -> Sentence -> Sentence
`S.and_` String -> Sentence
S String
"high quality",
forall r.
(HasUID r, HasRefAddress r, HasShortName r) =>
r -> Sentence -> Sentence
namedRef ([Contents] -> [Section] -> Section
SRS.offShelfSol ([] :: [Contents]) ([] :: [Section])) (forall n. NamedIdea n => n -> Sentence
plural ConceptChunk
physLib),
String -> Sentence
S String
"available to be used for", forall n. NamedIdea n => n -> Sentence
phrase IdeaDict
consumer, forall n. NamedIdea n => n -> Sentence
plural IdeaDict
product_]
terms :: [ConceptChunk]
terms :: [ConceptChunk]
terms = [ConceptChunk
CP.rigidBody, ConceptChunk
CP.elasticity, ConceptChunk
CPP.ctrOfMass, ConceptChunk
CM.cartesian, ConceptChunk
CM.rightHand, ConceptChunk
CM.line, ConceptChunk
CM.point, ConceptChunk
CP.damping]
generalDefinitionsIntro :: Contents
generalDefinitionsIntro :: Contents
generalDefinitionsIntro = [Sentence] -> Contents
foldlSP
[String -> Sentence
S String
"This", forall n. NamedIdea n => n -> Sentence
phrase IdeaDict
section_, String -> Sentence
S String
"collects the", forall n. NounPhrase n => n -> Sentence
pluralNP (ConceptChunk
CM.law forall c d. (NamedIdea c, NamedIdea d) => c -> d -> NP
`and_PP`
ConceptChunk
CM.equation), String -> Sentence
S String
"that will be used in deriving the",
forall n. NamedIdea n => n -> Sentence
plural CI
dataDefn Sentence -> Sentence -> Sentence
`sC` String -> Sentence
S String
"which in turn will be used to build the",
forall n. NamedIdea n => n -> Sentence
plural CI
inModel]
dataDefinitionsIntro :: Sentence
dataDefinitionsIntro :: Sentence
dataDefinitionsIntro = [Sentence] -> Sentence
foldlSent [forall n. NounPhrase n => n -> Sentence
atStartNP (forall t. NamedIdea t => t -> NP
the ConceptChunk
CPP.dimension)
Sentence -> Sentence -> Sentence
`S.of_` String -> Sentence
S String
"each", forall n. NamedIdea n => n -> Sentence
phrase IdeaDict
quantity, String -> Sentence
S String
"is also given"]
offShelfSols :: [Contents]
offShelfSols :: [Contents]
offShelfSols = [Contents
offShelfSolsIntro, Contents
offShelfSols2DList,
Contents
offShelfSolsMid, Contents
offShelfSols3DList]
offShelfSolsIntro, offShelfSols2DList,
offShelfSolsMid, offShelfSols3DList :: Contents
offShelfSolsIntro :: Contents
offShelfSolsIntro = Sentence -> Contents
mkParagraph forall a b. (a -> b) -> a -> b
$ [Sentence] -> Sentence
foldlSentCol
[String -> Sentence
S String
"As mentioned in the", forall r.
(HasUID r, HasRefAddress r, HasShortName r) =>
r -> Sentence -> Sentence
namedRef ([Contents] -> [Section] -> Section
SRS.probDesc [] []) (forall n. NamedIdea n => n -> Sentence
phrase IdeaDict
problemDescription) Sentence -> Sentence -> Sentence
`sC`
String -> Sentence
S String
"there already exist free", forall n. NamedIdea n => n -> Sentence
phrase IdeaDict
openSource, forall n. NamedIdea n => n -> Sentence
phrase IdeaDict
game Sentence -> Sentence -> Sentence
+:+.
forall n. NamedIdea n => n -> Sentence
plural ConceptChunk
physLib, String -> Sentence
S String
"Similar", CI -> Sentence
getAcc CI
twoD, forall n. NamedIdea n => n -> Sentence
plural ConceptChunk
physLib, String -> Sentence
S String
"are"]
offShelfSols2DList :: Contents
offShelfSols2DList = [Sentence] -> Contents
enumBulletU [String -> Sentence
S String
"Box2D: http://box2d.org/",
String -> Sentence
S String
"Nape Physics Engine: http://napephys.com/"]
offShelfSolsMid :: Contents
offShelfSolsMid = Sentence -> Contents
mkParagraph forall a b. (a -> b) -> a -> b
$ forall (t :: * -> *) b a.
Foldable t =>
(b -> a -> b) -> b -> t a -> b
foldl Sentence -> Sentence -> Sentence
(+:+) Sentence
EmptyS [String -> Sentence
S String
"Free", forall n. NamedIdea n => n -> Sentence
phrase IdeaDict
openSource,
CI -> Sentence
getAcc CI
threeD, forall n. NamedIdea n => n -> Sentence
phrase IdeaDict
game, forall n. NamedIdea n => n -> Sentence
plural ConceptChunk
physLib, String -> Sentence
S String
"include:"]
offShelfSols3DList :: Contents
offShelfSols3DList = [Sentence] -> Contents
enumBulletU [
String -> Sentence
S String
"Bullet: http://bulletphysics.org/",
String -> Sentence
S String
"Open Dynamics Engine: http://www.ode.org/",
String -> Sentence
S String
"Newton Game Dynamics: http://newtondynamics.com/"]