Skip to content

Commit

Permalink
add new content website
Browse files Browse the repository at this point in the history
  • Loading branch information
peter-michalski committed Sep 22, 2022
1 parent 3553724 commit 7020a82
Show file tree
Hide file tree
Showing 4 changed files with 240 additions and 27 deletions.
98 changes: 98 additions & 0 deletions code/drasil-website/lib/Drasil/Website/About.hs
Original file line number Diff line number Diff line change
@@ -0,0 +1,98 @@
{-# LANGUAGE PostfixOperators #-}
-- | About Drasil
module Drasil.Website.About where

import Language.Drasil

-- * About Section

-- | Creates the about section.
aboutSec :: Reference -> Reference -> Reference -> Reference -> Reference -> Reference -> Reference -> Reference ->
Reference -> Reference -> Section
aboutSec csRef docRef analysisSecRef repoRef wikiRef infoEncodingWiki chunksWiki recipesWiki paperGOOL papersWiki =
section (S "About") -- Title
(map mkParagraph [aboutParagraph1 repoRef wikiRef, aboutParagraph2 csRef docRef analysisSecRef, aboutParagraph3]
++ [currentlyGeneratedArtifacts] ++ map mkParagraph [aboutParagraph4] ++ [futureGeneratedArtifacts] ++ map mkParagraph
[aboutParagraph5 infoEncodingWiki, aboutParagraph6 chunksWiki, aboutParagraph7 recipesWiki, aboutParagraph8 paperGOOL,
aboutParagraph9 papersWiki]) -- Contents
[] $ makeSecRef "About" $ S "About" -- Section reference

-- | Paragraph to about Drasil and its goals.
aboutParagraph1 :: Reference -> Reference -> Sentence
aboutParagraph1 repoRef wikiRef = S "Drasil is a framework for generating all of the software artifacts \
\from a stable knowledge base, focusing currently on scientific software. The main goals are to reduce knowledge \
\duplication and improve traceability. The artifacts are generated from a common knowledge-base using recipes \
\written in a Domain-Specific Language (DSL). These recipes allow us to specify which pieces of \
\knowledge should be used in which artifacts, how to transform them, and more. For more information on the design, documentation, \
\useage, and specifics of Drasil, please visit the" +:+ namedRef repoRef (S "GitHub repository") +:+ S "or the" +:+
(namedRef wikiRef (S "GitHub Wiki") !.)

-- | Paragraph to describe the layout of the rest of the Drasil website.
aboutParagraph2 :: Reference -> Reference -> Reference -> Sentence
aboutParagraph2 caseStudySecRef docsRef analysisSecRef = S "This webpage is designed to contain the most up to date" +:+
foldlList Comma List (zipWith (\x y -> namedRef x (S y)) [caseStudySecRef, docsRef, analysisSecRef] ["case study artifacts",
"Haddock documentation", "Drasil analysis"]) +:+ S "from the Drasil repository. \
\The case study artifacts include the Software Requirements Specification (SRS) for each case study, \
\which specifies what the program sets out to achieve. \
\The Haddock Documentation section contains the current documentation for the Drasil framework. \
\The package dependency graphs shows the hierarchy of modules within each package."
-- \The footer of this page contains the continuous integration build of the project, \
-- \as well as the commit number that the build and artifacts are based off of.

-- |
aboutParagraph3 :: Sentence
aboutParagraph3 = S "The following is a list of artifacts that Drasil currently generates:"

currentlyGeneratedArtifacts :: Contents
currentlyGeneratedArtifacts = enumBulletU $ map foldlSent_
[[S "SRS"],
[S "code"],
[S "README"],
[S "Makefile"]]

aboutParagraph4 :: Sentence
aboutParagraph4 = S "We hope to generate the following artifacts in the future:"

futureGeneratedArtifacts :: Contents
futureGeneratedArtifacts = enumBulletU $ map foldlSent_
[[S "License"],
[S "Installation Instructions"],
[S "Dependency List"],
[S "Authors"],
[S "Getting Started / User Manual"],
[S "Release Info"],
[S "Design Documentation"],
[S "Build Scripts"],
[S "Test Cases"]]

aboutParagraph5 :: Reference -> Sentence
aboutParagraph5 infoEncodingWiki = S "As described in the" +:+ namedRef infoEncodingWiki (S "Information Encoding") +:+ S " wiki page, \
\Drasil uses specific terminology to address types of \
\knowledge for the purpose of encoding information, since we know that we want to eventually generate words, sentences, paragraphs, \
\whole documents with headings, references, formulas, tables, graphs, and code. This is done by trying to understand the basic 'units' \
\of all artifacts, and methods for composing larger structures from these units. The removal of duplicate units is an important feature \
\of this methodology. The basic building blocks of the methodology include different expressions for units with a specific meaning. \
\These are built into ontologies of domains that address broader knowledge. Chunks form a fundamental part of such ontologies."

aboutParagraph6 :: Reference -> Sentence
aboutParagraph6 chunksWiki = S "As described in the" +:+ namedRef chunksWiki (S "Chunks") +:+ S "wiki page, a chunk is a data type specialized \
\in holding a specific type of information for \
\a specific purpose so that knowledge may be used in generated models, definitions, and theories. Chunks are usually made up of several \
\lower-level types that hold lower-lever information; when contained together, these pieces of lower-level information hold a new specific \
\purpose. The structure of a chunk can be thought of as a wrapper of information, and this is all implemented using Haskell's record-type \
\syntax. Recipes transform the acquired knowledge into a usable format."

aboutParagraph7 :: Reference -> Sentence
aboutParagraph7 recipesWiki= S "As described in the" +:+ namedRef recipesWiki (S "Recipes") +:+ S "wiki page, recipes are instructions that \
\unpackage necessary information from chunks and send \
\that information to Drasil generators/printers to build complete artifacts. When an artifact needs to be changed, the recipe is modified to \
\unpackage the additional necessary information from a chunk, or alternatively to omit unpackaging information that is no longer required."

aboutParagraph8 :: Reference -> Sentence
aboutParagraph8 paperGOOL = S "As described in the" +:+ namedRef paperGOOL (S "GOOL") +:+ S "paper, this is a Generic Object-Oriented Language \
\that provides intermediary assistance in code \
\generation, allowing Drasil to more efficiently generate code in several languages, including Python, Java, C-Sharp, and C++."

aboutParagraph9 :: Reference -> Sentence
aboutParagraph9 papersWiki = S "A list of papers and documents written about Drasil can be found in the" +:+ namedRef papersWiki (S "Drasil Papers \
\and Documents") +:+ S "wiki page"
35 changes: 31 additions & 4 deletions code/drasil-website/lib/Drasil/Website/Body.hs
Original file line number Diff line number Diff line change
Expand Up @@ -8,10 +8,12 @@ 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)

