{-# LANGUAGE TupleSections #-}
module Drasil.Website.Analysis where
import Language.Drasil
analysisSec :: FilePath -> FilePath -> FilePath -> FilePath -> [String] -> Section
analysisSec :: FilePath
-> FilePath -> FilePath -> FilePath -> [FilePath] -> Section
analysisSec FilePath
analysisPath FilePath
typePath FilePath
clsIPath FilePath
graphPath [FilePath]
pkgs =
Sentence -> [Contents] -> [Section] -> Reference -> Section
section Sentence
drasilAnalysisTitle
[Sentence -> Contents
mkParagraph Sentence
analysisIntro]
[FilePath -> Section
dataTableSec FilePath
analysisPath, FilePath -> FilePath -> [FilePath] -> Section
tableOfGraphsSec FilePath
typePath FilePath
clsIPath [FilePath]
pkgs,
FilePath -> [FilePath] -> Section
graphSec FilePath
graphPath ([FilePath] -> Section) -> [FilePath] -> Section
forall a b. (a -> b) -> a -> b
$ (FilePath -> FilePath) -> [FilePath] -> [FilePath]
forall a b. (a -> b) -> [a] -> [b]
map (FilePath
"drasil-" FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++) [FilePath]
pkgs]
(Reference -> Section) -> Reference -> Section
forall a b. (a -> b) -> a -> b
$ FilePath -> Sentence -> Reference
makeSecRef FilePath
"Analysis" (Sentence -> Reference) -> Sentence -> Reference
forall a b. (a -> b) -> a -> b
$ FilePath -> Sentence
S FilePath
"Analysis"
drasilAnalysisTitle :: Sentence
drasilAnalysisTitle :: Sentence
drasilAnalysisTitle = FilePath -> Sentence
S FilePath
"Analysis of Drasil"
analysisIntro :: Sentence
analysisIntro :: Sentence
analysisIntro = FilePath -> Sentence
S FilePath
"This section contains graphs and tables that may be used to analyze the \
\structure of the Drasil framework. Here, we will explore the relationship between data types, \
\classes, and instances of those classes within Drasil, as well as the structure of individual \
\Drasil packages."
analysisRefs :: FilePath -> FilePath -> FilePath -> FilePath -> [String] -> [Reference]
analysisRefs :: FilePath
-> FilePath -> FilePath -> FilePath -> [FilePath] -> [Reference]
analysisRefs FilePath
analysisPath FilePath
typePath FilePath
clsIPath FilePath
graphPath [FilePath]
pkgs =
[FilePath -> Reference
dataTableHTMLRef FilePath
analysisPath, FilePath -> Reference
dataTableCSVRef FilePath
analysisPath]
[Reference] -> [Reference] -> [Reference]
forall a. [a] -> [a] -> [a]
++ (FilePath -> Reference) -> [FilePath] -> [Reference]
forall a b. (a -> b) -> [a] -> [b]
map (FilePath -> FilePath -> FilePath -> FilePath -> Reference
getGraphsInTableRef FilePath
"datatype" FilePath
"" FilePath
typePath) [FilePath]
pkgs
[Reference] -> [Reference] -> [Reference]
forall a. [a] -> [a] -> [a]
++ (FilePath -> Reference) -> [FilePath] -> [Reference]
forall a b. (a -> b) -> [a] -> [b]
map (FilePath -> FilePath -> FilePath -> FilePath -> Reference
getGraphsInTableRef FilePath
"classInst" FilePath
"" FilePath
clsIPath) [FilePath]
pkgs
[Reference] -> [Reference] -> [Reference]
forall a. [a] -> [a] -> [a]
++ (FilePath -> Reference) -> [FilePath] -> [Reference]
forall a b. (a -> b) -> [a] -> [b]
map (FilePath -> FilePath -> FilePath -> FilePath -> Reference
getGraphsInTableRef FilePath
"datatype" FilePath
"circo_" FilePath
typePath) [FilePath]
pkgs
[Reference] -> [Reference] -> [Reference]
forall a. [a] -> [a] -> [a]
++ (FilePath -> Reference) -> [FilePath] -> [Reference]
forall a b. (a -> b) -> [a] -> [b]
map (FilePath -> FilePath -> FilePath -> FilePath -> Reference
getGraphsInTableRef FilePath
"classInst" FilePath
"circo_" FilePath
clsIPath) [FilePath]
pkgs
[Reference] -> [Reference] -> [Reference]
forall a. [a] -> [a] -> [a]
++ FilePath -> [FilePath] -> [Reference]
drasilDepGraphRefs FilePath
graphPath ((FilePath -> FilePath) -> [FilePath] -> [FilePath]
forall a b. (a -> b) -> [a] -> [b]
map (FilePath
"drasil-" FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++) [FilePath]
pkgs)
dataTableSec :: FilePath -> Section
dataTableSec :: FilePath -> Section
dataTableSec FilePath
path =
Sentence -> [Contents] -> [Section] -> Reference -> Section
section Sentence
dataTableTitle
[Sentence -> Contents
mkParagraph (Sentence -> Contents) -> Sentence -> Contents
forall a b. (a -> b) -> a -> b
$ FilePath -> Sentence
dataTableDesc FilePath
path]
[] (Reference -> Section) -> Reference -> Section
forall a b. (a -> b) -> a -> b
$ FilePath -> Sentence -> Reference
makeSecRef FilePath
"DataTable" (Sentence -> Reference) -> Sentence -> Reference
forall a b. (a -> b) -> a -> b
$ FilePath -> Sentence
S FilePath
"DataTable"
dataTableTitle :: Sentence
dataTableTitle :: Sentence
dataTableTitle = FilePath -> Sentence
S FilePath
"Intersections of Types and Classes"
dataTableDesc :: FilePath -> Sentence
dataTableDesc :: FilePath -> Sentence
dataTableDesc FilePath
path = FilePath -> Sentence
S FilePath
"This" Sentence -> Sentence -> Sentence
+:+ Reference -> Sentence -> Sentence
forall r.
(HasUID r, HasRefAddress r, HasShortName r) =>
r -> Sentence -> Sentence
namedRef (FilePath -> Reference
dataTableHTMLRef FilePath
path) (FilePath -> Sentence
S FilePath
"Data Table") Sentence -> Sentence -> Sentence
+:+
FilePath -> Sentence
S FilePath
"is generated by Drasil to keep track of all the different types, classes, and where they intersect through instances. \
\The rows are organized in order of Drasil packages, modules, and data types. \
\The data types are further separated by their composition; those labelled \
\Data Type are completely new types created and used in Drasil, while Newtype Types are \
\type synonyms. All of the classes in Drasil are defined as \
\column headers, starting from Haskell-native classes like Eq and going through every \
\unique Drasil-defined class. A box marked with \
\'YYYY' symbolizes the file location of where that particular data type is an instance of a particular class. \
\There is also a" Sentence -> Sentence -> Sentence
+:+ Reference -> Sentence -> Sentence
forall r.
(HasUID r, HasRefAddress r, HasShortName r) =>
r -> Sentence -> Sentence
namedRef (FilePath -> Reference
dataTableCSVRef FilePath
path) (FilePath -> Sentence
S FilePath
"downloadable version") Sentence -> Sentence -> Sentence
+:+ FilePath -> Sentence
S FilePath
"of the Data Table available as a .csv file."
dataTableHTMLRef, dataTableCSVRef :: FilePath -> Reference
dataTableHTMLRef :: FilePath -> Reference
dataTableHTMLRef FilePath
path = FilePath -> FilePath -> ShortName -> Reference
makeURI FilePath
"dataTableHTML" (FilePath
path FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
"ClassInstDep/DataTable.html") (Sentence -> ShortName
shortname' (Sentence -> ShortName) -> Sentence -> ShortName
forall a b. (a -> b) -> a -> b
$ FilePath -> Sentence
S FilePath
"dataTableHTML")
dataTableCSVRef :: FilePath -> Reference
dataTableCSVRef FilePath
path = FilePath -> FilePath -> ShortName -> Reference
makeURI FilePath
"dataTableCSV" (FilePath
path FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
"ClassInstDep/DataTable.csv") (Sentence -> ShortName
shortname' (Sentence -> ShortName) -> Sentence -> ShortName
forall a b. (a -> b) -> a -> b
$ FilePath -> Sentence
S FilePath
"dataTableCSV")
tableOfGraphsSec :: FilePath -> FilePath -> [String] -> Section
tableOfGraphsSec :: FilePath -> FilePath -> [FilePath] -> Section
tableOfGraphsSec FilePath
typePath FilePath
clsIPath [FilePath]
pkgs =
Sentence -> [Contents] -> [Section] -> Reference -> Section
section Sentence
tableOfGraphsTitle
[Sentence -> Contents
mkParagraph Sentence
tableOfGraphsDescType, Sentence -> Contents
mkParagraph Sentence
tableOfGraphsDescClassInst, FilePath -> FilePath -> [FilePath] -> Contents
mkGraphsTable FilePath
typePath FilePath
clsIPath [FilePath]
pkgs]
[] (Reference -> Section) -> Reference -> Section
forall a b. (a -> b) -> a -> b
$ FilePath -> Sentence -> Reference
makeSecRef FilePath
"TypeAndClassGraphs" (Sentence -> Reference) -> Sentence -> Reference
forall a b. (a -> b) -> a -> b
$ FilePath -> Sentence
S FilePath
"TypeAndClassGraphs"
tableOfGraphsTitle :: Sentence
tableOfGraphsTitle :: Sentence
tableOfGraphsTitle = FilePath -> Sentence
S FilePath
"Table of Graphs"
graphTable :: String -> FilePath -> String -> FilePath -> [String] -> [[Sentence]]
graphTable :: FilePath
-> FilePath -> FilePath -> FilePath -> [FilePath] -> [[Sentence]]
graphTable FilePath
knd1 FilePath
path1 FilePath
knd2 FilePath
path2 = (FilePath -> [Sentence]) -> [FilePath] -> [[Sentence]]
forall a b. (a -> b) -> [a] -> [b]
map (FilePath
-> FilePath -> FilePath -> FilePath -> FilePath -> [Sentence]
graphTableEntry FilePath
knd1 FilePath
path1 FilePath
knd2 FilePath
path2)
graphTableEntry :: String -> FilePath -> String -> FilePath -> String -> [Sentence]
graphTableEntry :: FilePath
-> FilePath -> FilePath -> FilePath -> FilePath -> [Sentence]
graphTableEntry FilePath
knd1 FilePath
path1 FilePath
knd2 FilePath
path2 FilePath
pkg =
[Reference -> Sentence -> Sentence
forall r.
(HasUID r, HasRefAddress r, HasShortName r) =>
r -> Sentence -> Sentence
namedRef (FilePath -> FilePath -> FilePath -> FilePath -> Reference
getGraphsInTableRef FilePath
knd1 FilePath
"" FilePath
path1 FilePath
pkg) (FilePath -> Sentence
S FilePath
"drasil-" Sentence -> Sentence -> Sentence
:+: FilePath -> Sentence
S FilePath
pkg Sentence -> Sentence -> Sentence
+:+ FilePath -> Sentence
S FilePath
"Types"),
Reference -> Sentence -> Sentence
forall r.
(HasUID r, HasRefAddress r, HasShortName r) =>
r -> Sentence -> Sentence
namedRef (FilePath -> FilePath -> FilePath -> FilePath -> Reference
getGraphsInTableRef FilePath
knd2 FilePath
"" FilePath
path2 FilePath
pkg) (FilePath -> Sentence
S FilePath
"drasil-" Sentence -> Sentence -> Sentence
:+: FilePath -> Sentence
S FilePath
pkg Sentence -> Sentence -> Sentence
+:+ FilePath -> Sentence
S FilePath
"Class Instances")]
getGraphsInTableRef :: String -> String -> FilePath -> String -> Reference
getGraphsInTableRef :: FilePath -> FilePath -> FilePath -> FilePath -> Reference
getGraphsInTableRef FilePath
knd FilePath
prfx FilePath
path FilePath
pkg = FilePath -> FilePath -> ShortName -> Reference
makeURI (FilePath
knd FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
pkg FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
prfx FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
"graph") (FilePath
path FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
prfx FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
pkg FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
".svg") (ShortName -> Reference) -> ShortName -> Reference
forall a b. (a -> b) -> a -> b
$ Sentence -> ShortName
shortname' (Sentence -> ShortName) -> Sentence -> ShortName
forall a b. (a -> b) -> a -> b
$ FilePath -> Sentence
S (FilePath -> Sentence) -> FilePath -> Sentence
forall a b. (a -> b) -> a -> b
$ FilePath
pkg FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
prfx FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
"graph"
tableOfGraphsDescType :: Sentence
tableOfGraphsDescType :: Sentence
tableOfGraphsDescType = FilePath -> Sentence
S FilePath
"The following" Sentence -> Sentence -> Sentence
+:+ Reference -> Sentence -> Sentence
forall r.
(HasUID r, HasRefAddress r, HasShortName r) =>
r -> Sentence -> Sentence
namedRef Reference
tableGraphRef (FilePath -> Sentence
S FilePath
"Table of Type and Class Instance Graphs") Sentence -> Sentence -> Sentence
+:+ FilePath -> Sentence
S FilePath
"is another artifact generated by Drasil. \
\The type graphs explore the dependency of data types upon each other. These graphs include record-defined types, newtype wrappers, \
\and data types built from other types. For these graphs, a node with a black outline signifies that the type is not defined in that package, \
\but is still used in the creation of other types (this includes Haskell-native types since we do not redefine those). A red outline signifies \
\that the type was created using Haskell's 'type' syntax, while dark green means the type was made using 'newtype' syntax. A purple border shows \
\that the type uses constructor syntax and cyan is used for types written with record syntax. The arrow starts from the base types at the tip and \
\follows through so that dependent types are placed at the tail. Usually, this means that those types at the tail may contain the type at the tip of the arrow."
tableOfGraphsDescClassInst :: Sentence
tableOfGraphsDescClassInst :: Sentence
tableOfGraphsDescClassInst = FilePath -> Sentence
S FilePath
"The class instance graphs aim to look at the structure of classes, data types, and the interactions \
\between those two. Specifically, each arrow represents the given type as an instance of a given class. The tip of the arrow points to the class, and the \
\tail specifies the type that is an instance of the tip's class. For clarity in analyzing the structure, classes defined in the graph's package are coloured magenta, \
\classes that are used but not defined in the package are rendered pink (including Haskell-native classes), and data types are rendered with a turquoise border."
mkGraphsTable :: FilePath -> FilePath -> [String] -> Contents
mkGraphsTable :: FilePath -> FilePath -> [FilePath] -> Contents
mkGraphsTable FilePath
typePath FilePath
clsInstPath [FilePath]
pkgs = LabelledContent -> Contents
LlC (LabelledContent -> Contents) -> LabelledContent -> Contents
forall a b. (a -> b) -> a -> b
$ Reference -> RawContent -> LabelledContent
llcc Reference
tableGraphRef (RawContent -> LabelledContent) -> RawContent -> LabelledContent
forall a b. (a -> b) -> a -> b
$ [Sentence] -> [[Sentence]] -> Sentence -> Bool -> RawContent
Table
[FilePath -> Sentence
S FilePath
"Generated Type Graphs", FilePath -> Sentence
S FilePath
"Generated Class Instance Graphs"]
(FilePath
-> FilePath -> FilePath -> FilePath -> [FilePath] -> [[Sentence]]
graphTable FilePath
"datatype" FilePath
typePath FilePath
"classInst" FilePath
clsInstPath [FilePath]
pkgs)
(FilePath -> Sentence
S FilePath
"Type Graphs") Bool
True
tableGraphRef :: Reference
tableGraphRef :: Reference
tableGraphRef = FilePath -> Reference
makeTabRef FilePath
"TableOfGraphs"
graphSec :: FilePath -> [String] -> Section
graphSec :: FilePath -> [FilePath] -> Section
graphSec FilePath
path [FilePath]
pkgs =
Sentence -> [Contents] -> [Section] -> Reference -> Section
section Sentence
packDepGraphTitle
(Sentence -> Contents
mkParagraph (FilePath -> Sentence
S FilePath
graphSecIntro) Contents -> [Contents] -> [Contents]
forall a. a -> [a] -> [a]
: [Contents]
displayGraphs [Contents] -> [Contents] -> [Contents]
forall a. [a] -> [a] -> [a]
++ [Contents]
listOfLinkedGraphs [Contents] -> [Contents] -> [Contents]
forall a. [a] -> [a] -> [a]
++ Sentence -> Contents
mkParagraph (FilePath -> Sentence
S FilePath
graphSecBwPkgs) Contents -> [Contents] -> [Contents]
forall a. a -> [a] -> [a]
: [Contents]
displayPkgsDepGraph)
[] (Reference -> Section) -> Reference -> Section
forall a b. (a -> b) -> a -> b
$ FilePath -> Sentence -> Reference
makeSecRef FilePath
"DependencyGraphs" (Sentence -> Reference) -> Sentence -> Reference
forall a b. (a -> b) -> a -> b
$ FilePath -> Sentence
S FilePath
"Dependency Graphs"
where
displayGraphs :: [Contents]
displayGraphs = [FilePath -> FilePath -> Contents
dependencyGraphs FilePath
path FilePath
"drasil-website"]
displayPkgsDepGraph :: [Contents]
displayPkgsDepGraph = [FilePath -> FilePath -> Contents
dependencyGraphs FilePath
path FilePath
"drasil-all-pkgs-deps"]
listOfLinkedGraphs :: [Contents]
listOfLinkedGraphs = [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
folderList FilePath
path [FilePath]
pkgs]
packDepGraphTitle :: Sentence
packDepGraphTitle :: Sentence
packDepGraphTitle = FilePath -> Sentence
S FilePath
"Package Dependency Graphs"
graphSecIntro :: String
graphSecIntro :: FilePath
graphSecIntro = FilePath
"The below list contains all of the different packages used to build the Drasil Framework. \
\Each package and its dependencies are displayed in the form of a graph, with the tail of the arrow being the dependent module, \
\and the tip of the arrow being the base module. In other words, the tip builds off of (or relies on) the tail to work. \
\Links are available to a PDF version of each package's dependency graph at the bottom. For example, the graph for the website package \
\is shown below. Each section is made from different modules that come together under the Drasil.Website.Body module and then \
\are generated by Drasil.Website.Main. This result shows that the package structure has a pyramid-like hierarchy."
graphSecBwPkgs :: String
graphSecBwPkgs :: FilePath
graphSecBwPkgs = FilePath
"The graph displayed below shows the dependencies between the packages used to build the Drasil Framework."
dependencyGraphs :: FilePath -> String -> Contents
dependencyGraphs :: FilePath -> FilePath -> Contents
dependencyGraphs FilePath
path FilePath
pkg = LabelledContent -> Contents
LlC (LabelledContent -> Contents) -> LabelledContent -> Contents
forall a b. (a -> b) -> a -> b
$ Reference -> RawContent -> LabelledContent
llcc (FilePath -> Reference
makeFigRef (FilePath -> Reference) -> FilePath -> Reference
forall a b. (a -> b) -> a -> b
$ FilePath
"Figure" FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
pkg) (RawContent -> LabelledContent) -> RawContent -> LabelledContent
forall a b. (a -> b) -> a -> b
$ Sentence -> FilePath -> RawContent
fig (FilePath -> Sentence
S (FilePath -> Sentence) -> FilePath -> Sentence
forall a b. (a -> b) -> a -> b
$ FilePath
"Package - " FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
pkg) (FilePath -> FilePath -> FilePath
drasilDisplayDepGraphPath FilePath
path FilePath
pkg)
drasilDisplayDepGraphPath :: FilePath -> FilePath -> String
drasilDisplayDepGraphPath :: FilePath -> FilePath -> FilePath
drasilDisplayDepGraphPath FilePath
path FilePath
fldr = FilePath
path FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
fldr FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
".png"
drasilDepGraphPathsPDF :: FilePath -> [String] -> [String]
drasilDepGraphPathsPDF :: FilePath -> [FilePath] -> [FilePath]
drasilDepGraphPathsPDF FilePath
path = (FilePath -> FilePath) -> [FilePath] -> [FilePath]
forall a b. (a -> b) -> [a] -> [b]
map (\FilePath
x -> FilePath
path FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
x FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
".pdf")
drasilDepGraphRefs :: FilePath -> [String] -> [Reference]
drasilDepGraphRefs :: FilePath -> [FilePath] -> [Reference]
drasilDepGraphRefs FilePath
path [FilePath]
pkgs = (FilePath -> FilePath -> Reference)
-> [FilePath] -> [FilePath] -> [Reference]
forall a b c. (a -> b -> c) -> [a] -> [b] -> [c]
zipWith (\FilePath
x FilePath
y -> FilePath -> FilePath -> ShortName -> Reference
makeURI FilePath
x FilePath
y (ShortName -> Reference) -> ShortName -> Reference
forall a b. (a -> b) -> a -> b
$ Sentence -> ShortName
shortname' (Sentence -> ShortName) -> Sentence -> ShortName
forall a b. (a -> b) -> a -> b
$ FilePath -> Sentence
S FilePath
x) [FilePath]
pkgs ([FilePath] -> [Reference]) -> [FilePath] -> [Reference]
forall a b. (a -> b) -> a -> b
$ FilePath -> [FilePath] -> [FilePath]
drasilDepGraphPathsPDF FilePath
path [FilePath]
pkgs
folderList :: FilePath -> [String] -> RawContent
folderList :: FilePath -> [FilePath] -> RawContent
folderList FilePath
path [FilePath]
pkgs = 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) (FilePath -> [FilePath] -> [ItemType]
folderListItems FilePath
path [FilePath]
pkgs)
folderListItems :: FilePath -> [String] -> [ItemType]
folderListItems :: FilePath -> [FilePath] -> [ItemType]
folderListItems FilePath
path [FilePath]
pkgs = (Sentence -> ItemType) -> [Sentence] -> [ItemType]
forall a b. (a -> b) -> [a] -> [b]
map Sentence -> ItemType
Flat ([Sentence] -> [ItemType]) -> [Sentence] -> [ItemType]
forall a b. (a -> b) -> a -> b
$ (Reference -> Sentence -> Sentence)
-> [Reference] -> [Sentence] -> [Sentence]
forall a b c. (a -> b -> c) -> [a] -> [b] -> [c]
zipWith Reference -> Sentence -> Sentence
forall r.
(HasUID r, HasRefAddress r, HasShortName r) =>
r -> Sentence -> Sentence
namedRef (FilePath -> [FilePath] -> [Reference]
drasilDepGraphRefs FilePath
path [FilePath]
pkgs) ([Sentence] -> [Sentence]) -> [Sentence] -> [Sentence]
forall a b. (a -> b) -> a -> b
$ (FilePath -> Sentence) -> [FilePath] -> [Sentence]
forall a b. (a -> b) -> [a] -> [b]
map FilePath -> Sentence
S [FilePath]
pkgs