{-# LANGUAGE PostfixOperators #-}
module Drasil.DblPendulum.Body where

import Language.Drasil hiding (organization, section)
import Theory.Drasil (TheoryModel)
import Drasil.SRSDocument
import qualified Drasil.DocLang.SRS as SRS

import Language.Drasil.Chunk.Concept.NamedCombinators
import qualified Language.Drasil.NounPhrase.Combinators as NP
import qualified Language.Drasil.Sentence.Combinators as S

import Data.Drasil.People (dong)
import Data.Drasil.SI_Units (metre, second, newton, kilogram, degree, radian, hertz)
import Data.Drasil.Concepts.Computation (inDatum, compcon, inValue, algorithm)
import qualified Data.Drasil.Concepts.Documentation as Doc (srs, physics, variable)
import Data.Drasil.Concepts.Documentation (assumption, condition, endUser, environment, datum, document,
  input_, interface, output_, organization, problem, product_, physical, sysCont, software, softwareConstraint,
  softwareSys, srsDomains, system, template, user, doccon, doccon', analysis)
import Data.Drasil.Concepts.Education (highSchoolPhysics, highSchoolCalculus, calculus, undergraduate, educon, )
import Data.Drasil.Concepts.Math (mathcon, cartesian, ode, mathcon', graph)
import Data.Drasil.Concepts.Physics (gravity, physicCon, physicCon', pendulum, twoD, motion)
import Data.Drasil.Concepts.PhysicalProperties (mass, len, physicalcon)
import Data.Drasil.Concepts.Software (program, errMsg)
import Data.Drasil.Quantities.Physics (physicscon)
import Data.Drasil.Quantities.Math (unitVect, unitVectj)
import Data.Drasil.Software.Products (prodtcon, sciCompS)
import Data.Drasil.Theories.Physics (newtonSL, accelerationTM, velocityTM, newtonSLR)
import Data.Drasil.TheoryConcepts (inModel)

import Drasil.DblPendulum.Figures (figMotion, sysCtxFig1)
import Drasil.DblPendulum.Assumptions (assumpDouble)
import Drasil.DblPendulum.Concepts (rod, concepts, pendMotion, progName, firstRod, secondRod, firstObject, secondObject)
import Drasil.DblPendulum.Goals (goals, goalsInputs)
import Drasil.DblPendulum.DataDefs (dataDefs)
import Drasil.DblPendulum.IMods (iMods)
import Drasil.DblPendulum.GenDefs (genDefns)
import Drasil.DblPendulum.Unitals (lenRod_1, lenRod_2, symbols, inputs, outputs,
  inConstraints, outConstraints, acronyms)
import Drasil.DblPendulum.Requirements (funcReqs, nonFuncReqs)
import Drasil.DblPendulum.References (citations, koothoor2013, smithLai2005)


srs :: Document
srs :: Document
srs = SRSDecl
-> (IdeaDict -> IdeaDict -> Sentence)
-> SystemInformation
-> Document
mkDoc SRSDecl
mkSRS ((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

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

mkSRS :: SRSDecl
mkSRS :: SRSDecl
mkSRS = [DocSection
TableOfContents, -- This creates the Table of Contents
  RefSec -> DocSection
RefSec (RefSec -> DocSection) -> RefSec -> DocSection
forall a b. (a -> b) -> a -> b
$      --This creates the Reference section of the SRS
    Contents -> [RefTab] -> RefSec
RefProg Contents
intro      -- This add the introduction blob to the reference section  
      [ RefTab
TUnits         -- Adds table of unit section with a table frame
      , [TSIntro] -> RefTab
tsymb [TSIntro
TSPurpose, [TConvention] -> TSIntro
TypogConvention [Emphasis -> TConvention
Vector Emphasis
Bold], TSIntro
SymbOrder, TSIntro
VectorUnits] -- Adds table of symbol section with a table frame
      --introductory blob (TSPurpose), TypogConvention, bolds vector parameters (Vector Bold), orders the symbol, and adds units to symbols 
      , RefTab
TAandA         -- Add table of abbreviation and acronym section
      ],
  IntroSec -> DocSection
IntroSec (IntroSec -> DocSection) -> IntroSec -> DocSection
forall a b. (a -> b) -> a -> b
$
    Sentence -> Sentence -> [IntroSub] -> IntroSec
IntroProg Sentence
justification (CI -> Sentence
forall n. (HasUID n, NamedIdea n) => n -> Sentence
phrase 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
organizationOfDocumentsIntro CI
inModel ([Contents] -> [Section] -> Section
SRS.inModel [] []) Sentence
EmptyS],
  GSDSec -> DocSection
GSDSec (GSDSec -> DocSection) -> GSDSec -> DocSection
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 (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
prob []                --  This adds a is used to define the problem your system will solve
        [ Maybe Sentence -> [ConceptChunk] -> PDSub
forall c. Concept c => Maybe Sentence -> [c] -> PDSub
TermsAndDefs Maybe Sentence
forall a. Maybe a
Nothing [ConceptChunk]
terms               -- This is used to define the terms to be defined in terminology sub section
      , CI -> [Sentence] -> LabelledContent -> [Contents] -> PDSub
forall a.
Idea a =>
a -> [Sentence] -> LabelledContent -> [Contents] -> PDSub
PhySysDesc CI
progName [Sentence]
physSystParts LabelledContent
figMotion [] -- This defines the Physicalsystem sub-section, define the parts
                                                          -- of the system using physSysParts, figMotion is a function in figures for the image
      , [Sentence] -> PDSub
Goals [Sentence]
goalsInputs] -- This adds a goals section and goals input is defined for the preample of the goal.
      , SolChSpec -> SSDSub
SSDSolChSpec (SolChSpec -> SSDSub) -> SolChSpec -> SSDSub
forall a b. (a -> b) -> a -> b
$ [SCSSub] -> SolChSpec
SCSProg --This creates the solution characteristics section with a preamble
        [ 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 [] ([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
EmptyS [UncertQ]
inConstraints
        , [UncertQ] -> [Contents] -> SCSSub
forall c.
(Quantity c, Constrained c) =>
[c] -> [Contents] -> SCSSub
CorrSolnPpties [UncertQ]
outConstraints []
       ]
     ],
  ReqrmntSec -> DocSection
ReqrmntSec (ReqrmntSec -> DocSection) -> ReqrmntSec -> DocSection
forall a b. (a -> b) -> a -> b
$ [ReqsSub] -> ReqrmntSec
ReqsProg
    [ Sentence -> [LabelledContent] -> ReqsSub
FReqsSub Sentence
EmptyS []
    , ReqsSub
NonFReqsSub
    ],
  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 [],  --Adds Auxilliary constraint section
  DocSection
Bibliography                    -- Adds reference section
  ]

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
progName, 
  _kind :: CI
_kind        = CI
Doc.srs,
  _authors :: [Person]
_authors     = [Person
dong],
  _purpose :: [Sentence]
_purpose     = CI -> Verbosity -> [Sentence]
purpDoc CI
progName Verbosity
Verbose,
  _quants :: [QuantityDict]
_quants      = [QuantityDict]
symbols,
  _concepts :: [DefinedQuantityDict]
_concepts    = [] :: [DefinedQuantityDict],
  _instModels :: [InstanceModel]
_instModels  = [InstanceModel]
iMods,
  _datadefs :: [DataDefinition]
_datadefs    = [DataDefinition]
dataDefs,
  _configFiles :: [String]
_configFiles = [],
  _inputs :: [QuantityDict]
_inputs      = [QuantityDict]
inputs,
  _outputs :: [QuantityDict]
_outputs     = [QuantityDict]
outputs,
  _defSequence :: [Block SimpleQDef]
_defSequence = [] :: [Block SimpleQDef],
  _constraints :: [UncertQ]
_constraints = [UncertQ]
inConstraints,
  _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 ((InstanceModel -> QuantityDict)
-> [InstanceModel] -> [QuantityDict]
forall a b. (a -> b) -> [a] -> [b]
map InstanceModel -> QuantityDict
forall q. (Quantity q, MayHaveUnit q) => q -> QuantityDict
qw [InstanceModel]
iMods [QuantityDict] -> [QuantityDict] -> [QuantityDict]
forall a. [a] -> [a] -> [a]
++ (QuantityDict -> QuantityDict) -> [QuantityDict] -> [QuantityDict]
forall a b. (a -> b) -> [a] -> [b]
map QuantityDict -> QuantityDict
forall q. (Quantity q, MayHaveUnit q) => q -> QuantityDict
qw [QuantityDict]
symbols)
  (TheoryModel -> IdeaDict
forall c. Idea c => c -> IdeaDict
nw TheoryModel
newtonSLR IdeaDict -> [IdeaDict] -> [IdeaDict]
forall a. a -> [a] -> [a]
: CI -> IdeaDict
forall c. Idea c => c -> IdeaDict
nw CI
progName IdeaDict -> [IdeaDict] -> [IdeaDict]
forall a. a -> [a] -> [a]
: ConceptChunk -> IdeaDict
forall c. Idea c => c -> IdeaDict
nw ConceptChunk
mass IdeaDict -> [IdeaDict] -> [IdeaDict]
forall a. a -> [a] -> [a]
: ConceptChunk -> IdeaDict
forall c. Idea c => c -> IdeaDict
nw ConceptChunk
len IdeaDict -> [IdeaDict] -> [IdeaDict]
forall a. a -> [a] -> [a]
: UnitDefn -> IdeaDict
forall c. Idea c => c -> IdeaDict
nw UnitDefn
kilogram IdeaDict -> [IdeaDict] -> [IdeaDict]
forall a. a -> [a] -> [a]
: NamedChunk -> IdeaDict
forall c. Idea c => c -> IdeaDict
nw NamedChunk
inValue IdeaDict -> [IdeaDict] -> [IdeaDict]
forall a. a -> [a] -> [a]
: UnitDefn -> IdeaDict
forall c. Idea c => c -> IdeaDict
nw UnitDefn
newton IdeaDict -> [IdeaDict] -> [IdeaDict]
forall a. a -> [a] -> [a]
: UnitDefn -> IdeaDict
forall c. Idea c => c -> IdeaDict
nw UnitDefn
degree IdeaDict -> [IdeaDict] -> [IdeaDict]
forall a. a -> [a] -> [a]
: UnitDefn -> IdeaDict
forall c. Idea c => c -> IdeaDict
nw UnitDefn
radian
    IdeaDict -> [IdeaDict] -> [IdeaDict]
forall a. a -> [a] -> [a]
: DefinedQuantityDict -> IdeaDict
forall c. Idea c => c -> IdeaDict
nw DefinedQuantityDict
unitVect IdeaDict -> [IdeaDict] -> [IdeaDict]
forall a. a -> [a] -> [a]
: DefinedQuantityDict -> IdeaDict
forall c. Idea c => c -> IdeaDict
nw DefinedQuantityDict
unitVectj IdeaDict -> [IdeaDict] -> [IdeaDict]
forall a. a -> [a] -> [a]
: [ConceptChunk -> IdeaDict
forall c. Idea c => c -> IdeaDict
nw ConceptChunk
errMsg, ConceptChunk -> IdeaDict
forall c. Idea c => c -> IdeaDict
nw ConceptChunk
program] [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 [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]
++ (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]
++ (CI -> IdeaDict) -> [CI] -> [IdeaDict]
forall a b. (a -> b) -> [a] -> [b]
map CI -> IdeaDict
forall c. Idea c => c -> IdeaDict
nw [CI]
physicCon' [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]
++ [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]
physicalcon [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]
acronyms [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 [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
metre, UnitDefn
hertz] [IdeaDict] -> [IdeaDict] -> [IdeaDict]
forall a. [a] -> [a] -> [a]
++
   [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) -> [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]
++ (NamedChunk -> IdeaDict) -> [NamedChunk] -> [IdeaDict]
forall a b. (a -> b) -> [a] -> [b]
map NamedChunk -> IdeaDict
forall c. Idea c => c -> IdeaDict
nw [NamedChunk]
prodtcon)
  ((InstanceModel -> ConceptChunk)
-> [InstanceModel] -> [ConceptChunk]
forall a b. (a -> b) -> [a] -> [b]
map InstanceModel -> ConceptChunk
forall c. Concept c => c -> ConceptChunk
cw [InstanceModel]
iMods [ConceptChunk] -> [ConceptChunk] -> [ConceptChunk]
forall a. [a] -> [a] -> [a]
++ [ConceptChunk]
srsDomains) ((UnitDefn -> UnitDefn) -> [UnitDefn] -> [UnitDefn]
forall a b. (a -> b) -> [a] -> [b]
map UnitDefn -> UnitDefn
forall u. IsUnit u => u -> UnitDefn
unitWrapper [UnitDefn
metre, UnitDefn
second, UnitDefn
newton, UnitDefn
kilogram, UnitDefn
degree, UnitDefn
radian, UnitDefn
hertz])
  [DataDefinition]
dataDefs [InstanceModel]
iMods [GenDefn]
genDefns [TheoryModel]
tMods [ConceptInstance]
concIns [] [] ([] :: [Reference])

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]) ((CI -> IdeaDict) -> [CI] -> [IdeaDict]
forall a b. (a -> b) -> [a] -> [b]
map CI -> IdeaDict
forall c. Idea c => c -> IdeaDict
nw [CI]
acronyms [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])

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

concIns :: [ConceptInstance]
concIns :: [ConceptInstance]
concIns = [ConceptInstance]
assumpDouble [ConceptInstance] -> [ConceptInstance] -> [ConceptInstance]
forall a. [a] -> [a] -> [a]
++ [ConceptInstance]
goals [ConceptInstance] -> [ConceptInstance] -> [ConceptInstance]
forall a. [a] -> [a] -> [a]
++ [ConceptInstance]
funcReqs [ConceptInstance] -> [ConceptInstance] -> [ConceptInstance]
forall a. [a] -> [a] -> [a]
++ [ConceptInstance]
nonFuncReqs
-- ++ likelyChgs ++ unlikelyChgs

------------------------------
-- Section : INTRODUCTION --
------------------------------
justification :: Sentence
justification :: Sentence
justification = [Sentence] -> Sentence
foldlSent [ NP -> Sentence
forall n. NounPhrase n => n -> Sentence
atStartNP (ConceptChunk -> NP
forall c. NamedIdea c => c -> NP
a_ ConceptChunk
pendulum), String -> Sentence
S "consists" Sentence -> Sentence -> Sentence
`S.of_` ConceptChunk -> Sentence
forall n. (HasUID n, NamedIdea n) => n -> Sentence
phrase ConceptChunk
mass, 
                            String -> Sentence
S "attached to the end" Sentence -> Sentence -> Sentence
`S.ofA` NamedChunk -> Sentence
forall n. (HasUID n, NamedIdea n) => n -> Sentence
phrase NamedChunk
rod Sentence -> Sentence -> Sentence
`S.andIts` String -> Sentence
S "moving curve" Sentence -> Sentence -> Sentence
`S.is`
                            (String -> Sentence
S "highly sensitive to initial conditions" Sentence -> Sentence
!.), String -> Sentence
S "Therefore" Sentence -> Sentence -> Sentence
`sC`
                            String -> Sentence
S "it is useful to have a", ConceptChunk -> Sentence
forall n. (HasUID n, NamedIdea n) => n -> Sentence
phrase ConceptChunk
program, String -> Sentence
S "to simulate", NP -> Sentence
forall n. NounPhrase n => n -> Sentence
phraseNP (ConceptChunk
motion
                            ConceptChunk -> ConceptChunk -> NP
forall c d. (NamedIdea c, NamedIdea d) => c -> d -> NP
`the_ofThe` ConceptChunk
pendulum), (String -> Sentence
S "to exhibit its chaotic characteristics" Sentence -> Sentence
!.),
                            NP -> Sentence
forall n. NounPhrase n => n -> Sentence
atStartNP (ConceptChunk -> NP
forall c. NamedIdea c => c -> NP
the ConceptChunk
program), String -> Sentence
S "documented here is called", CI -> Sentence
forall n. (HasUID n, NamedIdea n) => n -> Sentence
phrase CI
progName]

-------------------------------
-- 2.1 : Purpose of Document --
-------------------------------
-- Purpose of Document automatically generated in IPurpose

---------------------------------
-- 2.2 : Scope of Requirements --
---------------------------------
scope :: Sentence
scope :: Sentence
scope = [Sentence] -> Sentence
foldlSent_ [NP -> Sentence
forall n. NounPhrase n => n -> Sentence
phraseNP (NP -> NP
NP.the (NamedChunk
analysis NamedChunk -> CI -> NP
forall c d. (NamedIdea c, NamedIdea d) => c -> d -> NP
`ofA` CI
twoD)), 
  Sentence -> Sentence
sParen (CI -> Sentence
getAcc CI
twoD), NamedChunk -> Sentence
forall n. (HasUID n, NamedIdea n) => n -> Sentence
phrase NamedChunk
pendMotion, NamedChunk -> Sentence
forall n. (HasUID n, NamedIdea n) => n -> Sentence
phrase NamedChunk
problem,
                   String -> Sentence
S "with various initial conditions"]

----------------------------------------------
-- 2.3 : Characteristics of Intended Reader --
----------------------------------------------
charsOfReader :: [Sentence]
charsOfReader :: [Sentence]
charsOfReader = [NamedChunk -> Sentence
forall n. (HasUID n, NamedIdea n) => n -> Sentence
phrase NamedChunk
undergraduate Sentence -> Sentence -> Sentence
+:+ String -> Sentence
S "level 2" Sentence -> Sentence -> Sentence
+:+ NamedChunk -> Sentence
forall n. (HasUID n, NamedIdea n) => n -> Sentence
phrase NamedChunk
Doc.physics,
                 NamedChunk -> Sentence
forall n. (HasUID n, NamedIdea n) => n -> Sentence
phrase NamedChunk
undergraduate Sentence -> Sentence -> Sentence
+:+ String -> Sentence
S "level 1" Sentence -> Sentence -> Sentence
+:+ NamedChunk -> Sentence
forall n. (HasUID n, NamedIdea n) => n -> Sentence
phrase NamedChunk
calculus,
                 CI -> Sentence
forall n. (HasUID n, NamedIdea n) => n -> Sentence
plural CI
ode]

-------------------------------------
-- 2.4 : Organization of Documents --
-------------------------------------
organizationOfDocumentsIntro :: Sentence
organizationOfDocumentsIntro :: Sentence
organizationOfDocumentsIntro = [Sentence] -> Sentence
foldlSent 
  [NP -> Sentence
forall n. NounPhrase n => n -> Sentence
atStartNP (NamedChunk -> NP
forall c. NamedIdea c => c -> 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", NamedChunk -> Sentence
forall n. (HasUID n, NamedIdea n) => n -> Sentence
phrase NamedChunk
template, String -> Sentence
S "for an", CI -> Sentence
getAcc CI
Doc.srs, String -> 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]


--------------------------------------------
-- Section 3: GENERAL SYSTEM DESCRIPTION --
--------------------------------------------
-- Description of Genreal System automatically generated in GSDProg

--------------------------
-- 3.1 : System Context --
--------------------------
sysCtxIntro :: Contents
sysCtxIntro :: Contents
sysCtxIntro = [Sentence] -> Contents
foldlSP
  [LabelledContent -> Sentence
forall r.
(HasUID r, HasRefAddress r, HasShortName r) =>
r -> Sentence
refS LabelledContent
sysCtxFig1, 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 entity external to 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 c. NamedIdea c => c -> NP
the NamedChunk
user), String -> Sentence
S "in this case. A rectangle represents the",
   NamedChunk -> Sentence
forall n. (HasUID n, NamedIdea n) => n -> Sentence
phrase NamedChunk
softwareSys, String -> Sentence
S "itself", Sentence -> Sentence
sParen (CI -> Sentence
forall c. (Idea c, HasUID c) => c -> Sentence
short CI
progName) Sentence -> Sentence -> Sentence
+:+. Sentence
EmptyS,
   String -> Sentence
S "Arrows are used to show the data 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)]

sysCtxDesc :: Contents
sysCtxDesc :: Contents
sysCtxDesc = [Sentence] -> Contents
foldlSPCol [String -> Sentence
S "The interaction between the", NP -> Sentence
forall n. NounPhrase n => n -> Sentence
phraseNP (NamedChunk
product_
   NamedChunk -> NamedChunk -> NP
forall c d. (NamedIdea c, NamedIdea d) => c -> d -> NP
`andThe` NamedChunk
user), String -> Sentence
S "is through an application programming" Sentence -> Sentence -> Sentence
+:+.
   NamedChunk -> Sentence
forall n. (HasUID n, NamedIdea n) => n -> Sentence
phrase NamedChunk
interface, String -> Sentence
S "The responsibilities of the", 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), String -> Sentence
S "are as follows"]

sysCtxUsrResp :: [Sentence]
sysCtxUsrResp :: [Sentence]
sysCtxUsrResp = [String -> Sentence
S "Provide initial" Sentence -> Sentence -> Sentence
+:+ NP -> Sentence
forall n. NounPhrase n => n -> Sentence
pluralNP (NamedChunk
condition NamedChunk -> NamedChunk -> NP
forall c d. (NamedIdea c, NamedIdea d) => c -> d -> NP
`ofThePS`
  NamedChunk
physical) Sentence -> Sentence -> Sentence
+:+ String -> Sentence
S "state of the" Sentence -> Sentence -> Sentence
+:+ ConceptChunk -> Sentence
forall n. (HasUID n, NamedIdea n) => n -> Sentence
phrase ConceptChunk
motion Sentence -> Sentence -> Sentence
+:+ String -> Sentence
S "and the" Sentence -> Sentence -> Sentence
+:+ NamedChunk -> Sentence
forall n. (HasUID n, NamedIdea n) => n -> Sentence
plural NamedChunk
inDatum Sentence -> Sentence -> Sentence
+:+ String -> Sentence
S "related to the" Sentence -> Sentence -> Sentence
+:+
  CI -> Sentence
forall n. (HasUID n, NamedIdea n) => n -> Sentence
phrase CI
progName Sentence -> Sentence -> Sentence
`sC` String -> Sentence
S "ensuring no errors in the" Sentence -> Sentence -> Sentence
+:+
  NamedChunk -> Sentence
forall n. (HasUID n, NamedIdea n) => n -> Sentence
plural NamedChunk
datum Sentence -> Sentence -> Sentence
+:+. String -> Sentence
S "entry",
  String -> Sentence
S "Ensure that consistent units are used for" Sentence -> Sentence -> Sentence
+:+. NP -> Sentence
forall n. NounPhrase n => n -> Sentence
pluralNP (NamedChunk -> NamedChunk -> NP
forall c d. (NamedIdea c, NamedIdea d) => c -> d -> NP
combineNINI NamedChunk
input_ NamedChunk
Doc.variable),
  String -> Sentence
S "Ensure required" Sentence -> Sentence -> Sentence
+:+
  Section -> Sentence -> Sentence
forall r.
(HasUID r, HasRefAddress r, HasShortName r) =>
r -> Sentence -> Sentence
namedRef ([Contents] -> [Section] -> Section
SRS.assumpt ([]::[Contents]) ([]::[Section])) (NamedChunk -> Sentence
forall n. (HasUID n, NamedIdea n) => n -> Sentence
phrase NamedChunk
software Sentence -> Sentence -> Sentence
+:+ CI -> Sentence
forall n. (HasUID n, NamedIdea n) => n -> Sentence
plural CI
assumption) Sentence -> Sentence -> Sentence
+:+
  String -> Sentence
S "are appropriate for any particular" Sentence -> Sentence -> Sentence
+:+
  NamedChunk -> Sentence
forall n. (HasUID n, NamedIdea n) => n -> Sentence
phrase NamedChunk
problem Sentence -> Sentence -> Sentence
+:+ String -> Sentence
S "input to the" Sentence -> Sentence -> Sentence
+:+. NamedChunk -> Sentence
forall n. (HasUID n, NamedIdea n) => n -> Sentence
phrase NamedChunk
software]

sysCtxSysResp :: [Sentence]
sysCtxSysResp :: [Sentence]
sysCtxSysResp = [String -> Sentence
S "Detect data type mismatch, such as a string of characters" Sentence -> Sentence -> Sentence
+:+
  NamedChunk -> Sentence
forall n. (HasUID n, NamedIdea n) => n -> Sentence
phrase NamedChunk
input_ Sentence -> Sentence -> Sentence
+:+. String -> Sentence
S "instead of a floating point number",
  String -> Sentence
S "Determine if the" Sentence -> Sentence -> Sentence
+:+ NamedChunk -> Sentence
forall n. (HasUID n, NamedIdea n) => n -> Sentence
plural NamedChunk
input_ Sentence -> Sentence -> Sentence
+:+ String -> Sentence
S "satisfy the required" Sentence -> Sentence -> Sentence
+:+.
  NP -> Sentence
forall n. NounPhrase n => n -> Sentence
pluralNP (NamedChunk
physical NamedChunk -> NamedChunk -> NP
forall c d. (NamedIdea c, NamedIdea d) => c -> d -> NP
`and_` NamedChunk
softwareConstraint),
  String -> Sentence
S "Calculate the required" Sentence -> Sentence -> Sentence
+:+. NamedChunk -> Sentence
forall n. (HasUID n, NamedIdea n) => n -> Sentence
plural NamedChunk
output_, 
  String -> Sentence
S "Generate the required" Sentence -> Sentence -> Sentence
+:+. ConceptChunk -> Sentence
forall n. (HasUID n, NamedIdea n) => n -> Sentence
plural ConceptChunk
graph]

sysCtxResp :: [Sentence]
sysCtxResp :: [Sentence]
sysCtxResp = [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"]

sysCtxList :: Contents
sysCtxList :: Contents
sysCtxList = 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 [Sentence]
sysCtxResp ([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]
sysCtxUsrResp, [Sentence]
sysCtxSysResp]

--------------------------------
-- 3.2 : User Characteristics --
--------------------------------
userCharacteristicsIntro :: Contents
userCharacteristicsIntro :: Contents
userCharacteristicsIntro = [Sentence] -> Contents
foldlSP
  [String -> Sentence
S "The", NamedChunk -> Sentence
forall n. (HasUID n, NamedIdea n) => n -> Sentence
phrase NamedChunk
endUser Sentence -> Sentence -> Sentence
`S.of_` CI -> Sentence
forall c. (Idea c, HasUID c) => c -> Sentence
short CI
progName,
   String -> Sentence
S "should have an understanding of", 
   NamedChunk -> Sentence
forall n. (HasUID n, NamedIdea n) => n -> Sentence
phrase NamedChunk
highSchoolPhysics Sentence -> Sentence -> Sentence
`sC` NamedChunk -> Sentence
forall n. (HasUID n, NamedIdea n) => n -> Sentence
phrase NamedChunk
highSchoolCalculus Sentence -> Sentence -> Sentence
`S.and_` CI -> Sentence
forall n. (HasUID n, NamedIdea n) => n -> Sentence
plural CI
ode]

-------------------------------
-- 3.3 : System Constraints  --
-------------------------------
-- System Constraints automatically generated in SystCons


--------------------------------------------
-- Section 4: Specific System Description --
--------------------------------------------
-- Description of Specific System automatically generated in SSDProg

-------------------------------
-- 4.1 : System Constraints  --
-------------------------------
prob :: Sentence
prob :: Sentence
prob = [Sentence] -> Sentence
foldlSent_ [String -> Sentence
S "efficiently and correctly to predict the", NP -> Sentence
forall n. NounPhrase n => n -> Sentence
phraseNP (ConceptChunk
motion ConceptChunk -> ConceptChunk -> NP
forall c d. (NamedIdea c, NamedIdea d) => c -> d -> NP
`ofA` ConceptChunk
pendulum)]

---------------------------------
-- 4.1.1 Terminology and Definitions --
---------------------------------
terms :: [ConceptChunk]
terms :: [ConceptChunk]
terms = [ConceptChunk
gravity, ConceptChunk
cartesian]

-----------------------------------
-- 4.1.2 Physical System Description --
-----------------------------------
physSystParts :: [Sentence]
physSystParts :: [Sentence]
physSystParts = (Sentence -> Sentence) -> [Sentence] -> [Sentence]
forall a b. (a -> b) -> [a] -> [b]
map Sentence -> Sentence
(!.)
  [NP -> Sentence
forall n. NounPhrase n => n -> Sentence
atStartNP (NamedChunk -> NP
forall c. NamedIdea c => c -> NP
the NamedChunk
firstRod) Sentence -> Sentence -> Sentence
+:+ Sentence -> Sentence
sParen (String -> Sentence
S "with" Sentence -> Sentence -> Sentence
+:+ UnitalChunk -> Sentence
forall a. Quantity a => a -> Sentence
getTandS UnitalChunk
lenRod_1),
   NP -> Sentence
forall n. NounPhrase n => n -> Sentence
atStartNP (NamedChunk -> NP
forall c. NamedIdea c => c -> NP
the NamedChunk
secondRod) Sentence -> Sentence -> Sentence
+:+ Sentence -> Sentence
sParen (String -> Sentence
S "with" Sentence -> Sentence -> Sentence
+:+ UnitalChunk -> Sentence
forall a. Quantity a => a -> Sentence
getTandS UnitalChunk
lenRod_2),
   NP -> Sentence
forall n. NounPhrase n => n -> Sentence
atStartNP (NamedChunk -> NP
forall c. NamedIdea c => c -> NP
the NamedChunk
firstObject),
   NP -> Sentence
forall n. NounPhrase n => n -> Sentence
atStartNP (NamedChunk -> NP
forall c. NamedIdea c => c -> NP
the NamedChunk
secondObject)]

-----------------------------
-- 4.1.3 : Goal Statements --
-----------------------------

--------------------------------------------------
-- 4.2 : Solution Characteristics Specification --
--------------------------------------------------

-------------------------
-- 4.2.1 : Assumptions --
-------------------------
-- Assumptions defined in Assumptions

--------------------------------
-- 4.2.2 : Theoretical Models --
--------------------------------
-- Theoretical Models defined in TMs
tMods :: [TheoryModel]
tMods :: [TheoryModel]
tMods = [TheoryModel
accelerationTM, TheoryModel
velocityTM, TheoryModel
newtonSL]

---------------------------------
-- 4.2.3 : General Definitions --
---------------------------------
-- General Definitions defined in GDs

------------------------------
-- 4.2.4 : Data Definitions --
------------------------------
-- Data Definitions defined in DDs

-----------------------------
-- 4.2.5 : Instance Models --
-----------------------------
-- Instance Models defined in IMs

-----------------------------
-- 4.2.6 : Data Constraints --
-----------------------------
-- Data Constraints defined in Constraints

-----------------------------
-- 4.2.7 : Properties of a Correct Solution --
-----------------------------
-- Properties of a Correct Solution defined in CorrSolnPpties

------------------------------
-- SECTION 5 : REQUIREMENTS --
------------------------------
-- in Requirements.hs

-----------------------------------
-- 5.1 : Functional Requirements --
-----------------------------------

--------------------------------------
-- 5.2 : Nonfunctional Requirements --
--------------------------------------

--------------------------------
-- SECTION 6 : LIKELY CHANGES --
--------------------------------

--------------------------------
-- SECTION 6b : UNLIKELY CHANGES --
--------------------------------

--------------------------------------------------
-- Section 7 : TRACEABILITY MATRICES AND GRAPHS --
--------------------------------------------------

-------------------------------------------------
-- Section 8 :  Specification Parameter Values --
-------------------------------------------------

----------------------------
-- Section 9 : References --
----------------------------