Skip to content

Commit

Permalink
cleaned up implementation of mkRawLC by creating setLabel function; i…
Browse files Browse the repository at this point in the history
…mplemented a function's use from makeRef; removes discrepancies occurring from underscores that were not being replaced with periods upon makeRef use
  • Loading branch information
niazim3 committed Aug 2, 2018
1 parent edeea14 commit 1ca3090
Show file tree
Hide file tree
Showing 4 changed files with 52 additions and 40 deletions.
2 changes: 1 addition & 1 deletion code/drasil-code/Language/Drasil/CodeSpec.hs
Original file line number Diff line number Diff line change
Expand Up @@ -80,7 +80,7 @@ codeSpec (SI {_sys = sys
let inputs' = map codevar ins
const' = map qtov constants
derived = map qtov $ getDerivedInputs ddefs defs' inputs' const' db
rels = (map qtoc (defs'++(map qdFromDD ddefs))) \\ derived
rels = (map qtoc ({-defs'++-}(map qdFromDD ddefs))) \\ derived
mods' = prefixFunctions $ (packmod "Calculations" $ map FCD rels):ms
mem = modExportMap mods' inputs' const'
outs' = map codevar outs
Expand Down
6 changes: 3 additions & 3 deletions code/drasil-example/Drasil/GlassBR/Assumptions.hs
Original file line number Diff line number Diff line change
Expand Up @@ -21,13 +21,13 @@ import Drasil.GlassBR.References (gbCitations, astm2009)
gbRefDB :: ReferenceDB
gbRefDB = rdb [] [] newAssumptions [] [] gbCitations []

newAssumptions :: [AssumpChunk] -- For testing
newAssumptions = [newA1, newA2, newA3, newA4, newA5, newA6, newA7, newA8]

assumptionConstants :: [QDefinition]
assumptionConstants = [constant_M, constant_K, constant_ModElas,
constant_LoadDur, constant_LoadSF]

newAssumptions :: [AssumpChunk] -- For testing
newAssumptions = [newA1, newA2, newA3, newA4, newA5, newA6, newA7, newA8]

newA1, newA2, newA3, newA4, newA5, newA6, newA7, newA8 :: AssumpChunk
newA1 = assump "glassTyA" a1Desc (mkLabelRA'' "glassTy")
newA2 = assump "glassConditionA" a2Desc (mkLabelRA'' "glassCondition" )
Expand Down
56 changes: 26 additions & 30 deletions code/drasil-lang/Language/Drasil/Document.hs
Original file line number Diff line number Diff line change
Expand Up @@ -10,7 +10,7 @@ import Language.Drasil.Chunk.Change (Change(..), ChngType(..))
import Language.Drasil.Chunk.Eq (QDefinition)
import Language.Drasil.Chunk.Relation (RelationConcept)
import Language.Drasil.Chunk.ReqChunk (ReqChunk(..), ReqType(..))
import Language.Drasil.Chunk.ShortName (HasShortName(shortname), getStringSN)
import Language.Drasil.Chunk.ShortName (HasShortName(shortname), getStringSN, ShortName)
import Language.Drasil.Classes (HasUID(uid), HasRefAddress(getRefAdd),
MayHaveLabel(getMaybeLabel), HasLabel(getLabel))

Expand Down Expand Up @@ -97,38 +97,34 @@ mkDefinitionLC labelUID refAdd sn dfn = llcc (mkLabelRA labelUID refAdd sn) dfn
-- FIXME: no pattern for Bib BibRef of RawContent
-- FIXME: improve design so there's no need for wild card labels?
mkRawLC :: RawContent -> Label -> LabelledContent
mkRawLC x@(Table _ _ _ _) lb = llcc (mkLabelRA' ("Table:" ++ (getAdd (lb ^. getRefAdd)))
(getStringSN (lb ^. shortname))) x
mkRawLC x@(Paragraph _) lb = llcc (mkLabelRA' ("Paragraph:" ++ (getAdd (lb ^. getRefAdd)))
(getStringSN (lb ^. shortname))) x
mkRawLC x@(Definition d) lb = llcc
(mkLabelRA' ((getDefName d) ++ concatMap repUnd (getAdd (lb ^. getRefAdd)))
(concatMap repUnd (getStringSN (lb ^. shortname)))) x
mkRawLC x@(Enumeration _) lb = llcc (mkLabelRA' ("List:" ++ (getAdd (lb ^. getRefAdd)))
(getStringSN (lb ^. shortname))) x
mkRawLC x@(Figure _ _ _) lb = llcc (mkLabelRA' ("Figure:" ++ (getAdd (lb ^. getRefAdd)))
(getStringSN (lb ^. shortname))) x
mkRawLC x@(Requirement (RC _ FR _ _)) lb = llcc (mkLabelRA' ("FR:" ++ (getAdd (lb ^. getRefAdd)))
(getStringSN (lb ^. shortname))) x
mkRawLC x@(Requirement (RC _ NFR _ _)) lb = llcc (mkLabelRA' ("NFR:" ++ (getAdd (lb ^. getRefAdd)))
(getStringSN (lb ^. shortname))) x
mkRawLC x@(Assumption ac) lb = llcc (mkLabelRA' ("A:" ++ (getAdd (lb ^. getRefAdd)))
(getStringSN (ac ^. shortname))) x
mkRawLC x@(Change (ChC _ Likely _ lb)) _ = llcc (mkLabelRA'
("LC:" ++ (getAdd (lb ^. getRefAdd))) (getStringSN (lb ^. shortname))) x
mkRawLC x@(Change (ChC _ Unlikely _ lb)) _ = llcc (mkLabelRA'
("UC:" ++ (getAdd (lb ^. getRefAdd))) (getStringSN (lb ^. shortname))) x
mkRawLC x@(Graph _ _ _ _) lb = llcc (mkLabelRA' ("Graph:" ++ (getAdd (lb ^. getRefAdd)))
(getStringSN (lb ^. shortname))) x
mkRawLC x@(Defnt d _) lb = llcc
(mkLabelRA' ((getDefName d) ++ concatMap repUnd (getAdd (lb ^. getRefAdd)))
(concatMap repUnd (getStringSN (lb ^. shortname)))) x
mkRawLC x@(Table _ _ _ _) lb = llcc (setLabel "Table:" "" lb) x
mkRawLC x@(Paragraph _) lb = llcc (setLabel "Paragraph:" "" lb) x
mkRawLC x@(Definition d) lb = llcc (setLabel (getDefName d) "" lb) x
mkRawLC x@(Enumeration _) lb = llcc (setLabel "List:" "" lb) x
mkRawLC x@(Figure _ _ _) lb = llcc (setLabel "Figure:" ""lb) x
mkRawLC x@(Requirement (RC _ FR _ _)) lb = llcc (setLabel "FR:" "" lb) x
mkRawLC x@(Requirement (RC _ NFR _ _)) lb = llcc (setLabel "NFR:" "" lb) x
mkRawLC x@(Assumption ac) lb = llcc (setLabel "A:" "" lb) x
mkRawLC x@(Change (ChC _ Likely _ lb)) _ = llcc (setLabel "LC:" "" lb) x
mkRawLC x@(Change (ChC _ Unlikely _ lb)) _ = llcc (setLabel "UC:" "" lb) x
mkRawLC x@(Graph _ _ _ _) lb = llcc (setLabel "Graph:" "" lb) x
mkRawLC x@(Defnt d _) lb = llcc (setLabel (getDefName d) "" lb) x

setLabel :: String -> String -> Label -> Label
setLabel prependRA prependSN lb = mkLabelRA' (setRefAdd prependRA (lb ^. getRefAdd))
(setSN prependSN (lb ^. shortname))

--setRefAdd :: String -> LblType -> String
setRefAdd prependRA ra = prependRA ++ concatMap repUnd (getAdd ra)

setSN :: String -> ShortName -> String
setSN prependSN sn = prependSN ++ concatMap repUnd (getStringSN sn)

-- | Automatically create the label for a definition
getDefName :: DType -> String
getDefName (Data c) = "DD:" ++ concatMap repUnd (c ^. uid) -- FIXME: To be removed
getDefName (Data' c) = "DD:" ++ concatMap repUnd (c ^. uid) -- FIXME: To be removed
getDefName (Theory c) = "T:" ++ concatMap repUnd (c ^. uid) -- FIXME: To be removed
getDefName (Data c) = "DD:"
getDefName (Data' c) = "DD:"
getDefName (Theory c) = "T:"
getDefName TM = "T:"
getDefName DD = "DD:"
getDefName Instance = "IM:"
Expand Down
28 changes: 22 additions & 6 deletions code/drasil-lang/Language/Drasil/Reference.hs
Original file line number Diff line number Diff line change
Expand Up @@ -18,10 +18,10 @@ import Language.Drasil.Chunk.Goal as G (Goal, refAddr)
import Language.Drasil.Chunk.InstanceModel (InstanceModel)
import Language.Drasil.Chunk.PhysSystDesc as PD (PhysSystDesc, refAddr)
import Language.Drasil.Chunk.ReqChunk as R (ReqChunk(..), ReqType(FR))
import Language.Drasil.Chunk.ShortName (HasShortName(shortname), ShortName)
import Language.Drasil.Chunk.ShortName (HasShortName(shortname), ShortName, getStringSN, shortname')
import Language.Drasil.Chunk.Theory (TheoryModel)
import Language.Drasil.Classes (ConceptDomain(cdom), HasUID(uid), HasLabel(getLabel), HasRefAddress(getRefAdd))
import Language.Drasil.Document (Section(Section), getDefName, repUnd)
import Language.Drasil.Document (Section(Section), getDefName, repUnd, setSN)
import Language.Drasil.Document.Core (RawContent(..), LabelledContent(..))
import Language.Drasil.People (People, comparePeople)
import Language.Drasil.Spec (Sentence((:+:), Ref, S))
Expand Down Expand Up @@ -341,7 +341,7 @@ assumptionsFromDB am = dropNums $ sortBy (compare `on` snd) assumptions
--FIXME: completely shift to being `HasLabel` since customref checks for
-- `HasShortName` and `Referable`?
makeRef :: (HasShortName l, Referable l) => l -> Sentence
makeRef r = customRef r (r ^. shortname)
makeRef r = customRef r (shortname' $ concatMap repUnd $ getStringSN (r ^. shortname))

--FIXME: needs design (HasShortName, Referable only possible when HasLabel)
mkRefFrmLbl :: (HasLabel l, HasShortName l, Referable l) => l -> Sentence
Expand All @@ -351,11 +351,27 @@ mkRefFrmLbl r = makeRef r
midRef :: Label -> Sentence
midRef r = customRef r (r ^. shortname)

-- | Create a reference with a custom 'ShortName'
-- | Create a reference with a customized 'ShortName'
customRef :: (HasShortName l, Referable l) => l -> ShortName -> Sentence
customRef r n = Ref (rType r) (refAdd r) n
customRef r n = Ref (rType r) (refAdd r) (shortname' $ temp (rType r) n)
where
temp :: RefType -> ShortName -> String
temp Tab s = setSN "" s
temp Fig s = setSN "" s
temp Sect s = setSN "" s
temp Def s = setSN "" s
temp Mod s = setSN "" s
temp Req s = setSN "" s
temp Assump s = setSN "" s
temp LC s = setSN "" s
temp UC s = setSN "" s
temp EqnB s = setSN "" s
temp Cite s = setSN "" s
temp Goal s = setSN "" s
temp PSD s = setSN "" s
temp Lbl s = setSN "" s

-- This works for passing the correct id to the reference generator for Assumptions,
-- Requirements and Likely Changes but I question whether we should use it.
-- Pass it the item to be referenced and the enumerated list of the respective
-- contents for that file. Change rType values to implement.
-- contents for that file. Change rType values to implement.

1 comment on commit 1ca3090

@JacquesCarette
Copy link
Owner

Choose a reason for hiding this comment

The reason will be displayed to describe this comment to others. Learn more.

Nice improvement!

Please sign in to comment.