-- * Functions to Generate the Website Through Drasil

Expand Down Expand Up @@ -78,9 +80,11 @@ si fl = SI {

-- | Puts all the sections in order. Basically the website version of the SRS declaration.
sections :: FolderLocation -> [Section]
sections fl = [headerSec, introSec (ref caseStudySec) (ref $ docsSec $ docsRt fl) (ref $ analysisSec (analysisRt fl) (typeGraphFolder fl) (classInstFolder fl) (graphRt fl) $ packages fl) gitHubRef wikiRef,
exampleSec (repoRt fl) (exRt fl), caseStudySec, docsSec (docsRt fl), analysisSec (analysisRt fl) (typeGraphFolder fl) (classInstFolder fl) (graphRt fl) $ packages fl,
footer fl]
sections fl = [headerSec, introSec, gettingStartedSec quickStartWiki newWorkspaceSetupWiki contribGuideWiki workflowWiki
createProjWiki debuggingWiki, aboutSec (ref caseStudySec) (ref $ docsSec $ docsRt fl) (ref $ analysisSec (analysisRt fl)
(typeGraphFolder fl) (classInstFolder fl) (graphRt fl) $ packages fl) gitHubRef wikiRef infoEncodingWiki chunksWiki recipesWiki
paperGOOL papersWiki, exampleSec (repoRt fl) (exRt fl), caseStudySec, docsSec (docsRt fl), analysisSec (analysisRt fl)
(typeGraphFolder fl) (classInstFolder fl) (graphRt fl) $ packages fl, footer fl]

-- | Needed for references and terms to work.
symbMap :: FolderLocation -> ChunkDB
Expand All @@ -98,7 +102,8 @@ usedDB = cdb ([] :: [QuantityDict]) ([] :: [IdeaDict])

-- | Holds all references and links used in the website.
allRefs :: FolderLocation -> [Reference]
allRefs fl = [gitHubRef, wikiRef]
allRefs fl = [gitHubRef, wikiRef, infoEncodingWiki, chunksWiki, recipesWiki, paperGOOL, papersWiki,
quickStartWiki, newWorkspaceSetupWiki, contribGuideWiki, workflowWiki, createProjWiki, debuggingWiki]
++ exampleRefs (repoRt fl) (exRt fl)
++ docRefs (docsRt fl)
++ analysisRefs (analysisRt fl) (typeGraphFolder fl) (classInstFolder fl) (graphRt fl) (packages fl)
Expand Down Expand Up @@ -127,6 +132,28 @@ gitHubRef :: Reference
gitHubRef = makeURI "gitHubRepo" gitHubInfoURL (shortname' $ S "gitHubRepo")
wikiRef :: Reference
wikiRef = makeURI "gitHubWiki" (gitHubInfoURL ++ "/wiki") (shortname' $ S "gitHubWiki")
infoEncodingWiki :: Reference
infoEncodingWiki = makeURI "InfoEncodingWiki" (gitHubInfoURL ++ "/wiki/Information-Encoding") (shortname' $ S "InfoEncodingWiki")
chunksWiki :: Reference
chunksWiki = makeURI "chunksWiki" (gitHubInfoURL ++ "/wiki/Chunks") (shortname' $ S "chunksWiki")
recipesWiki :: Reference
recipesWiki = makeURI "recipesWiki" (gitHubInfoURL ++ "/wiki/Recipes") (shortname' $ S "recipesWiki")
paperGOOL :: Reference
paperGOOL = makeURI "GOOLPaper" (gitHubInfoURL ++ "/blob/master/Papers/GOOL/GOOL.pdf") (shortname' $ S "GOOLPaper")
papersWiki :: Reference
papersWiki = makeURI "papersWiki" (gitHubInfoURL ++ "/wiki/Drasil-Papers-and-Documents") (shortname' $ S "papersWiki")
quickStartWiki :: Reference
quickStartWiki = makeURI "quickStartWiki" (gitHubInfoURL ++ "#quick-start") (shortname' $ S "quickStartWiki")
newWorkspaceSetupWiki :: Reference
newWorkspaceSetupWiki = makeURI "newWorkspaceSetupWiki" (gitHubInfoURL ++ "/wiki/New-Workspace-Setup") (shortname' $ S "newWorkspaceSetupWiki")
contribGuideWiki :: Reference
contribGuideWiki = makeURI "contribGuideWiki" (gitHubInfoURL ++ "/wiki/Contributor's-Guide") (shortname' $ S "contribGuideWiki")
workflowWiki :: Reference
workflowWiki = makeURI "workflowWiki" (gitHubInfoURL ++ "/wiki/Workflow") (shortname' $ S "workflowWiki")
createProjWiki :: Reference
createProjWiki = makeURI "createProjWiki" (gitHubInfoURL ++ "/wiki/Creating-Your-Project-in-Drasil") (shortname' $ S "createProjWiki")
debuggingWiki :: Reference
debuggingWiki = makeURI "debuggingWiki" (gitHubInfoURL ++ "/wiki/Debugging-in-Drasil") (shortname' $ S "debuggingWiki")

-- | Hardcoded info for the title, URL, and image path.
websiteTitle :: String
Expand Down
103 changes: 103 additions & 0 deletions code/drasil-website/lib/Drasil/Website/GettingStarted.hs
Original file line number Diff line number Diff line change
@@ -0,0 +1,103 @@
module Drasil.Website.GettingStarted where

import Language.Drasil


-- * Getting Started Section

gettingStartedSec :: Reference -> Reference -> Reference -> Reference -> Reference -> Reference -> Section
gettingStartedSec quickstartWiki newWorkspaceSetupWiki contribGuideWiki workflowWiki createProjWiki debuggingWiki =
section gettingStartedTitle -- Section title
[mkParagraph gettingStartedIntro] -- Section introduction
[quickStartSec quickstartWiki, newWorkspaceSec newWorkspaceSetupWiki, contribGuideWorkflowSec contribGuideWiki
workflowWiki, createOwnProjectSec createProjWiki, debuggingDrasilSec debuggingWiki] -- Subsections
$ makeSecRef "GettingStarted" $ S "GettingStarted" -- Section Reference

-- | Getting started section title.
gettingStartedTitle :: Sentence
gettingStartedTitle = S "Getting Started"

-- | Getting started section introduction.
gettingStartedIntro :: Sentence
gettingStartedIntro = S ""

-- | Quick Start subsection.
quickStartSec :: Reference -> Section
quickStartSec quickstartWiki =
section quickStartTitle -- Title
[mkParagraph $ quickStartDesc quickstartWiki] -- Contents
[] $ makeSecRef "QuickStart" $ S "QuickStart" -- Section reference

-- | Quick Start subsection title.
quickStartTitle :: Sentence
quickStartTitle = S "Quick Start"

-- | Link to Quick Start Wiki.
quickStartDesc :: Reference -> Sentence
quickStartDesc quickstartWiki = S "Navigate to the" +:+ namedRef quickstartWiki (S "Quick Start Guide")
+:+ S "to see what Drasil can do."

-- | New workspace subsection.
newWorkspaceSec :: Reference -> Section
newWorkspaceSec newWorkspaceSetupWiki =
section newWorkspaceTitle -- Title
[mkParagraph $ newWorkspaceDesc newWorkspaceSetupWiki] -- Contents
[] $ makeSecRef "NewWorkspace" $ S "NewWorkspace" -- Section reference

-- | New workspace subsection title.
newWorkspaceTitle :: Sentence
newWorkspaceTitle = S "New Workspace Setup"

-- | Link to new workspace Wiki.
newWorkspaceDesc :: Reference -> Sentence
newWorkspaceDesc newWorkspaceSetupWiki = S "Workspace recommendations are available in the" +:+ namedRef
newWorkspaceSetupWiki (S "New Workspace Setup") +:+ S "page."

-- | Contributor's Guide and Workflow subsection.
contribGuideWorkflowSec :: Reference -> Reference -> Section
contribGuideWorkflowSec contribGuideWiki workflowWiki =
section contribGuideWorkflowTitle -- Title
[mkParagraph $ contribGuideWorkflowDesc contribGuideWiki workflowWiki] -- Contents
[] $ makeSecRef "ContribGuideWorkflow" $ S "ContribGuideWorkflow" -- Section reference

-- | Contributor's Guide and Workflow title.
contribGuideWorkflowTitle :: Sentence
contribGuideWorkflowTitle = S "Contributor's Guide and Workflow"

-- | Link to Contributor's Guide and Workflow Wiki.
contribGuideWorkflowDesc :: Reference -> Reference -> Sentence
contribGuideWorkflowDesc contribGuideWiki workflowWiki = S "If you are interested in contributing to the \
\project, please look at the" +:+ namedRef contribGuideWiki (S "Contributor's Guide") +:+ S" as well as the"
+:+ namedRef workflowWiki (S "Workflow") +:+ S "page."

-- | Creating Your Own Project subsection.
createOwnProjectSec :: Reference -> Section
createOwnProjectSec createProjWiki =
section createOwnProjectTitle -- Title
[mkParagraph $ createOwnProjectDesc createProjWiki] -- Contents
[] $ makeSecRef "OwnProject" $ S "OwnProject" -- Section reference

-- | Creating Your Own Project title.
createOwnProjectTitle :: Sentence
createOwnProjectTitle = S "Creating Your Own Project"

-- | Link to Creating Your Own Project Wiki.
createOwnProjectDesc :: Reference -> Sentence
createOwnProjectDesc createProjWiki = S "If you are interested in creating your own project in Drasil, \
\please look at the" +:+ namedRef createProjWiki (S "Creating Your Project in Drasil") +:+ S "page."

-- | Debugging Drasil subsection.
debuggingDrasilSec :: Reference -> Section
debuggingDrasilSec debuggingWiki =
section debuggingDrasilTitle -- Title
[mkParagraph $ debuggingDrasilDesc debuggingWiki] -- Contents
[] $ makeSecRef "DebuggingDrasil" $ S "DebuggingDrasil" -- Section reference

-- | Debugging Drasil title.
debuggingDrasilTitle :: Sentence
debuggingDrasilTitle = S "Debugging Drasil"

-- | Debugging Drasil Wiki.
debuggingDrasilDesc :: Reference -> Sentence
debuggingDrasilDesc debuggingWiki = S "Debugging information can be found in the" +:+ namedRef
debuggingWiki (S "Debugging in Drasil") +:+ S "page."
31 changes: 8 additions & 23 deletions code/drasil-website/lib/Drasil/Website/Introduction.hs
Original file line number Diff line number Diff line change
Expand Up @@ -7,30 +7,15 @@ import Language.Drasil

-- * Introduction Section

-- | Creates the introduction section.
introSec :: Reference -> Reference -> Reference -> Reference -> Reference -> Section
introSec csRef docRef analysisSecRef repoRef wikiRef =
-- | Creates the about section.
introSec :: Section
introSec =
section (S "Introduction") -- Title
(map mkParagraph [introParagraph1 repoRef wikiRef, introParagraph2 csRef docRef analysisSecRef]) -- Contents
(map mkParagraph [introParagraph1]) -- Contents
[] $ makeSecRef "Introduction" $ S "Introduction" -- Section reference

-- | Paragraph to introduce Drasil and its goals.
introParagraph1 :: Reference -> Reference -> Sentence
introParagraph1 repoRef wikiRef = S "Drasil is a framework for generating all of the software artifacts from a stable knowledge base, \
\focusing currently on scientific software. The main goals are to reduce knowledge duplication and \
\improve traceability. The artifacts are generated from a common knowledge-base using recipes \
\written in a Domain-Specific Language (DSL). These recipes allow us to specify which pieces of \
\knowledge should be used in which artifacts, how to transform them, and more. For more information on the design, documentation, \
\useage, and specifics of Drasil, please visit the" +:+ namedRef repoRef (S "GitHub repository") +:+ S "or the" +:+ (namedRef wikiRef (S "GitHub Wiki") !.)

-- | Paragraph to describe the layout of the Drasil website.
introParagraph2 :: Reference -> Reference -> Reference -> Sentence
introParagraph2 caseStudySecRef docsRef analysisSecRef = S "This webpage is designed to contain the most up to date" +:+
foldlList Comma List (zipWith (\x y -> namedRef x (S y)) [caseStudySecRef, docsRef, analysisSecRef] ["case study artifacts", "Haddock documentation", "Drasil analysis"])
+:+ S "from the Drasil repository. \
\The case study artifacts include the Software Requirements Specification (SRS) for each case study, \
\which specifies what the program sets out to achieve. \
\The Haddock Documentation section contains the current documentation for the Drasil framework. \
\The package dependency graphs shows the hierarchy of modules within each package."
-- \The footer of this page contains the continuous integration build of the project, \
-- \as well as the commit number that the build and artifacts are based off of.
introParagraph1 :: Sentence
introParagraph1 = S "Drasil is a framework for generating all of the software artifacts from a stable knowledge base, \
\focusing currently on scientific software. We welcome students and collaborators to assist us as we research optimal ways \
\to extend Drasil's functionality."

0 comments on commit 7020a82

Please sign in to comment.