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