module Drasil.Website.Body where
import Control.Lens ((^.))
import Language.Drasil.Printers (PrintingInformation(..), defaultConfiguration)
import Database.Drasil
import SysInfo.Drasil
import Language.Drasil
import Drasil.DocLang (findAllRefs)
import Drasil.Website.Introduction (introSec)
import Drasil.Website.About (aboutSec)
import Drasil.Website.CaseStudy (caseStudySec)
import Drasil.Website.Example (exampleSec, exampleRefs, allExampleSI)
import Drasil.Website.Documentation (docsSec, docRefs)
import Drasil.Website.Analysis (analysisSec, analysisRefs)
import Drasil.Website.GettingStarted (gettingStartedSec)
import Data.Drasil.Concepts.Physics (pendulum, motion, rigidBody)
import Data.Drasil.Concepts.Documentation (game, physics, condition, safety)
import Drasil.GlassBR.Unitals (blast)
import Drasil.GlassBR.Concepts (glaSlab)
import Data.Drasil.Concepts.Thermodynamics (heatTrans)
import Drasil.SWHS.Concepts (sWHT, water, phsChgMtrl)
import Drasil.PDController.Concepts (pidC)
import Drasil.Projectile.Concepts (target, projectile)
import Drasil.SSP.Defs (crtSlpSrf, intrslce, slope, slpSrf, factor)
import Data.Drasil.Concepts.SolidMechanics (shearForce, normForce)
import Drasil.SSP.IMods (fctSfty)
printSetting :: FolderLocation -> PrintingInformation
printSetting :: FolderLocation -> PrintingInformation
printSetting FolderLocation
fl = ChunkDB -> Stage -> PrintingConfiguration -> PrintingInformation
PI (FolderLocation -> ChunkDB
symbMap FolderLocation
fl) Stage
Equational PrintingConfiguration
defaultConfiguration
mkWebsite :: FolderLocation -> Document
mkWebsite :: FolderLocation -> Document
mkWebsite FolderLocation
fl =
Title -> Title -> ShowTableOfContents -> [Section] -> Document
Document (String -> Title
S String
websiteTitle) (Reference -> Title -> Title
forall r.
(HasUID r, HasRefAddress r, HasShortName r) =>
r -> Title -> Title
namedRef Reference
gitHubRef (String -> Title
S String
"Link to GitHub Repository")) ShowTableOfContents
NoToC ([Section] -> Document) -> [Section] -> Document
forall a b. (a -> b) -> a -> b
$ FolderLocation -> [Section]
sections FolderLocation
fl
data FolderLocation = Folder {
FolderLocation -> String
depL :: FilePath
, FolderLocation -> String
docsRt :: FilePath
, FolderLocation -> String
exRt :: FilePath
, FolderLocation -> String
graphRt :: FilePath
, FolderLocation -> String
analysisRt :: FilePath
, FolderLocation -> String
typeGraphFolder :: FilePath
, FolderLocation -> String
classInstFolder :: FilePath
, FolderLocation -> String
repoRt :: FilePath
, FolderLocation -> String
buildNum :: FilePath
, FolderLocation -> String
buildPth :: FilePath
, FolderLocation -> [String]
packages :: [String]
}
si :: FolderLocation -> SystemInformation
si :: FolderLocation -> SystemInformation
si FolderLocation
fl = SI {
_sys :: CI
_sys = CI
webName,
_kind :: CI
_kind = CI
web,
_authors :: People
_authors = [] :: [Person],
_quants :: [QuantityDict]
_quants = [] :: [QuantityDict],
_purpose :: Purpose
_purpose = [],
_background :: Purpose
_background = [],
_motivation :: Purpose
_motivation = [],
_scope :: Purpose
_scope = [],
_concepts :: [UnitalChunk]
_concepts = [] :: [UnitalChunk],
_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 = FolderLocation -> ChunkDB
symbMap FolderLocation
fl,
_usedinfodb :: ChunkDB
_usedinfodb = ChunkDB
usedDB,
refdb :: ReferenceDB
refdb = BibRef -> [ConceptInstance] -> ReferenceDB
rdb [] []
}
sections :: FolderLocation -> [Section]
sections :: FolderLocation -> [Section]
sections FolderLocation
fl = [Section
headerSec, Section
introSec, Reference
-> Reference
-> Reference
-> Reference
-> Reference
-> Reference
-> Section
gettingStartedSec Reference
quickStartWiki Reference
newWorkspaceSetupWiki Reference
contribGuideWiki Reference
workflowWiki
Reference
createProjWiki Reference
debuggingWiki, Reference
-> Reference
-> Reference
-> Reference
-> Reference
-> Reference
-> Reference
-> Reference
-> Reference
-> Reference
-> Reference
-> Reference
-> Reference
-> Section
aboutSec (Section -> Reference
forall r.
(HasUID r, HasRefAddress r, HasShortName r) =>
r -> Reference
ref Section
caseStudySec) (Section -> Reference
forall r.
(HasUID r, HasRefAddress r, HasShortName r) =>
r -> Reference
ref (Section -> Reference) -> Section -> Reference
forall a b. (a -> b) -> a -> b
$ String -> Section
docsSec (String -> Section) -> String -> Section
forall a b. (a -> b) -> a -> b
$ FolderLocation -> String
docsRt FolderLocation
fl) (Section -> Reference
forall r.
(HasUID r, HasRefAddress r, HasShortName r) =>
r -> Reference
ref (Section -> Reference) -> Section -> Reference
forall a b. (a -> b) -> a -> b
$ String -> String -> String -> String -> [String] -> Section
analysisSec (FolderLocation -> String
analysisRt FolderLocation
fl)
(FolderLocation -> String
typeGraphFolder FolderLocation
fl) (FolderLocation -> String
classInstFolder FolderLocation
fl) (FolderLocation -> String
graphRt FolderLocation
fl) ([String] -> Section) -> [String] -> Section
forall a b. (a -> b) -> a -> b
$ FolderLocation -> [String]
packages FolderLocation
fl) Reference
gitHubRef Reference
wikiRef Reference
infoEncodingWiki Reference
chunksWiki Reference
recipesWiki
Reference
paperGOOL Reference
papersWiki Reference
icsePositionPaper Reference
danPoster Reference
wellUnderstoodPaper, String -> String -> Section
exampleSec (FolderLocation -> String
repoRt FolderLocation
fl) (FolderLocation -> String
exRt FolderLocation
fl), Section
caseStudySec, String -> Section
docsSec (FolderLocation -> String
docsRt FolderLocation
fl),
String -> String -> String -> String -> [String] -> Section
analysisSec (FolderLocation -> String
analysisRt FolderLocation
fl) (FolderLocation -> String
typeGraphFolder FolderLocation
fl) (FolderLocation -> String
classInstFolder FolderLocation
fl) (FolderLocation -> String
graphRt FolderLocation
fl) ([String] -> Section) -> [String] -> Section
forall a b. (a -> b) -> a -> b
$ FolderLocation -> [String]
packages FolderLocation
fl, FolderLocation -> Section
footer FolderLocation
fl]
symbMap :: FolderLocation -> ChunkDB
symbMap :: FolderLocation -> ChunkDB
symbMap FolderLocation
fl = [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
webName, CI
web, CI
phsChgMtrl] [IdeaDict] -> [IdeaDict] -> [IdeaDict]
forall a. [a] -> [a] -> [a]
++
(SystemInformation -> IdeaDict)
-> [SystemInformation] -> [IdeaDict]
forall a b. (a -> b) -> [a] -> [b]
map SystemInformation -> IdeaDict
getSysName [SystemInformation]
allExampleSI [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
pendulum, ConceptChunk
motion, ConceptChunk
rigidBody, ConceptChunk
blast,
ConceptChunk
heatTrans, ConceptChunk
sWHT, ConceptChunk
water, ConceptChunk
pidC, ConceptChunk
target, ConceptChunk
projectile, ConceptChunk
crtSlpSrf, ConceptChunk
shearForce,
ConceptChunk
normForce, ConceptChunk
slpSrf] [IdeaDict] -> [IdeaDict] -> [IdeaDict]
forall a. [a] -> [a] -> [a]
++ [QuantityDict -> IdeaDict
forall c. Idea c => c -> IdeaDict
nw (QuantityDict -> IdeaDict) -> QuantityDict -> IdeaDict
forall a b. (a -> b) -> a -> b
$ InstanceModel
fctSfty InstanceModel
-> Getting QuantityDict InstanceModel QuantityDict -> QuantityDict
forall s a. s -> Getting a s a -> a
^. Getting QuantityDict InstanceModel QuantityDict
forall d. DefinesQuantity d => Getter d QuantityDict
Getter InstanceModel QuantityDict
defLhs] [IdeaDict] -> [IdeaDict] -> [IdeaDict]
forall a. [a] -> [a] -> [a]
++ [IdeaDict
game, IdeaDict
physics, IdeaDict
condition, IdeaDict
glaSlab, IdeaDict
intrslce,
IdeaDict
slope, IdeaDict
safety, IdeaDict
factor]) ([] :: [ConceptChunk]) ([] :: [UnitDefn]) [] [] [] []
[] [] [] ([Reference] -> ChunkDB) -> [Reference] -> ChunkDB
forall a b. (a -> b) -> a -> b
$ FolderLocation -> [Reference]
allRefs FolderLocation
fl
getSysName :: SystemInformation -> IdeaDict
getSysName :: SystemInformation -> IdeaDict
getSysName SI{_sys :: ()
_sys = a
nm} = a -> IdeaDict
forall c. Idea c => c -> IdeaDict
nw a
nm
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]) [] [] [] [] [] [] [] ([] :: [Reference])
allRefs :: FolderLocation -> [Reference]
allRefs :: FolderLocation -> [Reference]
allRefs FolderLocation
fl = [Reference
gitHubRef, Reference
wikiRef, Reference
infoEncodingWiki, Reference
chunksWiki, Reference
recipesWiki, Reference
paperGOOL, Reference
papersWiki,
Reference
quickStartWiki, Reference
newWorkspaceSetupWiki, Reference
contribGuideWiki, Reference
workflowWiki, Reference
createProjWiki, Reference
debuggingWiki,
Reference
icsePositionPaper, Reference
danPoster, Reference
wellUnderstoodPaper]
[Reference] -> [Reference] -> [Reference]
forall a. [a] -> [a] -> [a]
++ String -> String -> [Reference]
exampleRefs (FolderLocation -> String
repoRt FolderLocation
fl) (FolderLocation -> String
exRt FolderLocation
fl)
[Reference] -> [Reference] -> [Reference]
forall a. [a] -> [a] -> [a]
++ String -> [Reference]
docRefs (FolderLocation -> String
docsRt FolderLocation
fl)
[Reference] -> [Reference] -> [Reference]
forall a. [a] -> [a] -> [a]
++ String -> String -> String -> String -> [String] -> [Reference]
analysisRefs (FolderLocation -> String
analysisRt FolderLocation
fl) (FolderLocation -> String
typeGraphFolder FolderLocation
fl) (FolderLocation -> String
classInstFolder FolderLocation
fl) (FolderLocation -> String
graphRt FolderLocation
fl) (FolderLocation -> [String]
packages FolderLocation
fl)
[Reference] -> [Reference] -> [Reference]
forall a. [a] -> [a] -> [a]
++ (Section -> [Reference]) -> [Section] -> [Reference]
forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
concatMap Section -> [Reference]
findAllRefs (FolderLocation -> [Section]
sections FolderLocation
fl)
webName, web :: CI
webName :: CI
webName = String -> NP -> String -> [UID] -> CI
commonIdea String
"websiteName" (String -> NP
cn String
websiteTitle) String
"Drasil" []
web :: CI
web = String -> NP -> String -> [UID] -> CI
commonIdea String
"website" (String -> NP
cn String
"website") String
"web" []
headerSec :: Section
=
Title -> [Contents] -> [Section] -> Reference -> Section
section Title
EmptyS
[LabelledContent -> Contents
LlC LabelledContent
imageContent]
[] (Reference -> Section) -> Reference -> Section
forall a b. (a -> b) -> a -> b
$ String -> Title -> Reference
makeSecRef String
"Header" (Title -> Reference) -> Title -> Reference
forall a b. (a -> b) -> a -> b
$ String -> Title
S String
"Header"
imageContent :: LabelledContent
imageContent :: LabelledContent
imageContent = Reference -> RawContent -> LabelledContent
llcc (String -> Reference
makeFigRef String
"Drasil") (RawContent -> LabelledContent) -> RawContent -> LabelledContent
forall a b. (a -> b) -> a -> b
$ Title -> String -> MaxWidthPercent -> RawContent
figNoCapWithWidth Title
EmptyS String
imagePath MaxWidthPercent
50
gitHubRef :: Reference
gitHubRef :: Reference
gitHubRef = String -> String -> ShortName -> Reference
makeURI String
"gitHubRepo" String
gitHubInfoURL (Title -> ShortName
shortname' (Title -> ShortName) -> Title -> ShortName
forall a b. (a -> b) -> a -> b
$ String -> Title
S String
"gitHubRepo")
wikiRef :: Reference
wikiRef :: Reference
wikiRef = String -> String -> ShortName -> Reference
makeURI String
"gitHubWiki" (String
gitHubInfoURL String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"/wiki") (Title -> ShortName
shortname' (Title -> ShortName) -> Title -> ShortName
forall a b. (a -> b) -> a -> b
$ String -> Title
S String
"gitHubWiki")
infoEncodingWiki :: Reference
infoEncodingWiki :: Reference
infoEncodingWiki = String -> String -> ShortName -> Reference
makeURI String
"InfoEncodingWiki" (String
gitHubInfoURL String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"/wiki/Information-Encoding") (Title -> ShortName
shortname' (Title -> ShortName) -> Title -> ShortName
forall a b. (a -> b) -> a -> b
$ String -> Title
S String
"InfoEncodingWiki")
chunksWiki :: Reference
chunksWiki :: Reference
chunksWiki = String -> String -> ShortName -> Reference
makeURI String
"chunksWiki" (String
gitHubInfoURL String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"/wiki/Chunks") (Title -> ShortName
shortname' (Title -> ShortName) -> Title -> ShortName
forall a b. (a -> b) -> a -> b
$ String -> Title
S String
"chunksWiki")
recipesWiki :: Reference
recipesWiki :: Reference
recipesWiki = String -> String -> ShortName -> Reference
makeURI String
"recipesWiki" (String
gitHubInfoURL String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"/wiki/Recipes") (Title -> ShortName
shortname' (Title -> ShortName) -> Title -> ShortName
forall a b. (a -> b) -> a -> b
$ String -> Title
S String
"recipesWiki")
paperGOOL :: Reference
paperGOOL :: Reference
paperGOOL = String -> String -> ShortName -> Reference
makeURI String
"GOOLPaper" (String
gitHubInfoURL String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"/blob/main/Papers/GOOL/GOOL.pdf") (Title -> ShortName
shortname' (Title -> ShortName) -> Title -> ShortName
forall a b. (a -> b) -> a -> b
$ String -> Title
S String
"GOOLPaper")
papersWiki :: Reference
papersWiki :: Reference
papersWiki = String -> String -> ShortName -> Reference
makeURI String
"papersWiki" (String
gitHubInfoURL String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"/wiki/Drasil-Papers-and-Documents") (Title -> ShortName
shortname' (Title -> ShortName) -> Title -> ShortName
forall a b. (a -> b) -> a -> b
$ String -> Title
S String
"papersWiki")
icsePositionPaper :: Reference
icsePositionPaper :: Reference
icsePositionPaper = String -> String -> ShortName -> Reference
makeURI String
"icsePositionPaper" (String
danContributionPath
String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"/ICSE%20Workshop%20-%20SE4Science/ICSE_LiterateFrameworkForSCSoftware_LSS.pdf") (Title -> ShortName
shortname' (Title -> ShortName) -> Title -> ShortName
forall a b. (a -> b) -> a -> b
$ String -> Title
S String
"icsePositionPaper")
danPoster :: Reference
danPoster :: Reference
danPoster = String -> String -> ShortName -> Reference
makeURI String
"danPoster" (String
danContributionPath
String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"/CAS%20Poster%20Competition/Poster/DrasilPoster.pdf") (Title -> ShortName
shortname' (Title -> ShortName) -> Title -> ShortName
forall a b. (a -> b) -> a -> b
$ String -> Title
S String
"danPoster")
wellUnderstoodPaper :: Reference
wellUnderstoodPaper :: Reference
wellUnderstoodPaper = String -> String -> ShortName -> Reference
makeURI String
"wellUnderstoodPaper" (String
gitHubInfoURL
String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"/blob/master/Papers/WellUnderstood/wu.pdf") (Title -> ShortName
shortname' (Title -> ShortName) -> Title -> ShortName
forall a b. (a -> b) -> a -> b
$ String -> Title
S String
"wellUnderstoodPaper")
quickStartWiki :: Reference
quickStartWiki :: Reference
quickStartWiki = String -> String -> ShortName -> Reference
makeURI String
"quickStartWiki" (String
gitHubInfoURL String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"#quick-start") (Title -> ShortName
shortname' (Title -> ShortName) -> Title -> ShortName
forall a b. (a -> b) -> a -> b
$ String -> Title
S String
"quickStartWiki")
newWorkspaceSetupWiki :: Reference
newWorkspaceSetupWiki :: Reference
newWorkspaceSetupWiki = String -> String -> ShortName -> Reference
makeURI String
"newWorkspaceSetupWiki" (String
gitHubInfoURL String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"/wiki/New-Workspace-Setup") (Title -> ShortName
shortname' (Title -> ShortName) -> Title -> ShortName
forall a b. (a -> b) -> a -> b
$ String -> Title
S String
"newWorkspaceSetupWiki")
contribGuideWiki :: Reference
contribGuideWiki :: Reference
contribGuideWiki = String -> String -> ShortName -> Reference
makeURI String
"contribGuideWiki" (String
gitHubInfoURL String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"/wiki/Contributor's-Guide") (Title -> ShortName
shortname' (Title -> ShortName) -> Title -> ShortName
forall a b. (a -> b) -> a -> b
$ String -> Title
S String
"contribGuideWiki")
workflowWiki :: Reference
workflowWiki :: Reference
workflowWiki = String -> String -> ShortName -> Reference
makeURI String
"workflowWiki" (String
gitHubInfoURL String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"/wiki/Workflow") (Title -> ShortName
shortname' (Title -> ShortName) -> Title -> ShortName
forall a b. (a -> b) -> a -> b
$ String -> Title
S String
"workflowWiki")
createProjWiki :: Reference
createProjWiki :: Reference
createProjWiki = String -> String -> ShortName -> Reference
makeURI String
"createProjWiki" (String
gitHubInfoURL String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"/wiki/Creating-Your-Project-in-Drasil") (Title -> ShortName
shortname' (Title -> ShortName) -> Title -> ShortName
forall a b. (a -> b) -> a -> b
$ String -> Title
S String
"createProjWiki")
debuggingWiki :: Reference
debuggingWiki :: Reference
debuggingWiki = String -> String -> ShortName -> Reference
makeURI String
"debuggingWiki" (String
gitHubInfoURL String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"/wiki/Debugging-in-Drasil") (Title -> ShortName
shortname' (Title -> ShortName) -> Title -> ShortName
forall a b. (a -> b) -> a -> b
$ String -> Title
S String
"debuggingWiki")
websiteTitle :: String
gitHubInfoURL, imagePath, danContributionPath :: FilePath
websiteTitle :: String
websiteTitle = String
"Drasil - Generate All the Things!"
gitHubInfoURL :: String
gitHubInfoURL = String
"https://github.com/JacquesCarette/Drasil"
danContributionPath :: String
danContributionPath = String
gitHubInfoURL String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"/blob/master/People/Dan"
imagePath :: String
imagePath = String
"./images/Icon.png"
footer :: FolderLocation -> Section
FolderLocation
_ = Title -> [Contents] -> [Section] -> Reference -> Section
section Title
EmptyS [Title -> Contents
mkParagraph Title
copyrightInfo] [] (Reference -> Section) -> Reference -> Section
forall a b. (a -> b) -> a -> b
$ String -> Title -> Reference
makeSecRef String
"Footer" (Title -> Reference) -> Title -> Reference
forall a b. (a -> b) -> a -> b
$ String -> Title
S String
"Footer"
copyrightInfo :: Sentence
copyrightInfo :: Title
copyrightInfo = String -> Title
S String
"Copyright (c) Jacques Carette, 2021. All rights reserved. This website is a software artifact generated by Drasil."