Skip to content

Commit

Permalink
Started using numerical short names in trace tables
Browse files Browse the repository at this point in the history
  • Loading branch information
samm82 committed Jul 19, 2019
1 parent a229c07 commit 0d4efdc
Show file tree
Hide file tree
Showing 4 changed files with 39 additions and 14 deletions.
12 changes: 6 additions & 6 deletions code/drasil-docLang/Drasil/DocumentLanguage/Definitions.hs
Original file line number Diff line number Diff line change
Expand Up @@ -113,12 +113,12 @@ helperRefs t s = foldlList Comma List $ map (`helpToRefField` s) $ nub $ refbyLo

helpToRefField :: UID -> SystemInformation -> Sentence
helpToRefField t si
| t `elem` keys (s ^. dataDefnTable) = makeRef2S $ datadefnLookup t (s ^. dataDefnTable)
| t `elem` keys (s ^. insmodelTable) = makeRef2S $ insmodelLookup t (s ^. insmodelTable)
| t `elem` keys (s ^. gendefTable) = makeRef2S $ gendefLookup t (s ^. gendefTable)
| t `elem` keys (s ^. theoryModelTable) = makeRef2S $ theoryModelLookup t (s ^. theoryModelTable)
| t `elem` keys (s ^. conceptinsTable) = makeRef2S $ conceptinsLookup t (s ^. conceptinsTable)
| t `elem` keys (s ^. sectionTable) = makeRef2S $ sectionLookup t (s ^. sectionTable)
| t `elem` keys (s ^. dataDefnTable) = makeRef2S $ datadefnLookup t (s ^. dataDefnTable)
| t `elem` keys (s ^. insmodelTable) = makeRef2S $ insmodelLookup t (s ^. insmodelTable)
| t `elem` keys (s ^. gendefTable) = makeRef2S $ gendefLookup t (s ^. gendefTable)
| t `elem` keys (s ^. theoryModelTable) = makeRef2S $ theoryModelLookup t (s ^. theoryModelTable)
| t `elem` keys (s ^. conceptinsTable) = makeRef2S $ conceptinsLookup t (s ^. conceptinsTable)
| t `elem` keys (s ^. sectionTable) = makeRef2S $ sectionLookup t (s ^. sectionTable)
| t `elem` keys (s ^. labelledcontentTable) = makeRef2S $ labelledconLookup t (s ^. labelledcontentTable)
| t `elem` map (^. uid) r = EmptyS
| otherwise = error $ t ++ "Caught."
Expand Down
30 changes: 25 additions & 5 deletions code/drasil-docLang/Drasil/DocumentLanguage/TraceabilityMatrix.hs
Original file line number Diff line number Diff line change
@@ -1,19 +1,22 @@
module Drasil.DocumentLanguage.TraceabilityMatrix where

import Language.Drasil
import Database.Drasil(ChunkDB, SystemInformation, refbyTable, conceptinsTable,
_sysinfodb, defTable, defLookup, traceTable, traceLookup, asOrderedList, UMap)
import Database.Drasil (ChunkDB, SystemInformation, UMap, asOrderedList,
citeDB, conceptinsLookup, conceptinsTable, datadefnLookup, dataDefnTable,
defTable, defLookup, gendefLookup, gendefTable, insmodelLookup, insmodelTable,
labelledconLookup, labelledcontentTable, refbyTable,
sectionLookup, sectionTable, theoryModelLookup, theoryModelTable,
traceTable, traceLookup, _sysinfodb)
import Utils.Drasil

import Data.Drasil.Concepts.Documentation (purpose, component, dependency,
item, reference, traceyGraph, traceyMatrix)
import Data.Drasil.Concepts.Math (graph)

import Drasil.DocumentLanguage.Definitions (helpToRefField)
import qualified Drasil.DocLang.SRS as SRS

import Control.Lens ((^.), Getting)
import Data.List (nub)
import Data.List (elemIndex, nub)
import qualified Data.Map as Map

type TraceViewCat = [UID] -> ChunkDB -> [UID]
Expand Down Expand Up @@ -53,7 +56,24 @@ traceMReferrers :: ([UID] -> [UID]) -> ChunkDB -> [UID]
traceMReferrers f = f . nub . concat . Map.elems . (^. refbyTable)

traceMHeader :: (ChunkDB -> [UID]) -> SystemInformation -> [Sentence]
traceMHeader f c = map (`helpToRefField` c) $ f $ _sysinfodb c
traceMHeader f c = map (\x -> helpToShortName x c (x `elemIndex` l)) l
where l = f $ _sysinfodb c

helpToShortName :: UID -> SystemInformation -> Maybe Int -> Sentence
helpToShortName t si (Just i)
| t `elem` Map.keys (s ^. dataDefnTable) = shortRef (datadefnLookup t (s ^. dataDefnTable)) i
| t `elem` Map.keys (s ^. insmodelTable) = makeRef2S $ insmodelLookup t (s ^. insmodelTable)
| t `elem` Map.keys (s ^. gendefTable) = makeRef2S $ gendefLookup t (s ^. gendefTable)
| t `elem` Map.keys (s ^. theoryModelTable) = makeRef2S $ theoryModelLookup t (s ^. theoryModelTable)
| t `elem` Map.keys (s ^. conceptinsTable) = makeRef2S $ conceptinsLookup t (s ^. conceptinsTable)
| t `elem` Map.keys (s ^. sectionTable) = makeRef2S $ sectionLookup t (s ^. sectionTable)
| t `elem` Map.keys (s ^. labelledcontentTable) = makeRef2S $ labelledconLookup t (s ^. labelledcontentTable)
| t `elem` map (^. uid) r = EmptyS
| otherwise = error $ t ++ "Caught."
where
s = _sysinfodb si
r = citeDB si
helpToShortName t _ Nothing = error $ t ++ " not found. (Should never occur.)"

