{-# 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 Language.Drasil.Printers (Format(..))
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 = (SystemInformation -> [Choices] -> Example)
-> [SystemInformation] -> [[Choices]] -> [Example]
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 (ListType -> RawContent) -> ListType -> RawContent
forall a b. (a -> b) -> a -> b
$ [(ItemType, Maybe FilePath)] -> ListType
Bullet ([(ItemType, Maybe FilePath)] -> ListType)
-> [(ItemType, Maybe FilePath)] -> ListType
forall a b. (a -> b) -> a -> b
$ (ItemType -> (ItemType, Maybe FilePath))
-> [ItemType] -> [(ItemType, Maybe FilePath)]
forall a b. (a -> b) -> [a] -> [b]
map (, Maybe FilePath
forall a. Maybe a
Nothing) ([Example] -> [ItemType]
allExampleList ([Example] -> [ItemType]) -> [Example] -> [ItemType]
forall a b. (a -> b) -> a -> b
$ FilePath -> FilePath -> [Example]
examples FilePath
codePth FilePath
srsDoxPth)
allExampleList :: [Example] -> [ItemType]
allExampleList :: [Example] -> [ItemType]
allExampleList = (Example -> ItemType) -> [Example] -> [ItemType]
forall a b. (a -> b) -> [a] -> [b]
map (\Example
x -> Header -> ListType -> ItemType
Nested (Example -> Header
nameAndDesc Example
x) (ListType -> ItemType) -> ListType -> ItemType
forall a b. (a -> b) -> a -> b
$ [(ItemType, Maybe FilePath)] -> ListType
Bullet ([(ItemType, Maybe FilePath)] -> ListType)
-> [(ItemType, Maybe FilePath)] -> ListType
forall a b. (a -> b) -> a -> b
$ (ItemType -> (ItemType, Maybe FilePath))
-> [ItemType] -> [(ItemType, Maybe FilePath)]
forall a b. (a -> b) -> [a] -> [b]
map (, Maybe FilePath
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 (a -> FilePath
forall c. CommonIdea c => c -> FilePath
abrv a
sys) Header -> Header -> Header
+:+ FilePath -> Header
S FilePath
" - To" Header -> Header -> Header
+:+. Purpose -> Header
forall a. HasCallStack => [a] -> a
head Purpose
purp
individualExList :: Example -> [ItemType]
individualExList :: Example -> [ItemType]
individualExList ex :: Example
ex@E{sysInfoE :: Example -> SystemInformation
sysInfoE = SI{_sys :: ()
_sys = a
sys}, choicesE :: Example -> [Choices]
choicesE = [], codePath :: Example -> FilePath
codePath = FilePath
srsP} =
[Header -> ItemType
Flat (Header -> ItemType) -> Header -> ItemType
forall a b. (a -> b) -> a -> b
$ Reference -> Header -> Header
forall r.
(HasUID r, HasRefAddress r, HasShortName r) =>
r -> Header -> Header
namedRef (Example -> Reference
buildDrasilExSrcRef Example
ex) (FilePath -> Header
S FilePath
"Drasil Source Code"),
Header -> ItemType
Flat (Header -> ItemType) -> Header -> ItemType
forall a b. (a -> b) -> a -> b
$ FilePath -> Header
S FilePath
"SRS:" Header -> Header -> Header
+:+ Reference -> Header -> Header
forall r.
(HasUID r, HasRefAddress r, HasShortName r) =>
r -> Header -> Header
namedRef (FilePath -> Format -> FilePath -> Reference
getSRSRef FilePath
srsP Format
HTML (FilePath -> Reference) -> FilePath -> Reference
forall a b. (a -> b) -> a -> b
$ a -> FilePath
forall c. CommonIdea c => c -> FilePath
programName a
sys) (FilePath -> Header
S FilePath
"[HTML]")
Header -> Header -> Header
+:+ Reference -> Header -> Header
forall r.
(HasUID r, HasRefAddress r, HasShortName r) =>
r -> Header -> Header
namedRef (FilePath -> Format -> FilePath -> Reference
getSRSRef FilePath
srsP Format
TeX (FilePath -> Reference) -> FilePath -> Reference
forall a b. (a -> b) -> a -> b
$ a -> FilePath
forall c. CommonIdea c => c -> FilePath
programName a
sys) (FilePath -> Header
S FilePath
"[PDF]")
Header -> Header -> Header
+:+ Reference -> Header -> Header
forall r.
(HasUID r, HasRefAddress r, HasShortName r) =>
r -> Header -> Header
namedRef (FilePath -> Format -> FilePath -> Reference
getSRSRef FilePath
srsP Format
MDBook (FilePath -> Reference) -> FilePath -> Reference
forall a b. (a -> b) -> a -> b
$ a -> FilePath
forall c. CommonIdea c => c -> FilePath
programName a
sys) (FilePath -> Header
S FilePath
"[mdBook]")]
individualExList ex :: Example
ex@E{sysInfoE :: Example -> SystemInformation
sysInfoE = SI{_sys :: ()
_sys = a
sys}, codePath :: Example -> FilePath
codePath = FilePath
srsP} =
[Header -> ItemType
Flat (Header -> ItemType) -> Header -> ItemType
forall a b. (a -> b) -> a -> b
$ Reference -> Header -> Header
forall r.
(HasUID r, HasRefAddress r, HasShortName r) =>
r -> Header -> Header
namedRef (Example -> Reference
buildDrasilExSrcRef Example
ex) (FilePath -> Header
S FilePath
"Drasil Source Code"),
Header -> ItemType
Flat (Header -> ItemType) -> Header -> ItemType
forall a b. (a -> b) -> a -> b
$ FilePath -> Header
S FilePath
"SRS:" Header -> Header -> Header
+:+ Reference -> Header -> Header
forall r.
(HasUID r, HasRefAddress r, HasShortName r) =>
r -> Header -> Header
namedRef (FilePath -> Format -> FilePath -> Reference
getSRSRef FilePath
srsP Format
HTML (FilePath -> Reference) -> FilePath -> Reference
forall a b. (a -> b) -> a -> b
$ a -> FilePath
forall c. CommonIdea c => c -> FilePath
programName a
sys) (FilePath -> Header
S FilePath
"[HTML]")
Header -> Header -> Header
+:+ Reference -> Header -> Header
forall r.
(HasUID r, HasRefAddress r, HasShortName r) =>
r -> Header -> Header
namedRef (FilePath -> Format -> FilePath -> Reference
getSRSRef FilePath
srsP Format
TeX (FilePath -> Reference) -> FilePath -> Reference
forall a b. (a -> b) -> a -> b
$ a -> FilePath
forall c. CommonIdea c => c -> FilePath
programName a
sys) (FilePath -> Header
S FilePath
"[PDF]")
Header -> Header -> Header
+:+ Reference -> Header -> Header
forall r.
(HasUID r, HasRefAddress r, HasShortName r) =>
r -> Header -> Header
namedRef (FilePath -> Format -> FilePath -> Reference
getSRSRef FilePath
srsP Format
MDBook (FilePath -> Reference) -> FilePath -> Reference
forall a b. (a -> b) -> a -> b
$ a -> FilePath
forall c. CommonIdea c => c -> FilePath
programName a
sys) (FilePath -> Header
S FilePath
"[mdBook]"),
Header -> ListType -> ItemType
Nested (FilePath -> Header
S FilePath
generatedCodeTitle) (ListType -> ItemType) -> ListType -> ItemType
forall a b. (a -> b) -> a -> b
$ [(ItemType, Maybe FilePath)] -> ListType
Bullet ([(ItemType, Maybe FilePath)] -> ListType)
-> [(ItemType, Maybe FilePath)] -> ListType
forall a b. (a -> b) -> a -> b
$ (ItemType -> (ItemType, Maybe FilePath))
-> [ItemType] -> [(ItemType, Maybe FilePath)]
forall a b. (a -> b) -> [a] -> [b]
map (, Maybe FilePath
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) (ListType -> ItemType) -> ListType -> ItemType
forall a b. (a -> b) -> a -> b
$ [(ItemType, Maybe FilePath)] -> ListType
Bullet ([(ItemType, Maybe FilePath)] -> ListType)
-> [(ItemType, Maybe FilePath)] -> ListType
forall a b. (a -> b) -> a -> b
$ (ItemType -> (ItemType, Maybe FilePath))
-> [ItemType] -> [(ItemType, Maybe FilePath)]
forall a b. (a -> b) -> [a] -> [b]
map (, Maybe FilePath
forall a. Maybe a
Nothing) ((Example -> Lang -> FilePath -> Reference) -> Example -> [ItemType]
versionList Example -> Lang -> FilePath -> Reference
getDoxRef Example
noSwiftJlEx)]
where
noSwiftJlEx :: Example
noSwiftJlEx = Example
ex {choicesE = map (\Choices
x -> Choices
x {lang = filter
(\Lang
l -> Lang
l Lang -> Lang -> Bool
forall a. Eq a => a -> a -> Bool
/= Lang
Swift Bool -> Bool -> Bool
&& Lang
l Lang -> Lang -> Bool
forall a. Eq a => a -> a -> Bool
/= Lang
Julia) $ lang x}) $ choicesE 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} =
(Choices -> ItemType) -> [Choices] -> [ItemType]
forall a b. (a -> b) -> [a] -> [b]
map Choices -> ItemType
versionItem [Choices]
chcs
where
versionItem :: Choices -> ItemType
versionItem Choices
chc = Header -> ItemType
Flat (Header -> ItemType) -> Header -> ItemType
forall a b. (a -> b) -> a -> b
$ FilePath -> Header
S (Choices -> FilePath
verName Choices
chc) Header -> Header -> Header
+:+ Purpose -> Header
foldlSent_ ((Lang -> Header) -> [Lang] -> Purpose
forall a b. (a -> b) -> [a] -> [b]
map (Choices -> Lang -> Header
makeLangRef Choices
chc) ([Lang] -> Purpose) -> [Lang] -> Purpose
forall a b. (a -> b) -> a -> b
$ Choices -> [Lang]
lang Choices
chc)
makeLangRef :: Choices -> Lang -> Header
makeLangRef Choices
chc Lang
lng = Reference -> Header -> Header
forall r.
(HasUID r, HasRefAddress r, HasShortName r) =>
r -> Header -> Header
namedRef (Example -> Lang -> FilePath -> Reference
getRef Example
ex Lang
lng (FilePath -> Reference) -> FilePath -> Reference
forall a b. (a -> b) -> a -> b
$ Choices -> FilePath
verName Choices
chc) (Header -> Header) -> Header -> Header
forall a b. (a -> b) -> a -> b
$ FilePath -> Header
S (FilePath -> Header) -> FilePath -> Header
forall a b. (a -> b) -> a -> b
$ FilePath
"[" FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ Lang -> FilePath
showLang Lang
lng FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
"]"
verName :: Choices -> FilePath
verName Choices
chc = case [Choices]
chcs of
[Choices
_] -> a -> FilePath
forall c. CommonIdea c => c -> FilePath
programName a
sys
[Choices]
_ -> FilePath -> Choices -> FilePath
Projectile.codedDirName (a -> FilePath
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 = Lang -> FilePath
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 (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
$ FilePath -> FilePath -> RawContent
fullExList FilePath
codePth FilePath
srsDoxPth]
[] (Reference -> Section) -> Reference -> Section
forall a b. (a -> b) -> a -> b
$ FilePath -> Header -> Reference
makeSecRef FilePath
"Examples" (Header -> Reference) -> Header -> Reference
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 contains its own generated PDF and HTML reports, and in some cases, \
\its 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"
convertLang Lang
Julia = FilePath
"julia"
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" FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
sysName FilePath -> FilePath -> FilePath
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' (Header -> ShortName) -> Header -> ShortName
forall a b. (a -> b) -> a -> b
$ FilePath -> Header
S FilePath
refUID
sysName :: FilePath
sysName = case [Choices]
chcs of
[Choices
_] -> (Char -> Char) -> FilePath -> FilePath
forall a b. (a -> b) -> [a] -> [b]
map Char -> Char
toLower (FilePath -> FilePath) -> FilePath -> FilePath
forall a b. (a -> b) -> a -> b
$ a -> FilePath
forall c. CommonIdea c => c -> FilePath
programName a
sys
[Choices]
_ -> (Char -> Char) -> FilePath -> FilePath
forall a b. (a -> b) -> [a] -> [b]
map Char -> Char
toLower (a -> FilePath
forall c. CommonIdea c => c -> FilePath
programName a
sys) FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
"/" FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
verName
programLang :: FilePath
programLang = Lang -> FilePath
convertLang Lang
l
buildDrasilExSrcRef :: Example -> Reference
buildDrasilExSrcRef :: Example -> Reference
buildDrasilExSrcRef ex :: Example
ex@E{sysInfoE :: Example -> SystemInformation
sysInfoE=SI{_sys :: ()
_sys = a
sys}} =
FilePath -> FilePath -> ShortName -> Reference
makeURI FilePath
refUID FilePath
refURI ShortName
refShortNm
where
refUID :: FilePath
refUID = FilePath
"srcCodeRef" FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
sysName
refURI :: FilePath
refURI = FilePath
path FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
"code/drasil-example/" FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
sysName
refShortNm :: ShortName
refShortNm = Header -> ShortName
shortname' (Header -> ShortName) -> Header -> ShortName
forall a b. (a -> b) -> a -> b
$ FilePath -> Header
S FilePath
refUID
sysName :: FilePath
sysName = (Char -> Char) -> FilePath -> FilePath
forall a b. (a -> b) -> [a] -> [b]
map Char -> Char
toLower (FilePath -> FilePath) -> FilePath -> FilePath
forall a b. (a -> b) -> a -> b
$ a -> FilePath
forall c. CommonIdea c => c -> FilePath
programName a
sys
path :: FilePath
path = Example -> FilePath
codePath Example
ex
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" FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
progName FilePath -> FilePath -> FilePath
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' (Header -> ShortName) -> Header -> ShortName
forall a b. (a -> b) -> a -> b
$ FilePath -> Header
S FilePath
refUID
progName :: FilePath
progName = a -> FilePath
forall c. CommonIdea c => c -> FilePath
programName a
sys
programLang :: FilePath
programLang = case [Choices]
chcs of
[Choices
_] -> Lang -> FilePath
convertLang Lang
l
[Choices]
_ -> (Char -> Char) -> FilePath -> FilePath
forall a b. (a -> b) -> [a] -> [b]
map Char -> Char
toLower FilePath
verName FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
"/" FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ Lang -> FilePath
convertLang Lang
l
getSRSRef :: FilePath -> Format -> String -> Reference
getSRSRef :: FilePath -> Format -> FilePath -> Reference
getSRSRef FilePath
path Format
format FilePath
ex = FilePath -> FilePath -> ShortName -> Reference
makeURI FilePath
refUID (FilePath -> Format -> FilePath -> FilePath
getSRSPath FilePath
path Format
format FilePath
ex) (ShortName -> Reference) -> ShortName -> Reference
forall a b. (a -> b) -> a -> b
$ Header -> ShortName
shortname' (Header -> ShortName) -> Header -> ShortName
forall a b. (a -> b) -> a -> b
$ FilePath -> Header
S FilePath
refUID
where
refUID :: FilePath
refUID = Format -> FilePath
forall a. Show a => a -> FilePath
show Format
format FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
"Ref" FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
ex
getSRSPath :: FilePath -> Format -> String -> FilePath
getSRSPath :: FilePath -> Format -> FilePath -> FilePath
getSRSPath FilePath
path Format
format FilePath
ex = FilePath
path FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ (Char -> Char) -> FilePath -> FilePath
forall a b. (a -> b) -> [a] -> [b]
map Char -> Char
toLower FilePath
ex FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
"/SRS/" FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ Format -> FilePath
forall a. Show a => a -> FilePath
show Format
format FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
"/" FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ Format -> FilePath
sufx Format
format
where
sufx :: Format -> FilePath
sufx Format
MDBook = FilePath
"book"
sufx Format
HTML = FilePath
ex FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
"_SRS.html"
sufx Format
TeX = FilePath
ex FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
"_SRS.pdf"
sufx Format
_ = FilePath -> FilePath
forall a. HasCallStack => FilePath -> a
error FilePath
"You can only get paths for TeX/HTML/MDBook."
getCodePath, getDoxPath :: FilePath -> String -> String -> FilePath
getCodePath :: FilePath -> FilePath -> FilePath -> FilePath
getCodePath FilePath
path FilePath
ex FilePath
programLang = FilePath
path FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
"code/stable/" FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ (Char -> Char) -> FilePath -> FilePath
forall a b. (a -> b) -> [a] -> [b]
map Char -> Char
toLower FilePath
ex FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
"/src/" FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
programLang
getDoxPath :: FilePath -> FilePath -> FilePath -> FilePath
getDoxPath FilePath
path FilePath
ex FilePath
programLang = FilePath
path FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ (Char -> Char) -> FilePath -> FilePath
forall a b. (a -> b) -> [a] -> [b]
map Char -> Char
toLower FilePath
ex FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
"/doxygen/" FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
programLang FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
"/index.html"
exampleRefs :: FilePath -> FilePath -> [Reference]
exampleRefs :: FilePath -> FilePath -> [Reference]
exampleRefs FilePath
codePth FilePath
srsDoxPth =
(Example -> [Reference]) -> [Example] -> [Reference]
forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
concatMap Example -> [Reference]
getCodeRefDB (FilePath -> FilePath -> [Example]
examples FilePath
codePth FilePath
srsDoxPth) [Reference] -> [Reference] -> [Reference]
forall a. [a] -> [a] -> [a]
++
(Example -> [Reference]) -> [Example] -> [Reference]
forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
concatMap Example -> [Reference]
getDoxRefDB (FilePath -> FilePath -> [Example]
examples FilePath
codePth FilePath
srsDoxPth) [Reference] -> [Reference] -> [Reference]
forall a. [a] -> [a] -> [a]
++
(Example -> Reference) -> [Example] -> [Reference]
forall a b. (a -> b) -> [a] -> [b]
map (FilePath -> Format -> FilePath -> Reference
getSRSRef FilePath
srsDoxPth Format
HTML (FilePath -> Reference)
-> (Example -> FilePath) -> Example -> Reference
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Example -> FilePath
getAbrv) (FilePath -> FilePath -> [Example]
examples FilePath
codePth FilePath
srsDoxPth) [Reference] -> [Reference] -> [Reference]
forall a. [a] -> [a] -> [a]
++
(Example -> Reference) -> [Example] -> [Reference]
forall a b. (a -> b) -> [a] -> [b]
map (FilePath -> Format -> FilePath -> Reference
getSRSRef FilePath
srsDoxPth Format
TeX (FilePath -> Reference)
-> (Example -> FilePath) -> Example -> Reference
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Example -> FilePath
getAbrv) (FilePath -> FilePath -> [Example]
examples FilePath
codePth FilePath
srsDoxPth) [Reference] -> [Reference] -> [Reference]
forall a. [a] -> [a] -> [a]
++
(Example -> Reference) -> [Example] -> [Reference]
forall a b. (a -> b) -> [a] -> [b]
map (FilePath -> Format -> FilePath -> Reference
getSRSRef FilePath
srsDoxPth Format
MDBook (FilePath -> Reference)
-> (Example -> FilePath) -> Example -> Reference
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Example -> FilePath
getAbrv) (FilePath -> FilePath -> [Example]
examples FilePath
codePth FilePath
srsDoxPth) [Reference] -> [Reference] -> [Reference]
forall a. [a] -> [a] -> [a]
++
(Example -> Reference) -> [Example] -> [Reference]
forall a b. (a -> b) -> [a] -> [b]
map Example -> Reference
buildDrasilExSrcRef (FilePath -> FilePath -> [Example]
examples FilePath
codePth FilePath
srsDoxPth)
getCodeRefDB, getDoxRefDB :: Example -> [Reference]
getCodeRefDB :: Example -> [Reference]
getCodeRefDB Example
ex = (Choices -> [Reference]) -> [Choices] -> [Reference]
forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
concatMap (\Choices
x -> (Lang -> Reference) -> [Lang] -> [Reference]
forall a b. (a -> b) -> [a] -> [b]
map (\Lang
y -> Example -> Lang -> FilePath -> Reference
getCodeRef Example
ex Lang
y (FilePath -> Reference) -> FilePath -> Reference
forall a b. (a -> b) -> a -> b
$ Choices -> FilePath
verName Choices
x) ([Lang] -> [Reference]) -> [Lang] -> [Reference]
forall a b. (a -> b) -> a -> b
$ Choices -> [Lang]
lang Choices
x) ([Choices] -> [Reference]) -> [Choices] -> [Reference]
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 = (Choices -> [Reference]) -> [Choices] -> [Reference]
forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
concatMap (\Choices
x -> (Lang -> Reference) -> [Lang] -> [Reference]
forall a b. (a -> b) -> [a] -> [b]
map (\Lang
y -> Example -> Lang -> FilePath -> Reference
getDoxRef Example
ex Lang
y (FilePath -> Reference) -> FilePath -> Reference
forall a b. (a -> b) -> a -> b
$ Choices -> FilePath
verName Choices
x) ([Lang] -> [Reference]) -> [Lang] -> [Reference]
forall a b. (a -> b) -> a -> b
$ Choices -> [Lang]
lang Choices
x) ([Choices] -> [Reference]) -> [Choices] -> [Reference]
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}} = a -> FilePath
forall c. CommonIdea c => c -> FilePath
programName a
sys