{-# LANGUAGE PostfixOperators, TupleSections #-}
module Drasil.DocumentLanguage.TraceabilityGraph where
import Language.Drasil
import Database.Drasil hiding (cdb)
import SysInfo.Drasil
import Control.Lens ((^.))
import qualified Data.Map as Map
import Drasil.DocumentLanguage.TraceabilityMatrix (TraceViewCat, traceMReferees, traceMReferrers,
traceMColumns, layoutUIDs, traceMIntro)
import Drasil.Sections.TraceabilityMandGs (tvAssumps,
tvDataDefns, tvGenDefns, tvTheoryModels, tvInsModels, tvGoals, tvReqs,
tvChanges)
import qualified Drasil.DocLang.SRS as SRS
import Language.Drasil.Printers (GraphInfo(..), NodeFamily(..))
import Data.Maybe (fromMaybe)
import Data.Drasil.Concepts.Math (graph)
import Data.Drasil.Concepts.Documentation (traceyGraph, component, dependency, reference, purpose, traceyMatrix)
import qualified Language.Drasil.Sentence.Combinators as S
import Data.Char (toLower)
import Drasil.Sections.ReferenceMaterial (emptySectSentPlu)
traceMGF :: [LabelledContent] -> [Sentence] -> [Contents] -> String -> [Section] -> Section
traceMGF :: [LabelledContent]
-> [Sentence] -> [Contents] -> String -> [Section] -> Section
traceMGF [] [] [] String
_ = [Contents] -> [Section] -> Section
SRS.traceyMandG [Sentence -> Contents
mkParagraph forall a b. (a -> b) -> a -> b
$ forall n. NamedIdea n => [n] -> Sentence
emptySectSentPlu [IdeaDict
traceyMatrix, IdeaDict
traceyGraph]]
traceMGF [LabelledContent]
refs [Sentence]
trailing [Contents]
otherContents String
ex = [Contents] -> [Section] -> Section
SRS.traceyMandG ([LabelledContent] -> [Sentence] -> Contents
traceMIntro [LabelledContent]
refs [Sentence]
trailing forall a. a -> [a] -> [a]
: [Contents]
otherContents
forall a. [a] -> [a] -> [a]
++ forall a b. (a -> b) -> [a] -> [b]
map UnlabelledContent -> Contents
UlC ([UID] -> [Sentence] -> [UnlabelledContent]
traceGIntro [UID]
traceGUIDs ([Sentence]
trailing forall a. [a] -> [a] -> [a]
++ [Sentence
allvsallDesc])) forall a. [a] -> [a] -> [a]
++ String -> [Contents]
traceGCon String
ex)
traceGIntro :: [UID] -> [Sentence] -> [UnlabelledContent]
traceGIntro :: [UID] -> [Sentence] -> [UnlabelledContent]
traceGIntro [UID]
refs [Sentence]
trailings = [RawContent -> UnlabelledContent
ulcc forall a b. (a -> b) -> a -> b
$ Sentence -> RawContent
Paragraph forall a b. (a -> b) -> a -> b
$ [Sentence] -> Sentence
foldlSent
[forall n. NamedIdea n => n -> Sentence
phrase IdeaDict
purpose Sentence -> Sentence -> Sentence
`S.the_ofTheC` forall n. NamedIdea n => n -> Sentence
plural IdeaDict
traceyGraph,
String -> Sentence
S String
"is also to provide easy", forall n. NamedIdea n => n -> Sentence
plural IdeaDict
reference, String -> Sentence
S String
"on what has to be",
String -> Sentence
S String
"additionally modified if a certain", forall n. NamedIdea n => n -> Sentence
phrase IdeaDict
component Sentence -> Sentence -> Sentence
+:+. String -> Sentence
S String
"is changed",
String -> Sentence
S String
"The arrows in the", forall n. NamedIdea n => n -> Sentence
plural ConceptChunk
graph, String -> Sentence
S String
"represent" Sentence -> Sentence -> Sentence
+:+. forall n. NamedIdea n => n -> Sentence
plural IdeaDict
dependency,
String -> Sentence
S String
"The", forall n. NamedIdea n => n -> Sentence
phrase IdeaDict
component, String -> Sentence
S String
"at the tail of an arrow is depended on by the",
forall n. NamedIdea n => n -> Sentence
phrase IdeaDict
component, String -> Sentence
S String
"at the head of that arrow. Therefore, if a", forall n. NamedIdea n => n -> Sentence
phrase IdeaDict
component,
String -> Sentence
S String
"is changed, the", forall n. NamedIdea n => n -> Sentence
plural IdeaDict
component, String -> Sentence
S String
"that it points to should also be changed"] Sentence -> Sentence -> Sentence
+:+
[Sentence] -> Sentence
foldlSent_ (forall a b c. (a -> b -> c) -> [a] -> [b] -> [c]
zipWith UID -> Sentence -> Sentence
graphShows [UID]
refs [Sentence]
trailings)]
mkGraphInfo :: SystemInformation -> GraphInfo
mkGraphInfo :: SystemInformation -> GraphInfo
mkGraphInfo SystemInformation
si = GI {
assumpNF :: NodeFamily
assumpNF = TraceViewCat -> SystemInformation -> String -> NodeFamily
mkGraphNodes TraceViewCat
tvAssumps SystemInformation
si String
"mistyrose"
, ddNF :: NodeFamily
ddNF = TraceViewCat -> SystemInformation -> String -> NodeFamily
mkGraphNodes TraceViewCat
tvDataDefns SystemInformation
si String
"paleturquoise1"
, gdNF :: NodeFamily
gdNF = TraceViewCat -> SystemInformation -> String -> NodeFamily
mkGraphNodes TraceViewCat
tvGenDefns SystemInformation
si String
"palegreen"
, tmNF :: NodeFamily
tmNF = TraceViewCat -> SystemInformation -> String -> NodeFamily
mkGraphNodes TraceViewCat
tvTheoryModels SystemInformation
si String
"pink"
, imNF :: NodeFamily
imNF = TraceViewCat -> SystemInformation -> String -> NodeFamily
mkGraphNodes TraceViewCat
tvInsModels SystemInformation
si String
"khaki1"
, reqNF :: NodeFamily
reqNF = TraceViewCat -> SystemInformation -> String -> NodeFamily
mkGraphNodes TraceViewCat
tvReqs SystemInformation
si String
"ivory"
, gsNF :: NodeFamily
gsNF = TraceViewCat -> SystemInformation -> String -> NodeFamily
mkGraphNodes TraceViewCat
tvGoals SystemInformation
si String
"darkgoldenrod1"
, chgNF :: NodeFamily
chgNF = TraceViewCat -> SystemInformation -> String -> NodeFamily
mkGraphNodes TraceViewCat
tvChanges SystemInformation
si String
"lavender"
, edgesAvsA :: [(UID, [UID])]
edgesAvsA = [TraceViewCat]
-> [TraceViewCat] -> SystemInformation -> [(UID, [UID])]
mkGraphEdges [TraceViewCat
tvAssumps] [TraceViewCat
tvAssumps] SystemInformation
si
, edgesAvsAll :: [(UID, [UID])]
edgesAvsAll = [TraceViewCat]
-> [TraceViewCat] -> SystemInformation -> [(UID, [UID])]
mkGraphEdges [TraceViewCat
tvAssumps] [TraceViewCat
tvDataDefns, TraceViewCat
tvTheoryModels, TraceViewCat
tvGenDefns, TraceViewCat
tvInsModels, TraceViewCat
tvReqs, TraceViewCat
tvChanges] SystemInformation
si
, edgesRefvsRef :: [(UID, [UID])]
edgesRefvsRef = [TraceViewCat]
-> [TraceViewCat] -> SystemInformation -> [(UID, [UID])]
mkGraphEdges [TraceViewCat
tvDataDefns, TraceViewCat
tvTheoryModels, TraceViewCat
tvGenDefns, TraceViewCat
tvInsModels] [TraceViewCat
tvDataDefns, TraceViewCat
tvTheoryModels, TraceViewCat
tvGenDefns, TraceViewCat
tvInsModels] SystemInformation
si
, edgesAllvsR :: [(UID, [UID])]
edgesAllvsR = [TraceViewCat]
-> [TraceViewCat] -> SystemInformation -> [(UID, [UID])]
mkGraphEdges [TraceViewCat
tvDataDefns, TraceViewCat
tvTheoryModels,TraceViewCat
tvGenDefns, TraceViewCat
tvInsModels, TraceViewCat
tvReqs] [TraceViewCat
tvGoals, TraceViewCat
tvReqs] SystemInformation
si
, edgesAllvsAll :: [(UID, [UID])]
edgesAllvsAll = [TraceViewCat]
-> [TraceViewCat] -> SystemInformation -> [(UID, [UID])]
mkGraphEdges [TraceViewCat
tvAssumps, TraceViewCat
tvDataDefns, TraceViewCat
tvTheoryModels, TraceViewCat
tvGenDefns, TraceViewCat
tvInsModels, TraceViewCat
tvReqs, TraceViewCat
tvGoals, TraceViewCat
tvChanges] [TraceViewCat
tvAssumps, TraceViewCat
tvDataDefns, TraceViewCat
tvTheoryModels, TraceViewCat
tvGenDefns, TraceViewCat
tvInsModels, TraceViewCat
tvReqs, TraceViewCat
tvGoals, TraceViewCat
tvChanges] SystemInformation
si
}
mkGraphNodes :: TraceViewCat -> SystemInformation -> String -> NodeFamily
mkGraphNodes :: TraceViewCat -> SystemInformation -> String -> NodeFamily
mkGraphNodes TraceViewCat
entry SystemInformation
si String
col = NF {nodeUIDs :: [UID]
nodeUIDs = [UID]
nodeContents, nodeLabels :: [String]
nodeLabels = forall a b. (a -> b) -> [a] -> [b]
map (SystemInformation -> UID -> String
checkUIDRefAdd SystemInformation
si) [UID]
nodeContents, nfLabel :: String
nfLabel = [UID] -> String
checkNodeContents [UID]
nodeContents, nfColour :: String
nfColour = String
col}
where
checkNodeContents :: [UID] -> String
checkNodeContents :: [UID] -> String
checkNodeContents [] = String
""
checkNodeContents (UID
x:[UID]
_) = SystemInformation -> UID -> String
checkUIDAbbrev SystemInformation
si UID
x
nodeContents :: [UID]
nodeContents = ([UID] -> [UID]) -> ChunkDB -> [UID]
traceMReferees [UID] -> [UID]
entryF ChunkDB
cdb
cdb :: ChunkDB
cdb = SystemInformation -> ChunkDB
_sysinfodb SystemInformation
si
entryF :: [UID] -> [UID]
entryF = [TraceViewCat] -> ChunkDB -> [UID] -> [UID]
layoutUIDs [TraceViewCat
entry] ChunkDB
cdb
mkGraphEdges :: [TraceViewCat] -> [TraceViewCat] -> SystemInformation -> [(UID, [UID])]
mkGraphEdges :: [TraceViewCat]
-> [TraceViewCat] -> SystemInformation -> [(UID, [UID])]
mkGraphEdges [TraceViewCat]
cols [TraceViewCat]
rows SystemInformation
si = [UID] -> [[UID]] -> [UID] -> [(UID, [UID])]
makeTGraph (([UID] -> [UID]) -> SystemInformation -> [UID]
traceGRowHeader [UID] -> [UID]
rowf SystemInformation
si) (([UID] -> [UID]) -> ([UID] -> [UID]) -> ChunkDB -> [[UID]]
traceMColumns [UID] -> [UID]
colf [UID] -> [UID]
rowf ChunkDB
cdb) forall a b. (a -> b) -> a -> b
$ ([UID] -> [UID]) -> ChunkDB -> [UID]
traceMReferees [UID] -> [UID]
colf ChunkDB
cdb
where
cdb :: ChunkDB
cdb = SystemInformation -> ChunkDB
_sysinfodb SystemInformation
si
colf :: [UID] -> [UID]
colf = [TraceViewCat] -> ChunkDB -> [UID] -> [UID]
layoutUIDs [TraceViewCat]
cols ChunkDB
cdb
rowf :: [UID] -> [UID]
rowf = [TraceViewCat] -> ChunkDB -> [UID] -> [UID]
layoutUIDs [TraceViewCat]
rows ChunkDB
cdb
makeTGraph :: [UID] -> [[UID]] -> [UID] -> [(UID, [UID])]
makeTGraph :: [UID] -> [[UID]] -> [UID] -> [(UID, [UID])]
makeTGraph [UID]
rowName [[UID]]
rows [UID]
cols = forall a b. [a] -> [b] -> [(a, b)]
zip [UID]
rowName [forall {t :: * -> *} {a}. (Foldable t, Eq a) => t a -> [a] -> [a]
zipFTable' [UID]
x [UID]
cols | [UID]
x <- [[UID]]
rows]
where
zipFTable' :: t a -> [a] -> [a]
zipFTable' t a
content = forall a. (a -> Bool) -> [a] -> [a]
filter (forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` t a
content)
checkUID :: UID -> SystemInformation -> UID
checkUID :: UID -> SystemInformation -> UID
checkUID UID
t SystemInformation
si
| Just Int
_ <- forall k a. Ord k => k -> Map k a -> Maybe Int
Map.lookupIndex UID
t (ChunkDB
s forall s a. s -> Getting a s a -> a
^. Lens' ChunkDB (Map UID (DataDefinition, Int))
dataDefnTable) = UID
t
| Just Int
_ <- forall k a. Ord k => k -> Map k a -> Maybe Int
Map.lookupIndex UID
t (ChunkDB
s forall s a. s -> Getting a s a -> a
^. Lens' ChunkDB (Map UID (InstanceModel, Int))
insmodelTable) = UID
t
| Just Int
_ <- forall k a. Ord k => k -> Map k a -> Maybe Int
Map.lookupIndex UID
t (ChunkDB
s forall s a. s -> Getting a s a -> a
^. Lens' ChunkDB (Map UID (GenDefn, Int))
gendefTable) = UID
t
| Just Int
_ <- forall k a. Ord k => k -> Map k a -> Maybe Int
Map.lookupIndex UID
t (ChunkDB
s forall s a. s -> Getting a s a -> a
^. Lens' ChunkDB (Map UID (TheoryModel, Int))
theoryModelTable) = UID
t
| Just Int
_ <- forall k a. Ord k => k -> Map k a -> Maybe Int
Map.lookupIndex UID
t (ChunkDB
s forall s a. s -> Getting a s a -> a
^. Lens' ChunkDB (Map UID (ConceptInstance, Int))
conceptinsTable) = UID
t
| Just Int
_ <- forall k a. Ord k => k -> Map k a -> Maybe Int
Map.lookupIndex UID
t (ChunkDB
s forall s a. s -> Getting a s a -> a
^. Lens' ChunkDB (Map UID (Section, Int))
sectionTable) = UID
t
| Just Int
_ <- forall k a. Ord k => k -> Map k a -> Maybe Int
Map.lookupIndex UID
t (ChunkDB
s forall s a. s -> Getting a s a -> a
^. Lens' ChunkDB (Map UID (LabelledContent, Int))
labelledcontentTable) = UID
t
| UID
t forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` forall a b. (a -> b) -> [a] -> [b]
map (forall s a. s -> Getting a s a -> a
^. forall c. HasUID c => Lens' c UID
uid) (SystemInformation -> BibRef
citeDB SystemInformation
si) = String -> UID
mkUid String
""
| Bool
otherwise = forall a. HasCallStack => String -> a
error forall a b. (a -> b) -> a -> b
$ forall a. Show a => a -> String
show UID
t forall a. [a] -> [a] -> [a]
++ String
"Caught."
where s :: ChunkDB
s = SystemInformation -> ChunkDB
_sysinfodb SystemInformation
si
checkUIDAbbrev :: SystemInformation -> UID -> String
checkUIDAbbrev :: SystemInformation -> UID -> String
checkUIDAbbrev SystemInformation
si UID
t
| Just (DataDefinition
x, Int
_) <- forall k a. Ord k => k -> Map k a -> Maybe a
Map.lookup UID
t (ChunkDB
s forall s a. s -> Getting a s a -> a
^. Lens' ChunkDB (Map UID (DataDefinition, Int))
dataDefnTable) = forall c. CommonIdea c => c -> String
abrv DataDefinition
x
| Just (InstanceModel
x, Int
_) <- forall k a. Ord k => k -> Map k a -> Maybe a
Map.lookup UID
t (ChunkDB
s forall s a. s -> Getting a s a -> a
^. Lens' ChunkDB (Map UID (InstanceModel, Int))
insmodelTable) = forall c. CommonIdea c => c -> String
abrv InstanceModel
x
| Just (GenDefn
x, Int
_) <- forall k a. Ord k => k -> Map k a -> Maybe a
Map.lookup UID
t (ChunkDB
s forall s a. s -> Getting a s a -> a
^. Lens' ChunkDB (Map UID (GenDefn, Int))
gendefTable) = forall c. CommonIdea c => c -> String
abrv GenDefn
x
| Just (TheoryModel
x, Int
_) <- forall k a. Ord k => k -> Map k a -> Maybe a
Map.lookup UID
t (ChunkDB
s forall s a. s -> Getting a s a -> a
^. Lens' ChunkDB (Map UID (TheoryModel, Int))
theoryModelTable) = forall c. CommonIdea c => c -> String
abrv TheoryModel
x
| Just (ConceptInstance
x, Int
_) <- forall k a. Ord k => k -> Map k a -> Maybe a
Map.lookup UID
t (ChunkDB
s forall s a. s -> Getting a s a -> a
^. Lens' ChunkDB (Map UID (ConceptInstance, Int))
conceptinsTable) = forall a. a -> Maybe a -> a
fromMaybe String
"" forall a b. (a -> b) -> a -> b
$ forall c. Idea c => c -> Maybe String
getA forall a b. (a -> b) -> a -> b
$ ChunkDB -> UID -> ConceptChunk
defResolve ChunkDB
s forall a b. (a -> b) -> a -> b
$ [UID] -> UID
sDom forall a b. (a -> b) -> a -> b
$ forall c. ConceptDomain c => c -> [UID]
cdom ConceptInstance
x
| Just (Section, Int)
_ <- forall k a. Ord k => k -> Map k a -> Maybe a
Map.lookup UID
t (ChunkDB
s forall s a. s -> Getting a s a -> a
^. Lens' ChunkDB (Map UID (Section, Int))
sectionTable) = forall a. Show a => a -> String
show UID
t
| Just (LabelledContent, Int)
_ <- forall k a. Ord k => k -> Map k a -> Maybe a
Map.lookup UID
t (ChunkDB
s forall s a. s -> Getting a s a -> a
^. Lens' ChunkDB (Map UID (LabelledContent, Int))
labelledcontentTable) = forall a. Show a => a -> String
show UID
t
| UID
t forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` forall a b. (a -> b) -> [a] -> [b]
map (forall s a. s -> Getting a s a -> a
^. forall c. HasUID c => Lens' c UID
uid) (SystemInformation -> BibRef
citeDB SystemInformation
si) = String
""
| Bool
otherwise = forall a. HasCallStack => String -> a
error forall a b. (a -> b) -> a -> b
$ forall a. Show a => a -> String
show UID
t forall a. [a] -> [a] -> [a]
++ String
"Caught."
where s :: ChunkDB
s = SystemInformation -> ChunkDB
_sysinfodb SystemInformation
si
checkUIDRefAdd :: SystemInformation -> UID -> String
checkUIDRefAdd :: SystemInformation -> UID -> String
checkUIDRefAdd SystemInformation
si UID
t
| Just (DataDefinition
x, Int
_) <- forall k a. Ord k => k -> Map k a -> Maybe a
Map.lookup UID
t (ChunkDB
s forall s a. s -> Getting a s a -> a
^. Lens' ChunkDB (Map UID (DataDefinition, Int))
dataDefnTable) = LblType -> String
getAdd forall a b. (a -> b) -> a -> b
$ forall b. HasRefAddress b => b -> LblType
getRefAdd DataDefinition
x
| Just (InstanceModel
x, Int
_) <- forall k a. Ord k => k -> Map k a -> Maybe a
Map.lookup UID
t (ChunkDB
s forall s a. s -> Getting a s a -> a
^. Lens' ChunkDB (Map UID (InstanceModel, Int))
insmodelTable) = LblType -> String
getAdd forall a b. (a -> b) -> a -> b
$ forall b. HasRefAddress b => b -> LblType
getRefAdd InstanceModel
x
| Just (GenDefn
x, Int
_) <- forall k a. Ord k => k -> Map k a -> Maybe a
Map.lookup UID
t (ChunkDB
s forall s a. s -> Getting a s a -> a
^. Lens' ChunkDB (Map UID (GenDefn, Int))
gendefTable) = LblType -> String
getAdd forall a b. (a -> b) -> a -> b
$ forall b. HasRefAddress b => b -> LblType
getRefAdd GenDefn
x
| Just (TheoryModel
x, Int
_) <- forall k a. Ord k => k -> Map k a -> Maybe a
Map.lookup UID
t (ChunkDB
s forall s a. s -> Getting a s a -> a
^. Lens' ChunkDB (Map UID (TheoryModel, Int))
theoryModelTable) = LblType -> String
getAdd forall a b. (a -> b) -> a -> b
$ forall b. HasRefAddress b => b -> LblType
getRefAdd TheoryModel
x
| Just (ConceptInstance
x, Int
_) <- forall k a. Ord k => k -> Map k a -> Maybe a
Map.lookup UID
t (ChunkDB
s forall s a. s -> Getting a s a -> a
^. Lens' ChunkDB (Map UID (ConceptInstance, Int))
conceptinsTable) = forall a. a -> Maybe a -> a
fromMaybe String
"" (forall c. Idea c => c -> Maybe String
getA forall a b. (a -> b) -> a -> b
$ ChunkDB -> UID -> ConceptChunk
defResolve ChunkDB
s forall a b. (a -> b) -> a -> b
$ [UID] -> UID
sDom forall a b. (a -> b) -> a -> b
$ forall c. ConceptDomain c => c -> [UID]
cdom ConceptInstance
x) forall a. [a] -> [a] -> [a]
++ String
":" forall a. [a] -> [a] -> [a]
++ LblType -> String
getAdd (forall b. HasRefAddress b => b -> LblType
getRefAdd ConceptInstance
x)
| Just (Section, Int)
_ <- forall k a. Ord k => k -> Map k a -> Maybe a
Map.lookup UID
t (ChunkDB
s forall s a. s -> Getting a s a -> a
^. Lens' ChunkDB (Map UID (Section, Int))
sectionTable) = forall a. Show a => a -> String
show UID
t
| Just (LabelledContent, Int)
_ <- forall k a. Ord k => k -> Map k a -> Maybe a
Map.lookup UID
t (ChunkDB
s forall s a. s -> Getting a s a -> a
^. Lens' ChunkDB (Map UID (LabelledContent, Int))
labelledcontentTable) = forall a. Show a => a -> String
show UID
t
| UID
t forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` forall a b. (a -> b) -> [a] -> [b]
map (forall s a. s -> Getting a s a -> a
^. forall c. HasUID c => Lens' c UID
uid) (SystemInformation -> BibRef
citeDB SystemInformation
si) = String
""
| Bool
otherwise = forall a. HasCallStack => String -> a
error forall a b. (a -> b) -> a -> b
$ forall a. Show a => a -> String
show UID
t forall a. [a] -> [a] -> [a]
++ String
"Caught."
where s :: ChunkDB
s = SystemInformation -> ChunkDB
_sysinfodb SystemInformation
si
traceGHeader :: (ChunkDB -> [UID]) -> SystemInformation -> [UID]
ChunkDB -> [UID]
f SystemInformation
c = forall a b. (a -> b) -> [a] -> [b]
map (UID -> SystemInformation -> UID
`checkUID` SystemInformation
c) forall a b. (a -> b) -> a -> b
$ ChunkDB -> [UID]
f forall a b. (a -> b) -> a -> b
$ SystemInformation -> ChunkDB
_sysinfodb SystemInformation
c
traceGRowHeader :: ([UID] -> [UID]) -> SystemInformation -> [UID]
[UID] -> [UID]
f = (ChunkDB -> [UID]) -> SystemInformation -> [UID]
traceGHeader (([UID] -> [UID]) -> ChunkDB -> [UID]
traceMReferrers [UID] -> [UID]
f)
graphShows :: UID -> Sentence -> Sentence
graphShows :: UID -> Sentence -> Sentence
graphShows UID
r Sentence
end = forall r.
(HasUID r, HasRefAddress r, HasShortName r) =>
r -> Sentence
refS (UID -> Reference
makeFigRef' UID
r) Sentence -> Sentence -> Sentence
+:+ String -> Sentence
S String
"shows the" Sentence -> Sentence -> Sentence
+:+ forall n. NamedIdea n => n -> Sentence
plural IdeaDict
dependency Sentence -> Sentence -> Sentence
`S.of_` (Sentence
end !.)
allvsallDesc :: Sentence
allvsallDesc :: Sentence
allvsallDesc = String -> Sentence
S String
"dependencies of assumptions, models, definitions, requirements, goals, and changes with each other"
traceGLst :: Contents
traceGLst :: Contents
traceGLst = UnlabelledContent -> Contents
UlC forall a b. (a -> b) -> a -> b
$ RawContent -> UnlabelledContent
ulcc forall a b. (a -> b) -> a -> b
$ ListType -> RawContent
Enumeration forall a b. (a -> b) -> a -> b
$ [(ItemType, Maybe String)] -> ListType
Bullet forall a b. (a -> b) -> a -> b
$ forall a b. (a -> b) -> [a] -> [b]
map (, forall a. Maybe a
Nothing) [ItemType]
folderList'
traceGCon :: String -> [Contents]
traceGCon :: String -> [Contents]
traceGCon String
ex = forall a b. (a -> b) -> [a] -> [b]
map LabelledContent -> Contents
LlC (forall a b c. (a -> b -> c) -> [a] -> [b] -> [c]
zipWith (String -> String -> UID -> LabelledContent
traceGraphLC String
ex) [String]
traceGFiles [UID]
traceGUIDs) forall a. [a] -> [a] -> [a]
++ [Sentence -> Contents
mkParagraph forall a b. (a -> b) -> a -> b
$ String -> Sentence
S String
"For convenience, the following graphs can be found at the links below:", Contents
traceGLst]
traceGraphLC :: String -> FilePath -> UID -> LabelledContent
traceGraphLC :: String -> String -> UID -> LabelledContent
traceGraphLC String
ex String
fp UID
u = Reference -> RawContent -> LabelledContent
llcc (UID -> Reference
makeFigRef' UID
u) forall a b. (a -> b) -> a -> b
$ Sentence -> String -> RawContent
fig (String -> Sentence
S forall a b. (a -> b) -> a -> b
$ forall a. Show a => a -> String
show UID
u) forall a b. (a -> b) -> a -> b
$ String -> String -> String
traceyGraphPath String
ex String
fp
traceGFiles :: [String]
traceGUIDs :: [UID]
traceyGraphPaths :: String -> [String]
traceyGraphGetRefs :: String -> [Reference]
traceyGraphPath :: String -> String -> String
traceGFiles :: [String]
traceGFiles = [String
"avsa", String
"avsall", String
"refvsref", String
"allvsr", String
"allvsall"]
traceGUIDs :: [UID]
traceGUIDs = forall a b. (a -> b) -> [a] -> [b]
map String -> UID
mkUid [String
"TraceGraphAvsA", String
"TraceGraphAvsAll", String
"TraceGraphRefvsRef", String
"TraceGraphAllvsR", String
"TraceGraphAllvsAll"]
traceyGraphPaths :: String -> [String]
traceyGraphPaths String
ex = forall a b. (a -> b) -> [a] -> [b]
map (\String
x -> String
resourcePath forall a. [a] -> [a] -> [a]
++ forall a b. (a -> b) -> [a] -> [b]
map Char -> Char
toLower String
ex forall a. [a] -> [a] -> [a]
++ String
"/" forall a. [a] -> [a] -> [a]
++ String
x forall a. [a] -> [a] -> [a]
++ String
".svg") [String]
traceGFiles
traceyGraphGetRefs :: String -> [Reference]
traceyGraphGetRefs String
ex = forall a b. (a -> b) -> [a] -> [b]
map UID -> Reference
makeFigRef' [UID]
traceGUIDs forall a. [a] -> [a] -> [a]
++ forall a b c. (a -> b -> c) -> [a] -> [b] -> [c]
zipWith (\UID
x String
y -> UID -> LblType -> ShortName -> Reference
Reference (UID
x UID -> String -> UID
+++. String
"Link") (String -> LblType
URI String
y) (Sentence -> ShortName
shortname' forall a b. (a -> b) -> a -> b
$ String -> Sentence
S forall a b. (a -> b) -> a -> b
$ forall a. Show a => a -> String
show UID
x)) [UID]
traceGUIDs (String -> [String]
traceyGraphPaths forall a b. (a -> b) -> a -> b
$ forall a b. (a -> b) -> [a] -> [b]
map Char -> Char
toLower String
ex)
traceyGraphPath :: String -> String -> String
traceyGraphPath String
ex String
f = String
resourcePath forall a. [a] -> [a] -> [a]
++ forall a b. (a -> b) -> [a] -> [b]
map Char -> Char
toLower String
ex forall a. [a] -> [a] -> [a]
++ String
"/" forall a. [a] -> [a] -> [a]
++ String
f forall a. [a] -> [a] -> [a]
++ String
".svg"
resourcePath :: String
resourcePath :: String
resourcePath = String
"../../../../traceygraphs/"
folderList' :: [ItemType]
folderList' :: [ItemType]
folderList' = forall a b. (a -> b) -> [a] -> [b]
map (Sentence -> ItemType
Flat forall b c a. (b -> c) -> (a -> b) -> a -> c
. (\UID
x -> UID -> Sentence -> RefInfo -> Sentence
Ref (UID
x UID -> String -> UID
+++. String
"Link") Sentence
EmptyS RefInfo
None)) [UID]
traceGUIDs