{-# LANGUAGE TupleSections #-}
module Drasil.Website.Example where
import Language.Drasil hiding (E)
import SysInfo.Drasil (SystemInformation(..))
import Language.Drasil.Code (Choices(..), Lang(..))
import Data.Char (toLower)
import qualified Drasil.DblPend.Body as DblPend (fullSI)
import qualified Drasil.GamePhysics.Body as GamePhysics (fullSI)
import qualified Drasil.GlassBR.Body as GlassBR (fullSI)
import qualified Drasil.HGHC.Body as HGHC (fullSI)
import qualified Drasil.SWHSNoPCM.Body as NoPCM (fullSI)
import qualified Drasil.PDController.Body as PDController (fullSI)
import qualified Drasil.Projectile.Body as Projectile (fullSI)
import qualified Drasil.SglPend.Body as SglPend (fullSI)
import qualified Drasil.SSP.Body as SSP (fullSI)
import qualified Drasil.SWHS.Body as SWHS (fullSI)
import qualified Drasil.DblPend.Choices as DblPend (choices)
import qualified Drasil.GlassBR.Choices as GlassBR (choices)
import qualified Drasil.SWHSNoPCM.Choices as NoPCM (choices)
import qualified Drasil.PDController.Choices as PDController (codeChoices)
import qualified Drasil.Projectile.Choices as Projectile (codedDirName, choiceCombos)
data Example = E {
Example -> SystemInformation
sysInfoE :: SystemInformation,
Example -> [Choices]
choicesE :: [Choices],
Example -> FilePath
codePath :: FilePath,
Example -> FilePath
srsDoxPath :: FilePath
}
allExampleSI :: [SystemInformation]
allExampleSI :: [SystemInformation]
allExampleSI = [SystemInformation
DblPend.fullSI, SystemInformation
GamePhysics.fullSI, SystemInformation
GlassBR.fullSI, SystemInformation
HGHC.fullSI, SystemInformation
NoPCM.fullSI, SystemInformation
PDController.fullSI, SystemInformation
Projectile.fullSI, SystemInformation
SglPend.fullSI, SystemInformation
SSP.fullSI, SystemInformation
SWHS.fullSI]
allExampleChoices :: [[Choices]]
allExampleChoices :: [[Choices]]
allExampleChoices = [[Choices
DblPend.choices], [], [Choices
GlassBR.choices], [], [Choices
NoPCM.choices], [Choices
PDController.codeChoices], [Choices]
Projectile.choiceCombos, [], [], []]
allExamples :: [SystemInformation] -> [[Choices]] -> FilePath -> FilePath -> [Example]
allExamples :: [SystemInformation]
-> [[Choices]] -> FilePath -> FilePath -> [Example]
allExamples [SystemInformation]
si [[Choices]]
choi FilePath
srsP FilePath
doxP = forall a b c. (a -> b -> c) -> [a] -> [b] -> [c]
zipWith (\SystemInformation
x [Choices]
y -> SystemInformation -> [Choices] -> FilePath -> FilePath -> Example
E SystemInformation
x [Choices]
y FilePath
srsP FilePath
doxP) [SystemInformation]
si [[Choices]]
choi
examples :: FilePath -> FilePath -> [Example]
examples :: FilePath -> FilePath -> [Example]
examples = [SystemInformation]
-> [[Choices]] -> FilePath -> FilePath -> [Example]
allExamples [SystemInformation]
allExampleSI [[Choices]]
allExampleChoices
fullExList :: FilePath -> FilePath -> RawContent
fullExList :: FilePath -> FilePath -> RawContent
fullExList FilePath
codePth FilePath
srsDoxPth = ListType -> RawContent
Enumeration forall a b. (a -> b) -> a -> b
$ [(ItemType, Maybe FilePath)] -> ListType
Bullet forall a b. (a -> b) -> a -> b
$ forall a b. (a -> b) -> [a] -> [b]
map (, forall a. Maybe a
Nothing) ([Example] -> [ItemType]
allExampleList forall a b. (a -> b) -> a -> b
$ FilePath -> FilePath -> [Example]
examples FilePath
codePth FilePath
srsDoxPth)
allExampleList :: [Example] -> [ItemType]
allExampleList :: [Example] -> [ItemType]
allExampleList = forall a b. (a -> b) -> [a] -> [b]
map (\Example
x -> Header -> ListType -> ItemType
Nested (Example -> Header
nameAndDesc Example
x) forall a b. (a -> b) -> a -> b
$ [(ItemType, Maybe FilePath)] -> ListType
Bullet forall a b. (a -> b) -> a -> b
$ forall a b. (a -> b) -> [a] -> [b]
map (, forall a. Maybe a
Nothing) (Example -> [ItemType]
individualExList Example
x))
where
nameAndDesc :: Example -> Header
nameAndDesc E{sysInfoE :: Example -> SystemInformation
sysInfoE = SI{_sys :: ()
_sys = a
sys, _purpose :: SystemInformation -> Purpose
_purpose = Purpose
purp}} = FilePath -> Header
S (forall c. CommonIdea c => c -> FilePath
abrv a
sys) Header -> Header -> Header
+:+ FilePath -> Header
S FilePath
" - To" Header -> Header -> Header
+:+. forall a. [a] -> a
head Purpose
purp
individualExList :: Example -> [ItemType]
individualExList :: Example -> [ItemType]
individualExList E{sysInfoE :: Example -> SystemInformation
sysInfoE = SI{_sys :: ()
_sys = a
sys}, choicesE :: Example -> [Choices]
choicesE = [], codePath :: Example -> FilePath
codePath = FilePath
srsP} =
[Header -> ItemType
Flat forall a b. (a -> b) -> a -> b
$ FilePath -> Header
S FilePath
"SRS:" Header -> Header -> Header
+:+ forall r.
(HasUID r, HasRefAddress r, HasShortName r) =>
r -> Header -> Header
namedRef (FilePath -> FilePath -> FilePath -> Reference
getSRSRef FilePath
srsP FilePath
"html" forall a b. (a -> b) -> a -> b
$ forall c. CommonIdea c => c -> FilePath
programName a
sys) (FilePath -> Header
S FilePath
"[HTML]") Header -> Header -> Header
+:+ forall r.
(HasUID r, HasRefAddress r, HasShortName r) =>
r -> Header -> Header
namedRef (FilePath -> FilePath -> FilePath -> Reference
getSRSRef FilePath
srsP FilePath
"pdf" forall a b. (a -> b) -> a -> b
$ forall c. CommonIdea c => c -> FilePath
programName a
sys) (FilePath -> Header
S FilePath
"[PDF]")]
individualExList ex :: Example
ex@E{sysInfoE :: Example -> SystemInformation
sysInfoE = SI{_sys :: ()
_sys = a
sys}, codePath :: Example -> FilePath
codePath = FilePath
srsP} =
[Header -> ItemType
Flat forall a b. (a -> b) -> a -> b
$ FilePath -> Header
S FilePath
"SRS:" Header -> Header -> Header
+:+ forall r.
(HasUID r, HasRefAddress r, HasShortName r) =>
r -> Header -> Header
namedRef (FilePath -> FilePath -> FilePath -> Reference
getSRSRef FilePath
srsP FilePath
"html" forall a b. (a -> b) -> a -> b
$ forall c. CommonIdea c => c -> FilePath
programName a
sys) (FilePath -> Header
S FilePath
"[HTML]") Header -> Header -> Header
+:+ forall r.
(HasUID r, HasRefAddress r, HasShortName r) =>
r -> Header -> Header
namedRef (FilePath -> FilePath -> FilePath -> Reference
getSRSRef FilePath
srsP FilePath
"pdf" forall a b. (a -> b) -> a -> b
$ forall c. CommonIdea c => c -> FilePath
programName a
sys) (FilePath -> Header
S FilePath
"[PDF]"),
Header -> ListType -> ItemType
Nested (FilePath -> Header
S FilePath
generatedCodeTitle) forall a b. (a -> b) -> a -> b
$ [(ItemType, Maybe FilePath)] -> ListType
Bullet forall a b. (a -> b) -> a -> b
$ forall a b. (a -> b) -> [a] -> [b]
map (, forall a. Maybe a
Nothing) ((Example -> Lang -> FilePath -> Reference) -> Example -> [ItemType]
versionList Example -> Lang -> FilePath -> Reference
getCodeRef Example
ex),
Header -> ListType -> ItemType
Nested (FilePath -> Header
S FilePath
generatedCodeDocsTitle) forall a b. (a -> b) -> a -> b
$ [(ItemType, Maybe FilePath)] -> ListType
Bullet forall a b. (a -> b) -> a -> b
$ forall a b. (a -> b) -> [a] -> [b]
map (, forall a. Maybe a
Nothing) ((Example -> Lang -> FilePath -> Reference) -> Example -> [ItemType]
versionList Example -> Lang -> FilePath -> Reference
getDoxRef Example
noSwiftEx)]
where
noSwiftEx :: Example
noSwiftEx = Example
ex {choicesE :: [Choices]
choicesE = forall a b. (a -> b) -> [a] -> [b]
map (\Choices
x -> Choices
x {lang :: [Lang]
lang = forall a. (a -> Bool) -> [a] -> [a]
filter (forall a. Eq a => a -> a -> Bool
/= Lang
Swift) forall a b. (a -> b) -> a -> b
$ Choices -> [Lang]
lang Choices
x}) forall a b. (a -> b) -> a -> b
$ Example -> [Choices]
choicesE Example
ex}
versionList :: (Example -> Lang -> String -> Reference) -> Example -> [ItemType]
versionList :: (Example -> Lang -> FilePath -> Reference) -> Example -> [ItemType]
versionList Example -> Lang -> FilePath -> Reference
_ E{choicesE :: Example -> [Choices]
choicesE = []} = []
versionList Example -> Lang -> FilePath -> Reference
getRef ex :: Example
ex@E{sysInfoE :: Example -> SystemInformation
sysInfoE = SI{_sys :: ()
_sys = a
sys}, choicesE :: Example -> [Choices]
choicesE = [Choices]
chcs} =
forall a b. (a -> b) -> [a] -> [b]
map Choices -> ItemType
versionItem [Choices]
chcs
where
versionItem :: Choices -> ItemType
versionItem Choices
chc = Header -> ItemType
Flat forall a b. (a -> b) -> a -> b
$ FilePath -> Header
S (Choices -> FilePath
verName Choices
chc) Header -> Header -> Header
+:+ Purpose -> Header
foldlSent_ (forall a b. (a -> b) -> [a] -> [b]
map (Choices -> Lang -> Header
makeLangRef Choices
chc) forall a b. (a -> b) -> a -> b
$ Choices -> [Lang]
lang Choices
chc)
makeLangRef :: Choices -> Lang -> Header
makeLangRef Choices
chc Lang
lng = forall r.
(HasUID r, HasRefAddress r, HasShortName r) =>
r -> Header -> Header
namedRef (Example -> Lang -> FilePath -> Reference
getRef Example
ex Lang
lng forall a b. (a -> b) -> a -> b
$ Choices -> FilePath
verName Choices
chc) forall a b. (a -> b) -> a -> b
$ FilePath -> Header
S forall a b. (a -> b) -> a -> b
$ FilePath
"[" forall a. [a] -> [a] -> [a]
++ Lang -> FilePath
showLang Lang
lng forall a. [a] -> [a] -> [a]
++ FilePath
"]"
verName :: Choices -> FilePath
verName Choices
chc = case [Choices]
chcs of
[Choices
_] -> forall c. CommonIdea c => c -> FilePath
programName a
sys
[Choices]
_ -> FilePath -> Choices -> FilePath
Projectile.codedDirName (forall c. CommonIdea c => c -> FilePath
programName a
sys) Choices
chc
showLang :: Lang -> String
showLang :: Lang -> FilePath
showLang Lang
Cpp = FilePath
"C++"
showLang Lang
CSharp = FilePath
"C Sharp"
showLang Lang
l = forall a. Show a => a -> FilePath
show Lang
l
exampleSec :: FilePath -> FilePath -> Section
exampleSec :: FilePath -> FilePath -> Section
exampleSec FilePath
codePth FilePath
srsDoxPth =
Header -> [Contents] -> [Section] -> Reference -> Section
section Header
exampleTitle
[Header -> Contents
mkParagraph Header
exampleIntro, UnlabelledContent -> Contents
UlC forall a b. (a -> b) -> a -> b
$ RawContent -> UnlabelledContent
ulcc forall a b. (a -> b) -> a -> b
$ FilePath -> FilePath -> RawContent
fullExList FilePath
codePth FilePath
srsDoxPth]
[] forall a b. (a -> b) -> a -> b
$ FilePath -> Header -> Reference
makeSecRef FilePath
"Examples" forall a b. (a -> b) -> a -> b
$ FilePath -> Header
S FilePath
"Examples"
exampleTitle :: Sentence
exampleTitle :: Header
exampleTitle = FilePath -> Header
S FilePath
"Generated Examples"
exampleIntro :: Sentence
exampleIntro :: Header
exampleIntro = FilePath -> Header
S FilePath
"The development of Drasil follows an example-driven approach, \
\with a current focus on creating Software Requirement Specifications (SRS). \
\More specifically, Drasil's knowledge of the domain of Physics has seen significant growth \
\through the creation of these examples, ranging from mechanics to thermodynamics. Each of the case studies \
\implemented in Drasil contain their own generated PDF and HTML reports, and in some cases, \
\their own generated code to solve the problem defined in their respective SRS documents."
generatedCodeTitle, generatedCodeDocsTitle :: String
generatedCodeTitle :: FilePath
generatedCodeTitle = FilePath
"Generated Code:"
generatedCodeDocsTitle :: FilePath
generatedCodeDocsTitle = FilePath
"Generated Code Documentation:"
convertLang :: Lang -> String
convertLang :: Lang -> FilePath
convertLang Lang
Cpp = FilePath
"cpp"
convertLang Lang
CSharp = FilePath
"csharp"
convertLang Lang
Java = FilePath
"java"
convertLang Lang
Python = FilePath
"python"
convertLang Lang
Swift = FilePath
"swift"
getCodeRef :: Example -> Lang -> String -> Reference
getCodeRef :: Example -> Lang -> FilePath -> Reference
getCodeRef ex :: Example
ex@E{sysInfoE :: Example -> SystemInformation
sysInfoE=SI{_sys :: ()
_sys = a
sys}, choicesE :: Example -> [Choices]
choicesE = [Choices]
chcs} Lang
l FilePath
verName =
FilePath -> FilePath -> ShortName -> Reference
makeURI FilePath
refUID FilePath
refURI ShortName
refShortNm
where
refUID :: FilePath
refUID = FilePath
"codeRef" forall a. [a] -> [a] -> [a]
++ FilePath
sysName forall a. [a] -> [a] -> [a]
++ FilePath
programLang
refURI :: FilePath
refURI = FilePath -> FilePath -> FilePath -> FilePath
getCodePath (Example -> FilePath
codePath Example
ex) FilePath
sysName FilePath
programLang
refShortNm :: ShortName
refShortNm = Header -> ShortName
shortname' forall a b. (a -> b) -> a -> b
$ FilePath -> Header
S FilePath
refUID
sysName :: FilePath
sysName = case [Choices]
chcs of
[Choices
_] -> forall a b. (a -> b) -> [a] -> [b]
map Char -> Char
toLower forall a b. (a -> b) -> a -> b
$ forall c. CommonIdea c => c -> FilePath
programName a
sys
[Choices]
_ -> forall a b. (a -> b) -> [a] -> [b]
map Char -> Char
toLower (forall c. CommonIdea c => c -> FilePath
programName a
sys) forall a. [a] -> [a] -> [a]
++ FilePath
"/" forall a. [a] -> [a] -> [a]
++ FilePath
verName
programLang :: FilePath
programLang = Lang -> FilePath
convertLang Lang
l
getDoxRef :: Example -> Lang -> String -> Reference
getDoxRef :: Example -> Lang -> FilePath -> Reference
getDoxRef ex :: Example
ex@E{sysInfoE :: Example -> SystemInformation
sysInfoE=SI{_sys :: ()
_sys = a
sys}, choicesE :: Example -> [Choices]
choicesE = [Choices]
chcs} Lang
l FilePath
verName =
FilePath -> FilePath -> ShortName -> Reference
makeURI FilePath
refUID FilePath
refURI ShortName
refShortNm
where
refUID :: FilePath
refUID = FilePath
"doxRef" forall a. [a] -> [a] -> [a]
++ FilePath
progName forall a. [a] -> [a] -> [a]
++ FilePath
programLang
refURI :: FilePath
refURI = FilePath -> FilePath -> FilePath -> FilePath
getDoxPath (Example -> FilePath
srsDoxPath Example
ex) FilePath
progName FilePath
programLang
refShortNm :: ShortName
refShortNm = Header -> ShortName
shortname' forall a b. (a -> b) -> a -> b
$ FilePath -> Header
S FilePath
refUID
progName :: FilePath
progName = forall c. CommonIdea c => c -> FilePath
programName a
sys
programLang :: FilePath
programLang = case [Choices]
chcs of
[Choices
_] -> Lang -> FilePath
convertLang Lang
l
[Choices]
_ -> forall a b. (a -> b) -> [a] -> [b]
map Char -> Char
toLower FilePath
verName forall a. [a] -> [a] -> [a]
++ FilePath
"/" forall a. [a] -> [a] -> [a]
++ Lang -> FilePath
convertLang Lang
l
getSRSRef :: FilePath -> String -> String -> Reference
getSRSRef :: FilePath -> FilePath -> FilePath -> Reference
getSRSRef FilePath
path FilePath
sufx FilePath
ex = FilePath -> FilePath -> ShortName -> Reference
makeURI FilePath
refUID (FilePath -> FilePath -> FilePath -> FilePath
getSRSPath FilePath
path (forall a b. (a -> b) -> [a] -> [b]
map Char -> Char
toLower FilePath
sufx) FilePath
ex) forall a b. (a -> b) -> a -> b
$ Header -> ShortName
shortname' forall a b. (a -> b) -> a -> b
$ FilePath -> Header
S FilePath
refUID
where
refUID :: FilePath
refUID = forall a b. (a -> b) -> [a] -> [b]
map Char -> Char
toLower FilePath
sufx forall a. [a] -> [a] -> [a]
++ FilePath
"Ref" forall a. [a] -> [a] -> [a]
++ FilePath
ex
getSRSPath :: FilePath -> String -> String -> FilePath
getSRSPath :: FilePath -> FilePath -> FilePath -> FilePath
getSRSPath FilePath
path FilePath
sufx FilePath
ex =
FilePath
path
forall a. [a] -> [a] -> [a]
++ forall a b. (a -> b) -> [a] -> [b]
map Char -> Char
toLower FilePath
ex
forall a. [a] -> [a] -> [a]
++ FilePath
"/SRS/srs/"
forall a. [a] -> [a] -> [a]
++ FilePath
ex forall a. [a] -> [a] -> [a]
++ FilePath
"_SRS." forall a. [a] -> [a] -> [a]
++ forall a b. (a -> b) -> [a] -> [b]
map Char -> Char
toLower FilePath
sufx
getCodePath, getDoxPath :: FilePath -> String -> String -> FilePath
getCodePath :: FilePath -> FilePath -> FilePath -> FilePath
getCodePath FilePath
path FilePath
ex FilePath
programLang = FilePath
path forall a. [a] -> [a] -> [a]
++ FilePath
"code/stable/" forall a. [a] -> [a] -> [a]
++ forall a b. (a -> b) -> [a] -> [b]
map Char -> Char
toLower FilePath
ex forall a. [a] -> [a] -> [a]
++ FilePath
"/src/" forall a. [a] -> [a] -> [a]
++ FilePath
programLang
getDoxPath :: FilePath -> FilePath -> FilePath -> FilePath
getDoxPath FilePath
path FilePath
ex FilePath
programLang = FilePath
path forall a. [a] -> [a] -> [a]
++ forall a b. (a -> b) -> [a] -> [b]
map Char -> Char
toLower FilePath
ex forall a. [a] -> [a] -> [a]
++ FilePath
"/doxygen/" forall a. [a] -> [a] -> [a]
++ FilePath
programLang forall a. [a] -> [a] -> [a]
++ FilePath
"/index.html"
exampleRefs :: FilePath -> FilePath -> [Reference]
exampleRefs :: FilePath -> FilePath -> [Reference]
exampleRefs FilePath
codePth FilePath
srsDoxPth = forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
concatMap Example -> [Reference]
getCodeRefDB (FilePath -> FilePath -> [Example]
examples FilePath
codePth FilePath
srsDoxPth) forall a. [a] -> [a] -> [a]
++
forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
concatMap Example -> [Reference]
getDoxRefDB (FilePath -> FilePath -> [Example]
examples FilePath
codePth FilePath
srsDoxPth) forall a. [a] -> [a] -> [a]
++
forall a b. (a -> b) -> [a] -> [b]
map (FilePath -> FilePath -> FilePath -> Reference
getSRSRef FilePath
srsDoxPth FilePath
"html" forall b c a. (b -> c) -> (a -> b) -> a -> c
. Example -> FilePath
getAbrv) (FilePath -> FilePath -> [Example]
examples FilePath
codePth FilePath
srsDoxPth) forall a. [a] -> [a] -> [a]
++ forall a b. (a -> b) -> [a] -> [b]
map (FilePath -> FilePath -> FilePath -> Reference
getSRSRef FilePath
srsDoxPth FilePath
"pdf" forall b c a. (b -> c) -> (a -> b) -> a -> c
. Example -> FilePath
getAbrv) (FilePath -> FilePath -> [Example]
examples FilePath
codePth FilePath
srsDoxPth)
getCodeRefDB, getDoxRefDB :: Example -> [Reference]
getCodeRefDB :: Example -> [Reference]
getCodeRefDB Example
ex = forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
concatMap (\Choices
x -> forall a b. (a -> b) -> [a] -> [b]
map (\Lang
y -> Example -> Lang -> FilePath -> Reference
getCodeRef Example
ex Lang
y forall a b. (a -> b) -> a -> b
$ Choices -> FilePath
verName Choices
x) forall a b. (a -> b) -> a -> b
$ Choices -> [Lang]
lang Choices
x) forall a b. (a -> b) -> a -> b
$ Example -> [Choices]
choicesE Example
ex
where
verName :: Choices -> FilePath
verName = FilePath -> Choices -> FilePath
Projectile.codedDirName (Example -> FilePath
getAbrv Example
ex)
getDoxRefDB :: Example -> [Reference]
getDoxRefDB Example
ex = forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
concatMap (\Choices
x -> forall a b. (a -> b) -> [a] -> [b]
map (\Lang
y -> Example -> Lang -> FilePath -> Reference
getDoxRef Example
ex Lang
y forall a b. (a -> b) -> a -> b
$ Choices -> FilePath
verName Choices
x) forall a b. (a -> b) -> a -> b
$ Choices -> [Lang]
lang Choices
x) forall a b. (a -> b) -> a -> b
$ Example -> [Choices]
choicesE Example
ex
where
verName :: Choices -> FilePath
verName = FilePath -> Choices -> FilePath
Projectile.codedDirName (Example -> FilePath
getAbrv Example
ex)
getAbrv :: Example -> String
getAbrv :: Example -> FilePath
getAbrv E{sysInfoE :: Example -> SystemInformation
sysInfoE = SI{_sys :: ()
_sys=a
sys}} = forall c. CommonIdea c => c -> FilePath
programName a
sys