{-# LANGUAGE TemplateHaskell #-}
-- | Defines types and functions to create a chunk database within Drasil.

-- Changes to ChunkDB should be reflected in the 'Creating Your Project 
-- in Drasil' tutorial found on the wiki:
-- https://github.com/JacquesCarette/Drasil/wiki/Creating-Your-Project-in-Drasil
module Database.Drasil.ChunkDB (
  -- * Types
  -- ** 'ChunkDB'
  -- | Main database type
  ChunkDB(CDB, symbolTable, termTable, defTable),
  -- ** Maps
  -- | Exported for external use.
  RefbyMap, TraceMap, UMap,
  -- * Functions
  -- ** Constructors
  cdb, idMap, termMap, conceptMap, traceMap, generateRefbyMap, -- idMap, termMap for docLang
  -- ** Lookup Functions
  asOrderedList, collectUnits,
  termResolve, defResolve, symbResolve,
  traceLookup, refbyLookup,
  datadefnLookup, insmodelLookup, gendefLookup, theoryModelLookup,
  conceptinsLookup, sectionLookup, labelledconLookup, refResolve,
  -- ** Lenses
  unitTable, traceTable, refbyTable,
  dataDefnTable, insmodelTable, gendefTable, theoryModelTable,
  conceptinsTable, sectionTable, labelledcontentTable, refTable
) where

import Language.Drasil
import Theory.Drasil (DataDefinition, GenDefn, InstanceModel, TheoryModel)

import Control.Lens ((^.), makeLenses)
import Data.List (sortOn)
import Data.Maybe (fromMaybe, mapMaybe)
import qualified Data.Map as Map
import Utils.Drasil (invert)

-- | The misnomers below (for the following Map types) are not actually a bad thing. We want to ensure data can't
-- be added to a map if it's not coming from a chunk, and there's no point confusing
-- what the map is for. One is for symbols + their units, and the others are for
-- what they state.
type UMap a = Map.Map UID (a, Int)

-- | A bit of a misnomer as it's really a map of all quantities, for retrieving
-- symbols and their units.
type SymbolMap  = UMap QuantityDict

-- | A map of all concepts, normally used for retrieving definitions.
type ConceptMap = UMap ConceptChunk

-- | A map of all the units used. Should be restricted to base units/synonyms.
type UnitMap = UMap UnitDefn

-- | Again a bit of a misnomer as it's really a map of all 'NamedIdea's.
-- Until these are built through automated means, there will
-- likely be some 'manual' duplication of terms as this map will contain all
-- quantities, concepts, etc.
type TermMap = UMap IdeaDict
-- | A traceability map, used to hold the relation between one 'UID' and a list of other 'UID's.
type TraceMap = Map.Map UID [UID]
-- | A reference map, used to hold a 'UID' and where it is referenced ('UID's).
type RefbyMap = Map.Map UID [UID]
-- | Data definitions map. Contains all data definitions ('DataDefinition').
type DatadefnMap = UMap DataDefinition
-- | Instance model map. Contains all instance models ('InstanceModel').
type InsModelMap = UMap InstanceModel
-- | General definitions map. Contains all general definitions ('GenDefn').
type GendefMap = UMap GenDefn
-- | Theory model map. Contains all theoretical models ('TheoryModel').
type TheoryModelMap = UMap TheoryModel
-- | Concept instance map. May hold similar information to a 'ConceptMap', but may also be referred to.
type ConceptInstanceMap = UMap ConceptInstance
-- | A map of all the different 'Section's.
type SectionMap = UMap Section
-- | A map of all 'LabelledContent's.
type LabelledContentMap = UMap LabelledContent
-- | A map of all 'Reference's.
type ReferenceMap = UMap Reference

-- | General chunk database map constructor. Creates a 'UMap' from a function that converts something with 'UID's into another type and a list of something with 'UID's.
cdbMap :: HasUID a => (a -> b) -> [a] -> Map.Map UID (b, Int)
cdbMap :: forall a b. HasUID a => (a -> b) -> [a] -> Map UID (b, Int)
cdbMap a -> b
fn = [(UID, (b, Int))] -> Map UID (b, Int)
forall k a. Ord k => [(k, a)] -> Map k a
Map.fromList ([(UID, (b, Int))] -> Map UID (b, Int))
-> ([a] -> [(UID, (b, Int))]) -> [a] -> Map UID (b, Int)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((a, Int) -> (UID, (b, Int))) -> [(a, Int)] -> [(UID, (b, Int))]
forall a b. (a -> b) -> [a] -> [b]
map (\(a
x,Int
y) -> (a
x a -> Getting UID a UID -> UID
forall s a. s -> Getting a s a -> a
^. Getting UID a UID
forall c. HasUID c => Getter c UID
Getter a UID
uid, (a -> b
fn a
x, Int
y))) ([(a, Int)] -> [(UID, (b, Int))])
-> ([a] -> [(a, Int)]) -> [a] -> [(UID, (b, Int))]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ([a] -> [Int] -> [(a, Int)]) -> [Int] -> [a] -> [(a, Int)]
forall a b c. (a -> b -> c) -> b -> a -> c
flip [a] -> [Int] -> [(a, Int)]
forall a b. [a] -> [b] -> [(a, b)]
zip [Int
1..]

-- | Smart constructor for a 'SymbolMap'.
symbolMap :: (Quantity c, MayHaveUnit c) => [c] -> SymbolMap
symbolMap :: forall c. (Quantity c, MayHaveUnit c) => [c] -> SymbolMap
symbolMap = (c -> QuantityDict) -> [c] -> SymbolMap
forall a b. HasUID a => (a -> b) -> [a] -> Map UID (b, Int)
cdbMap c -> QuantityDict
forall q. (Quantity q, MayHaveUnit q) => q -> QuantityDict
qw

-- | Smart constructor for a 'TermMap'.
termMap :: (Idea c) => [c] -> TermMap
termMap :: forall c. Idea c => [c] -> TermMap
termMap = (c -> IdeaDict) -> [c] -> TermMap
forall a b. HasUID a => (a -> b) -> [a] -> Map UID (b, Int)
cdbMap c -> IdeaDict
forall c. Idea c => c -> IdeaDict
nw

-- | Smart constructor for a 'ConceptMap'.
conceptMap :: (Concept c) => [c] -> ConceptMap
conceptMap :: forall c. Concept c => [c] -> ConceptMap
conceptMap = (c -> ConceptChunk) -> [c] -> ConceptMap
forall a b. HasUID a => (a -> b) -> [a] -> Map UID (b, Int)
cdbMap c -> ConceptChunk
forall c. Concept c => c -> ConceptChunk
cw

-- | Smart constructor for a 'UnitMap'.
unitMap :: (IsUnit u) => [u] -> UnitMap
unitMap :: forall u. IsUnit u => [u] -> UnitMap
unitMap = (u -> UnitDefn) -> [u] -> UnitMap
forall a b. HasUID a => (a -> b) -> [a] -> Map UID (b, Int)
cdbMap u -> UnitDefn
forall u. IsUnit u => u -> UnitDefn
unitWrapper

-- | General smart constructor for making a 'UMap' out of anything that has a 'UID'. 
idMap :: HasUID a => [a] -> Map.Map UID (a, Int)
idMap :: forall a. HasUID a => [a] -> Map UID (a, Int)
idMap = (a -> a) -> [a] -> Map UID (a, Int)
forall a b. HasUID a => (a -> b) -> [a] -> Map UID (b, Int)
cdbMap a -> a
forall a. a -> a
id

-- | Smart constructor for a 'TraceMap' given a traceability matrix.
traceMap :: [(UID, [UID])] -> TraceMap
traceMap :: [(UID, [UID])] -> TraceMap
traceMap = [(UID, [UID])] -> TraceMap
forall k a. Ord k => [(k, a)] -> Map k a
Map.fromList

-- | Gets a unit if it exists, or Nothing.        
getUnitLup :: HasUID c => ChunkDB -> c -> Maybe UnitDefn
getUnitLup :: forall c. HasUID c => ChunkDB -> c -> Maybe UnitDefn
getUnitLup ChunkDB
m c
c = QuantityDict -> Maybe UnitDefn
forall u. MayHaveUnit u => u -> Maybe UnitDefn
getUnit (QuantityDict -> Maybe UnitDefn) -> QuantityDict -> Maybe UnitDefn
forall a b. (a -> b) -> a -> b
$ ChunkDB -> UID -> QuantityDict
symbResolve ChunkDB
m (c
c c -> Getting UID c UID -> UID
forall s a. s -> Getting a s a -> a
^. Getting UID c UID
forall c. HasUID c => Getter c UID
Getter c UID
uid)

-- | Looks up a 'UID' in a 'UMap' table. If nothing is found, an error is thrown.
uMapLookup :: String -> String -> UID -> UMap a -> a
uMapLookup :: forall a. String -> String -> UID -> UMap a -> a
uMapLookup String
tys String
ms UID
u UMap a
t = Maybe (a, Int) -> a
forall {b} {b}. Maybe (b, b) -> b
getFM (Maybe (a, Int) -> a) -> Maybe (a, Int) -> a
forall a b. (a -> b) -> a -> b
$ UID -> UMap a -> Maybe (a, Int)
forall k a. Ord k => k -> Map k a -> Maybe a
Map.lookup UID
u UMap a
t
  where getFM :: Maybe (b, b) -> b
getFM = b -> ((b, b) -> b) -> Maybe (b, b) -> b
forall b a. b -> (a -> b) -> Maybe a -> b
maybe (String -> b
forall a. HasCallStack => String -> a
error (String -> b) -> String -> b
forall a b. (a -> b) -> a -> b
$ String
tys String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
": " String -> String -> String
forall a. [a] -> [a] -> [a]
++ UID -> String
forall a. Show a => a -> String
show UID
u String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
" not found in " String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
ms) (b, b) -> b
forall a b. (a, b) -> a
fst

-- | Looks up a 'UID' in the symbol table from the 'ChunkDB'. If nothing is found, an error is thrown.
symbResolve :: ChunkDB -> UID -> QuantityDict
symbResolve :: ChunkDB -> UID -> QuantityDict
symbResolve ChunkDB
m UID
x = String -> String -> UID -> SymbolMap -> QuantityDict
forall a. String -> String -> UID -> UMap a -> a
uMapLookup String
"Symbol" String
"SymbolMap" UID
x (SymbolMap -> QuantityDict) -> SymbolMap -> QuantityDict
forall a b. (a -> b) -> a -> b
$ ChunkDB -> SymbolMap
symbolTable ChunkDB
m

-- | Looks up a 'UID' in the term table from the 'ChunkDB'. If nothing is found, an error is thrown.
termResolve :: ChunkDB -> UID -> IdeaDict
termResolve :: ChunkDB -> UID -> IdeaDict
termResolve ChunkDB
m UID
x = String -> String -> UID -> TermMap -> IdeaDict
forall a. String -> String -> UID -> UMap a -> a
uMapLookup String
"Term" String
"TermMap" UID
x (TermMap -> IdeaDict) -> TermMap -> IdeaDict
forall a b. (a -> b) -> a -> b
$ ChunkDB -> TermMap
termTable ChunkDB
m

-- | Looks up a 'UID' in the reference table from the 'ChunkDB'. If nothing is found, an error is thrown.
refResolve :: UID -> ReferenceMap -> Reference
refResolve :: UID -> ReferenceMap -> Reference
refResolve = String -> String -> UID -> ReferenceMap -> Reference
forall a. String -> String -> UID -> UMap a -> a
uMapLookup String
"Reference" String
"ReferenceMap"

-- | Looks up a 'UID' in the unit table. If nothing is found, an error is thrown.
unitLookup :: UID -> UnitMap -> UnitDefn
unitLookup :: UID -> UnitMap -> UnitDefn
unitLookup = String -> String -> UID -> UnitMap -> UnitDefn
forall a. String -> String -> UID -> UMap a -> a
uMapLookup String
"Unit" String
"UnitMap"

-- | Looks up a 'UID' in the definition table from the 'ChunkDB'. If nothing is found, an error is thrown.
defResolve :: ChunkDB -> UID -> ConceptChunk
defResolve :: ChunkDB -> UID -> ConceptChunk
defResolve ChunkDB
m UID
x = String -> String -> UID -> ConceptMap -> ConceptChunk
forall a. String -> String -> UID -> UMap a -> a
uMapLookup String
"Concept" String
"ConceptMap" UID
x (ConceptMap -> ConceptChunk) -> ConceptMap -> ConceptChunk
forall a b. (a -> b) -> a -> b
$ ChunkDB -> ConceptMap
defTable ChunkDB
m

-- | Looks up a 'UID' in the datadefinition table. If nothing is found, an error is thrown.
datadefnLookup :: UID -> DatadefnMap -> DataDefinition
datadefnLookup :: UID -> DatadefnMap -> DataDefinition
datadefnLookup = String -> String -> UID -> DatadefnMap -> DataDefinition
forall a. String -> String -> UID -> UMap a -> a
uMapLookup String
"DataDefinition" String
"DatadefnMap"

-- | Looks up a 'UID' in the instance model table. If nothing is found, an error is thrown.
insmodelLookup :: UID -> InsModelMap -> InstanceModel
insmodelLookup :: UID -> InsModelMap -> InstanceModel
insmodelLookup = String -> String -> UID -> InsModelMap -> InstanceModel
forall a. String -> String -> UID -> UMap a -> a
uMapLookup String
"InstanceModel" String
"InsModelMap"

-- | Looks up a 'UID' in the general definition table. If nothing is found, an error is thrown.
gendefLookup :: UID -> GendefMap -> GenDefn
gendefLookup :: UID -> GendefMap -> GenDefn
gendefLookup = String -> String -> UID -> GendefMap -> GenDefn
forall a. String -> String -> UID -> UMap a -> a
uMapLookup String
"GenDefn" String
"GenDefnMap" 

-- | Looks up a 'UID' in the theory model table. If nothing is found, an error is thrown.
theoryModelLookup :: UID -> TheoryModelMap -> TheoryModel
theoryModelLookup :: UID -> TheoryModelMap -> TheoryModel
theoryModelLookup = String -> String -> UID -> TheoryModelMap -> TheoryModel
forall a. String -> String -> UID -> UMap a -> a
uMapLookup String
"TheoryModel" String
"TheoryModelMap"

-- | Looks up a 'UID' in the concept instance table. If nothing is found, an error is thrown.
conceptinsLookup :: UID -> ConceptInstanceMap -> ConceptInstance
conceptinsLookup :: UID -> ConceptInstanceMap -> ConceptInstance
conceptinsLookup = String -> String -> UID -> ConceptInstanceMap -> ConceptInstance
forall a. String -> String -> UID -> UMap a -> a
uMapLookup String
"ConceptInstance" String
"ConceptInstanceMap"

-- | Looks up a 'UID' in the section table. If nothing is found, an error is thrown.
sectionLookup :: UID -> SectionMap -> Section
sectionLookup :: UID -> SectionMap -> Section
sectionLookup = String -> String -> UID -> SectionMap -> Section
forall a. String -> String -> UID -> UMap a -> a
uMapLookup String
"Section" String
"SectionMap"

-- | Looks up a 'UID' in the labelled content table. If nothing is found, an error is thrown.
labelledconLookup :: UID -> LabelledContentMap -> LabelledContent
labelledconLookup :: UID -> LabelledContentMap -> LabelledContent
labelledconLookup = String -> String -> UID -> LabelledContentMap -> LabelledContent
forall a. String -> String -> UID -> UMap a -> a
uMapLookup String
"LabelledContent" String
"LabelledContentMap"

-- | Gets an ordered list of @a@ from any @a@ that is of type 'UMap'.
asOrderedList :: UMap a -> [a]
asOrderedList :: forall a. UMap a -> [a]
asOrderedList = ((a, Int) -> a) -> [(a, Int)] -> [a]
forall a b. (a -> b) -> [a] -> [b]
map (a, Int) -> a
forall a b. (a, b) -> a
fst ([(a, Int)] -> [a]) -> (UMap a -> [(a, Int)]) -> UMap a -> [a]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((a, Int) -> Int) -> [(a, Int)] -> [(a, Int)]
forall b a. Ord b => (a -> b) -> [a] -> [a]
sortOn (a, Int) -> Int
forall a b. (a, b) -> b
snd ([(a, Int)] -> [(a, Int)])
-> (UMap a -> [(a, Int)]) -> UMap a -> [(a, Int)]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((UID, (a, Int)) -> (a, Int)) -> [(UID, (a, Int))] -> [(a, Int)]
forall a b. (a -> b) -> [a] -> [b]
map (UID, (a, Int)) -> (a, Int)
forall a b. (a, b) -> b
snd ([(UID, (a, Int))] -> [(a, Int)])
-> (UMap a -> [(UID, (a, Int))]) -> UMap a -> [(a, Int)]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. UMap a -> [(UID, (a, Int))]
forall k a. Map k a -> [(k, a)]
Map.toList

-- | Our chunk databases. \Must contain all maps needed in an example.\
-- In turn, these maps must contain every chunk definition or concept 
-- used in its respective example, else an error is thrown.
data ChunkDB = CDB { ChunkDB -> SymbolMap
symbolTable           :: SymbolMap
                   , ChunkDB -> TermMap
termTable             :: TermMap 
                   , ChunkDB -> ConceptMap
defTable              :: ConceptMap
                   , ChunkDB -> UnitMap
_unitTable            :: UnitMap
                   , ChunkDB -> TraceMap
_traceTable           :: TraceMap
                   , ChunkDB -> TraceMap
_refbyTable           :: RefbyMap
                   , ChunkDB -> DatadefnMap
_dataDefnTable        :: DatadefnMap
                   , ChunkDB -> InsModelMap
_insmodelTable        :: InsModelMap
                   , ChunkDB -> GendefMap
_gendefTable          :: GendefMap
                   , ChunkDB -> TheoryModelMap
_theoryModelTable     :: TheoryModelMap
                   , ChunkDB -> ConceptInstanceMap
_conceptinsTable      :: ConceptInstanceMap
                   , ChunkDB -> SectionMap
_sectionTable         :: SectionMap
                   , ChunkDB -> LabelledContentMap
_labelledcontentTable :: LabelledContentMap
                   , ChunkDB -> ReferenceMap
_refTable             :: ReferenceMap
                   } -- TODO: Expand and add more databases
makeLenses ''ChunkDB

-- | Smart constructor for chunk databases. Takes in the following:
--
--     * ['Quantity'] (for 'SymbolMap'), 
--     * 'NamedIdea's (for 'TermMap'),
--     * 'Concept's (for 'ConceptMap'),
--     * Units (something that 'IsUnit' for 'UnitMap'),
--     * 'DataDefinition's (for 'DatadefnMap'),
--     * 'InstanceModel's (for 'InsModelMap'),
--     * 'GenDefn's (for 'GendefMap'),
--     * 'TheoryModel's (for 'TheoryModelMap'),
--     * 'ConceptInstance's (for 'ConceptInstanceMap'),
--     * 'Section's (for 'SectionMap'),
--     * 'LabelledContent's (for 'LabelledContentMap').
cdb :: (Quantity q, MayHaveUnit q, Idea t, Concept c, IsUnit u) =>
    [q] -> [t] -> [c] -> [u] -> [DataDefinition] -> [InstanceModel] ->
    [GenDefn] -> [TheoryModel] -> [ConceptInstance] -> [Section] ->
    [LabelledContent] -> [Reference] -> ChunkDB
cdb :: forall q t c u.
(Quantity q, MayHaveUnit q, Idea t, Concept c, IsUnit u) =>
[q]
-> [t]
-> [c]
-> [u]
-> [DataDefinition]
-> [InstanceModel]
-> [GenDefn]
-> [TheoryModel]
-> [ConceptInstance]
-> [Section]
-> [LabelledContent]
-> [Reference]
-> ChunkDB
cdb [q]
s [t]
t [c]
c [u]
u [DataDefinition]
d [InstanceModel]
ins [GenDefn]
gd [TheoryModel]
tm [ConceptInstance]
ci [Section]
sect [LabelledContent]
lc [Reference]
r = SymbolMap
-> TermMap
-> ConceptMap
-> UnitMap
-> TraceMap
-> TraceMap
-> DatadefnMap
-> InsModelMap
-> GendefMap
-> TheoryModelMap
-> ConceptInstanceMap
-> SectionMap
-> LabelledContentMap
-> ReferenceMap
-> ChunkDB
CDB ([q] -> SymbolMap
forall c. (Quantity c, MayHaveUnit c) => [c] -> SymbolMap
symbolMap [q]
s) ([t] -> TermMap
forall c. Idea c => [c] -> TermMap
termMap [t]
t) ([c] -> ConceptMap
forall c. Concept c => [c] -> ConceptMap
conceptMap [c]
c)
  ([u] -> UnitMap
forall u. IsUnit u => [u] -> UnitMap
unitMap [u]
u) TraceMap
forall k a. Map k a
Map.empty TraceMap
forall k a. Map k a
Map.empty ([DataDefinition] -> DatadefnMap
forall a. HasUID a => [a] -> Map UID (a, Int)
idMap [DataDefinition]
d) ([InstanceModel] -> InsModelMap
forall a. HasUID a => [a] -> Map UID (a, Int)
idMap [InstanceModel]
ins) ([GenDefn] -> GendefMap
forall a. HasUID a => [a] -> Map UID (a, Int)
idMap [GenDefn]
gd) ([TheoryModel] -> TheoryModelMap
forall a. HasUID a => [a] -> Map UID (a, Int)
idMap [TheoryModel]
tm)
  ([ConceptInstance] -> ConceptInstanceMap
forall a. HasUID a => [a] -> Map UID (a, Int)
idMap [ConceptInstance]
ci) ([Section] -> SectionMap
forall a. HasUID a => [a] -> Map UID (a, Int)
idMap [Section]
sect) ([LabelledContent] -> LabelledContentMap
forall a. HasUID a => [a] -> Map UID (a, Int)
idMap [LabelledContent]
lc) ([Reference] -> ReferenceMap
forall a. HasUID a => [a] -> Map UID (a, Int)
idMap [Reference]
r)

-- | Gets the units of a 'Quantity' as 'UnitDefn's.
collectUnits :: Quantity c => ChunkDB -> [c] -> [UnitDefn]
collectUnits :: forall c. Quantity c => ChunkDB -> [c] -> [UnitDefn]
collectUnits ChunkDB
m = (UID -> UnitDefn) -> [UID] -> [UnitDefn]
forall a b. (a -> b) -> [a] -> [b]
map (UnitDefn -> UnitDefn
forall u. IsUnit u => u -> UnitDefn
unitWrapper (UnitDefn -> UnitDefn) -> (UID -> UnitDefn) -> UID -> UnitDefn
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (UID -> UnitMap -> UnitDefn) -> UnitMap -> UID -> UnitDefn
forall a b c. (a -> b -> c) -> b -> a -> c
flip UID -> UnitMap -> UnitDefn
unitLookup (ChunkDB
m ChunkDB -> Getting UnitMap ChunkDB UnitMap -> UnitMap
forall s a. s -> Getting a s a -> a
^. Getting UnitMap ChunkDB UnitMap
Lens' ChunkDB UnitMap
unitTable))
 ([UID] -> [UnitDefn]) -> ([c] -> [UID]) -> [c] -> [UnitDefn]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (UnitDefn -> [UID]) -> [UnitDefn] -> [UID]
forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
concatMap UnitDefn -> [UID]
forall u. IsUnit u => u -> [UID]
getUnits ([UnitDefn] -> [UID]) -> ([c] -> [UnitDefn]) -> [c] -> [UID]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (c -> Maybe UnitDefn) -> [c] -> [UnitDefn]
forall a b. (a -> Maybe b) -> [a] -> [b]
mapMaybe (ChunkDB -> c -> Maybe UnitDefn
forall c. HasUID c => ChunkDB -> c -> Maybe UnitDefn
getUnitLup ChunkDB
m)

-- | Trace a 'UID' to related 'UID's.
traceLookup :: UID -> TraceMap -> [UID]
traceLookup :: UID -> TraceMap -> [UID]
traceLookup UID
c = [UID] -> Maybe [UID] -> [UID]
forall a. a -> Maybe a -> a
fromMaybe [] (Maybe [UID] -> [UID])
-> (TraceMap -> Maybe [UID]) -> TraceMap -> [UID]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. UID -> TraceMap -> Maybe [UID]
forall k a. Ord k => k -> Map k a -> Maybe a
Map.lookup UID
c

-- | Translates a traceability map into a reference map.
generateRefbyMap :: TraceMap -> RefbyMap
generateRefbyMap :: TraceMap -> TraceMap
generateRefbyMap = TraceMap -> TraceMap
forall v k. Ord v => Map k [v] -> Map v [k]
invert

-- | Trace a 'UID' to referenced 'UID's.
refbyLookup :: UID -> RefbyMap -> [UID]
refbyLookup :: UID -> TraceMap -> [UID]
refbyLookup UID
c = [UID] -> Maybe [UID] -> [UID]
forall a. a -> Maybe a -> a
fromMaybe [] (Maybe [UID] -> [UID])
-> (TraceMap -> Maybe [UID]) -> TraceMap -> [UID]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. UID -> TraceMap -> Maybe [UID]
forall k a. Ord k => k -> Map k a -> Maybe a
Map.lookup UID
c