traceMColHeader :: ([UID] -> [UID]) -> SystemInformation -> [Sentence]
traceMColHeader f = traceMHeader (traceMReferees f)
Expand Down
5 changes: 3 additions & 2 deletions code/drasil-lang/Language/Drasil.hs
Original file line number Diff line number Diff line change
Expand Up @@ -137,7 +137,7 @@ module Language.Drasil (
-- Symbol.Helpers
, eqSymb, codeSymb, hasStageSymbol
-- Reference
, makeRef2S, makeCite, makeCiteS, makeRef2, makeCiteInfo, makeCiteInfoS
, makeRef2S, makeCite, makeCiteS, makeRef2, makeCiteInfo, makeCiteInfoS, shortRef
-- Label.Type
, getAdd, prepend
, LblType(RP, Citation, URI), IRefProg(..)
Expand Down Expand Up @@ -258,7 +258,8 @@ import Language.Drasil.Space (Space(..)
import Language.Drasil.Sentence (Sentence(..), sParen, sDash, sC, (+:+), (+:+.), (+:), ch
, SentenceStyle(..))
import Language.Drasil.Sentence.Extract (sdep, shortdep) -- exported for drasil-database FIXME: move to development package?
import Language.Drasil.Reference (makeCite, makeCiteS, makeRef2, makeRef2S, makeCiteInfo, makeCiteInfoS)
import Language.Drasil.Reference (makeCite, makeCiteS, makeRef2, makeRef2S, makeCiteInfo,
makeCiteInfoS, shortRef)
import Language.Drasil.Symbol (Decoration(..), Symbol(..), sub, sup, vec, hat,
prime, compsy, staged)
import Language.Drasil.Symbol.Helpers (eqSymb, codeSymb, hasStageSymbol)
Expand Down
6 changes: 5 additions & 1 deletion code/drasil-lang/Language/Drasil/Reference.hs
Original file line number Diff line number Diff line change
Expand Up @@ -4,9 +4,13 @@ import Control.Lens ((^.))

import Language.Drasil.Chunk.Citation (Citation)
import Language.Drasil.Classes.Core (HasUID(uid), HasShortName(shortname))
import Language.Drasil.Classes (Referable(renderRef))
import Language.Drasil.Classes (CommonIdea(abrv), Referable(renderRef))
import Language.Drasil.RefProg (Reference(..), RefInfo(..))
import Language.Drasil.Sentence (Sentence(Ref))
import Language.Drasil.ShortName (shortname')

shortRef :: (CommonIdea l, Referable l) => l -> Int -> Sentence
shortRef l i = Ref $ Reference (l ^. uid) (renderRef l) (shortname' $ abrv l ++ show (i + 1)) None

This comment has been minimized.

Copy link
@samm82

samm82 Jul 19, 2019

Author Collaborator

I couldn't find a way to get around needing this function, and it still displays a DD in the trace table as "DD: DD2", probably because of renderRef. Would there be a way to define a similar function in docLang that doesn't use prepend through renderRef? @Mornix

This comment has been minimized.

Copy link
@JacquesCarette

JacquesCarette Jul 22, 2019

Owner

You're talking too low-level. What are you really trying to achieve? Why? Give a specific example situation of current output and output you would rather have - and why that's a good thing.

This comment has been minimized.

Copy link
@samm82

samm82 Jul 22, 2019

Author Collaborator

Right now, in the traceability matrix of Projectile, the first DD shows up as "DD: vecMag" (in the master branch). I want it to display as "DD1", but with my change, it displays as "DD: DD1". Currently, I'm focusing on making this change only in the trace tables, but eventually this should be a variability where this shorter name would be used throughout the document.

This comment has been minimized.

Copy link
@JacquesCarette

JacquesCarette Jul 22, 2019

Owner

I think what you're grasping for here is an 'alias' that is local to a document (or even a sub-section). You're trying to go through the Reference machinery, which was never built with that requirement / use case in mind, and so it's unlikely to be able to do it, at least not without horrible hacks.

Again, think higher level. You're still thinking too much in code terms.

This comment has been minimized.

Copy link
@samm82

samm82 Jul 22, 2019

Author Collaborator

I don't know if I understand the underlying code structure well enough to see a better solution, and I can't think of a way to address this problem that isn't code specific. Maybe using a function when generating the trace tables that links to the same location as the normal references do, but that displays the shorter name in the text?

This comment has been minimized.

Copy link
@JacquesCarette

JacquesCarette Jul 22, 2019

Owner

Please open an issue, I can't deal with this right now either.

This comment has been minimized.

Copy link
@samm82

samm82 Jul 22, 2019

Author Collaborator

There already is an issue: #1539 - I'll link to this commit to keep track of this discussion

This comment has been minimized.

Copy link
@samm82

samm82 Aug 6, 2019

Author Collaborator

I figured the prepending issue in 1932020 (ie. it now displays as "DD1" instead of "DD: DD1"). Now onto figuring out a better way to implement it.


makeRef2 :: (Referable l, HasShortName l) => l -> Reference
makeRef2 l = Reference (l ^. uid) (renderRef l) (shortname l) None
Expand Down

0 comments on commit 0d4efdc

Please sign in to comment.