{-# LANGUAGE PostfixOperators #-}
module Drasil.DocumentLanguage.TraceabilityMatrix where
import Language.Drasil
import Database.Drasil hiding (cdb)
import SysInfo.Drasil
import qualified Language.Drasil.Sentence.Combinators as S
import Data.Drasil.Concepts.Documentation (purpose, component, dependency,
item, reference, traceyMatrix)
import Drasil.DocumentLanguage.Definitions (helpToRefField)
import Control.Lens ((^.), Getting)
import Data.List (nub)
import qualified Data.Map as Map
type TraceViewCat = [UID] -> ChunkDB -> [UID]
traceMIntro :: [LabelledContent] -> [Sentence] -> Contents
traceMIntro :: [LabelledContent] -> [Sentence] -> Contents
traceMIntro [LabelledContent]
refs [Sentence]
trailings = UnlabelledContent -> Contents
UlC forall a b. (a -> b) -> a -> b
$ 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
traceyMatrix, String -> Sentence
S String
"is to provide easy", forall n. NamedIdea n => n -> Sentence
plural IdeaDict
reference,
String -> Sentence
S String
"on what has to be additionally modified if a certain",
forall n. NamedIdea n => n -> Sentence
phrase IdeaDict
component, String -> Sentence
S String
"is changed. Every time 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
item, String -> Sentence
S String
"in the column of that",
forall n. NamedIdea n => n -> Sentence
phrase IdeaDict
component, String -> Sentence
S String
"that are marked with an", Sentence -> Sentence
Quote (String -> Sentence
S String
"X"),
String -> Sentence
S String
"should be modified as well"] Sentence -> Sentence -> Sentence
+:+ [Sentence] -> Sentence
foldlSent_ (forall a b c. (a -> b -> c) -> [a] -> [b] -> [c]
zipWith forall a.
(Referable a, HasShortName a) =>
a -> Sentence -> Sentence
tableShows [LabelledContent]
refs [Sentence]
trailings)
generateTraceTableView :: UID -> Sentence -> [TraceViewCat] -> [TraceViewCat] -> SystemInformation -> LabelledContent
generateTraceTableView :: UID
-> Sentence
-> [TraceViewCat]
-> [TraceViewCat]
-> SystemInformation
-> LabelledContent
generateTraceTableView UID
u Sentence
desc [TraceViewCat]
cols [TraceViewCat]
rows SystemInformation
c = Reference -> RawContent -> LabelledContent
llcc (UID -> Reference
makeTabRef' UID
u) forall a b. (a -> b) -> a -> b
$ [Sentence] -> [[Sentence]] -> Sentence -> Bool -> RawContent
Table
(Sentence
EmptyS forall a. a -> [a] -> [a]
: ([UID] -> [UID]) -> SystemInformation -> [Sentence]
traceMColHeader [UID] -> [UID]
colf SystemInformation
c)
(forall a. Eq a => [Sentence] -> [[a]] -> [a] -> [[Sentence]]
makeTMatrix (([UID] -> [UID]) -> SystemInformation -> [Sentence]
traceMRowHeader [UID] -> [UID]
rowf SystemInformation
c) (([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)
(forall c. NamedIdea c => c -> Sentence -> Sentence
showingCxnBw IdeaDict
traceyMatrix Sentence
desc) Bool
True
where
cdb :: ChunkDB
cdb = SystemInformation -> ChunkDB
_sysinfodb SystemInformation
c
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
traceMReferees :: ([UID] -> [UID]) -> ChunkDB -> [UID]
traceMReferees :: ([UID] -> [UID]) -> ChunkDB -> [UID]
traceMReferees [UID] -> [UID]
f = [UID] -> [UID]
f forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Eq a => [a] -> [a]
nub forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall k a. Map k a -> [k]
Map.keys forall b c a. (b -> c) -> (a -> b) -> a -> c
. (forall s a. s -> Getting a s a -> a
^. Lens' ChunkDB (Map UID [UID])
refbyTable)
traceMReferrers :: ([UID] -> [UID]) -> ChunkDB -> [UID]
traceMReferrers :: ([UID] -> [UID]) -> ChunkDB -> [UID]
traceMReferrers [UID] -> [UID]
f = [UID] -> [UID]
f forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Eq a => [a] -> [a]
nub forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall k a. Map k a -> [a]
Map.elems forall b c a. (b -> c) -> (a -> b) -> a -> c
. (forall s a. s -> Getting a s a -> a
^. Lens' ChunkDB (Map UID [UID])
refbyTable)
traceMHeader :: (ChunkDB -> [UID]) -> SystemInformation -> [Sentence]
ChunkDB -> [UID]
f SystemInformation
c = forall a b. (a -> b) -> [a] -> [b]
map (UID -> SystemInformation -> Sentence
`helpToRefField` SystemInformation
c) forall a b. (a -> b) -> a -> b
$ ChunkDB -> [UID]
f forall a b. (a -> b) -> a -> b
$ SystemInformation -> ChunkDB
_sysinfodb SystemInformation
c
traceMColHeader :: ([UID] -> [UID]) -> SystemInformation -> [Sentence]
[UID] -> [UID]
f = (ChunkDB -> [UID]) -> SystemInformation -> [Sentence]
traceMHeader (([UID] -> [UID]) -> ChunkDB -> [UID]
traceMReferees [UID] -> [UID]
f)
traceMRowHeader :: ([UID] -> [UID]) -> SystemInformation -> [Sentence]
[UID] -> [UID]
f = (ChunkDB -> [UID]) -> SystemInformation -> [Sentence]
traceMHeader (([UID] -> [UID]) -> ChunkDB -> [UID]
traceMReferrers [UID] -> [UID]
f)
traceMColumns :: ([UID] -> [UID]) -> ([UID] -> [UID]) -> ChunkDB -> [[UID]]
traceMColumns :: ([UID] -> [UID]) -> ([UID] -> [UID]) -> ChunkDB -> [[UID]]
traceMColumns [UID] -> [UID]
fc [UID] -> [UID]
fr ChunkDB
c = forall a b. (a -> b) -> [a] -> [b]
map ((\[UID]
u -> forall a. (a -> Bool) -> [a] -> [a]
filter (forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` [UID]
u) forall a b. (a -> b) -> a -> b
$ [UID] -> [UID]
fc [UID]
u) forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b c. (a -> b -> c) -> b -> a -> c
flip UID -> Map UID [UID] -> [UID]
traceLookup (ChunkDB
c forall s a. s -> Getting a s a -> a
^. Lens' ChunkDB (Map UID [UID])
traceTable)) forall a b. (a -> b) -> a -> b
$ ([UID] -> [UID]) -> ChunkDB -> [UID]
traceMReferrers [UID] -> [UID]
fr ChunkDB
c
tableShows :: (Referable a, HasShortName a) => a -> Sentence -> Sentence
tableShows :: forall a.
(Referable a, HasShortName a) =>
a -> Sentence -> Sentence
tableShows a
r Sentence
end = forall r.
(HasUID r, HasRefAddress r, HasShortName r) =>
r -> Sentence
refS a
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.ofThe` (Sentence
end !.)
layoutUIDs :: [TraceViewCat] -> ChunkDB -> [UID] -> [UID]
layoutUIDs :: [TraceViewCat] -> ChunkDB -> [UID] -> [UID]
layoutUIDs [TraceViewCat]
a ChunkDB
c [UID]
e = forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
concatMap (forall a. (a -> Bool) -> [a] -> [a]
filter (forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` (forall k a. Map k a -> [k]
Map.keys forall a b. (a -> b) -> a -> b
$ ChunkDB
c forall s a. s -> Getting a s a -> a
^. Lens' ChunkDB (Map UID [UID])
traceTable)) forall b c a. (b -> c) -> (a -> b) -> a -> c
. (\ TraceViewCat
x -> TraceViewCat
x [UID]
e ChunkDB
c)) [TraceViewCat]
a
traceViewFilt :: HasUID a => (a -> Bool) -> Getting (UMap a) ChunkDB (UMap a) -> TraceViewCat
traceViewFilt :: forall a.
HasUID a =>
(a -> Bool) -> Getting (UMap a) ChunkDB (UMap a) -> TraceViewCat
traceViewFilt a -> Bool
f Getting (UMap a) ChunkDB (UMap a)
table [UID]
_ = 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) forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. (a -> Bool) -> [a] -> [a]
filter a -> Bool
f forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. UMap a -> [a]
asOrderedList forall b c a. (b -> c) -> (a -> b) -> a -> c
. (forall s a. s -> Getting a s a -> a
^. Getting (UMap a) ChunkDB (UMap a)
table)
traceView :: HasUID a => Getting (UMap a) ChunkDB (UMap a) -> TraceViewCat
traceView :: forall a.
HasUID a =>
Getting (UMap a) ChunkDB (UMap a) -> TraceViewCat
traceView = forall a.
HasUID a =>
(a -> Bool) -> Getting (UMap a) ChunkDB (UMap a) -> TraceViewCat
traceViewFilt (forall a b. a -> b -> a
const Bool
True)
traceViewCC :: Concept c => c -> TraceViewCat
traceViewCC :: forall c. Concept c => c -> TraceViewCat
traceViewCC c
dom [UID]
u ChunkDB
c = forall a.
HasUID a =>
(a -> Bool) -> Getting (UMap a) ChunkDB (UMap a) -> TraceViewCat
traceViewFilt (UID -> UID -> Bool
isDomUnder (c
dom forall s a. s -> Getting a s a -> a
^. forall c. HasUID c => Lens' c UID
uid) forall b c a. (b -> c) -> (a -> b) -> a -> c
. [UID] -> UID
sDom forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall c. ConceptDomain c => c -> [UID]
cdom) Lens' ChunkDB (UMap ConceptInstance)
conceptinsTable [UID]
u ChunkDB
c
where
isDomUnder :: UID -> UID -> Bool
isDomUnder :: UID -> UID -> Bool
isDomUnder UID
filtDom UID
curr
| UID
filtDom forall a. Eq a => a -> a -> Bool
== UID
curr = Bool
True
| Bool -> Bool
not forall a b. (a -> b) -> a -> b
$ forall (t :: * -> *) a. Foldable t => t a -> Bool
null forall a b. (a -> b) -> a -> b
$ UID -> [UID]
getDom UID
curr = UID -> UID -> Bool
isDomUnder UID
filtDom ([UID] -> UID
sDom forall a b. (a -> b) -> a -> b
$ UID -> [UID]
getDom UID
curr)
| Bool
otherwise = Bool
False
getDom :: UID -> [UID]
getDom :: UID -> [UID]
getDom UID
curr = forall c. ConceptDomain c => c -> [UID]
cdom forall a b. (a -> b) -> a -> b
$ ChunkDB -> UID -> ConceptChunk
defResolve ChunkDB
c UID
curr