Skip to content

Commit

Permalink
Created HasShortName and Merged refName with newly built shortname (
Browse files Browse the repository at this point in the history
#563)

* implemented all changes from 46331be to d7dedf5

* minor comment fix
  • Loading branch information
niazim3 authored and JacquesCarette committed May 31, 2018
1 parent 9b6439f commit 9dc128c
Show file tree
Hide file tree
Showing 13 changed files with 115 additions and 64 deletions.
4 changes: 2 additions & 2 deletions code/Example/Drasil/DocumentLanguage.hs
Original file line number Diff line number Diff line change
Expand Up @@ -510,8 +510,8 @@ siSys (SI {_sys = sys}) = nw sys
-- mkAssump i desc = Assumption $ ac' i desc

mkRequirement :: String -> Sentence -> String -> Contents
mkRequirement i desc shrtn = Requirement $ frc i desc (shrtn) [shortname shrtn] --FIXME: HACK - Should have explicit refname
mkRequirement i desc shrtn = Requirement $ frc i desc (shrtn) [shortname' shrtn] --FIXME: HACK - Should have explicit refname

mkLklyChnk :: String -> Sentence -> String -> Contents
mkLklyChnk i desc shrtn = Change $ lc i desc (shrtn) [shortname shrtn] -- FIXME: HACK -- See above
mkLklyChnk i desc shrtn = Change $ lc i desc (shrtn) [shortname' shrtn] -- FIXME: HACK -- See above

2 changes: 1 addition & 1 deletion code/Example/Drasil/SSP/Body.hs
Original file line number Diff line number Diff line change
Expand Up @@ -264,7 +264,7 @@ s4_1_2_p1 = physSystIntro slope how intrslce slice (S "slice base")
fig_indexconv
where how = S "as a series of" +:+ phrase slice +:+. plural element

physSystIntro :: (NamedIdea a, NamedIdea b, NamedIdea c, Referable d) =>
physSystIntro :: (NamedIdea a, NamedIdea b, NamedIdea c, HasShortName d, Referable d) =>
a -> Sentence -> b -> c -> Sentence -> d -> Contents
physSystIntro what how p1 p2 p3 indexref = foldlSP [
at_start analysis, S "of the", phrase what, S "is performed by looking at",
Expand Down
2 changes: 1 addition & 1 deletion code/Example/Drasil/Sections/SolutionCharacterSpec.hs
Original file line number Diff line number Diff line change
Expand Up @@ -488,7 +488,7 @@ iModIntro = foldlSP [S "This", phrase Doc.section_,
plural Doc.symbol_, S "defined in", S "FIXME REF",
S "to replace the abstract", plural Doc.symbol_, S "in the",
plural Doc.model, S "identified in", S "FIXME REF" :+: S " and" +:+ S "FIXME REF"]

---------------------
-- DATA CONSTRAINTS --
---------------------
Expand Down
2 changes: 1 addition & 1 deletion code/Example/Drasil/Sections/SpecificSystemDescription.hs
Original file line number Diff line number Diff line change
Expand Up @@ -203,7 +203,7 @@ dataConstraintParagraph hasUncertainty tableRef middleSent trailingSent = Paragr
-- makes a list of references to tables takes
-- l list of layout objects that can be referenced
-- outputs a sentence containing references to the layout objects
listofTablesToRefs :: Referable l => [l] -> Sentence
listofTablesToRefs :: (HasShortName l, Referable l) => [l] -> Sentence
listofTablesToRefs [] = EmptyS
listofTablesToRefs [x] = (makeRef x) +:+ S "shows"
listofTablesToRefs [x,y] = (makeRef x) `sC` S "and" +:+ listofTablesToRefs [y]
Expand Down
4 changes: 3 additions & 1 deletion code/Language/Drasil.hs
Original file line number Diff line number Diff line change
Expand Up @@ -88,9 +88,10 @@ module Language.Drasil (
, Attributes
-- Chunk.Attributes
, getSource
, Derivation, getDerivation, getShortName, shortname
, Derivation, getDerivation, getShortName, shortname'
, sourceref
, References
, HasShortName(shortname)
--Citations
, Citation, BibRef, CiteField, Month(..), HP
-- CiteFields smart constructors
Expand Down Expand Up @@ -221,6 +222,7 @@ import Language.Drasil.Chunk.Attribute
import Language.Drasil.Chunk.Attribute.Core (Attributes)
import Language.Drasil.Chunk.Attribute.Derivation (Derivation)
import Language.Drasil.Chunk.Attribute.References (References)
import Language.Drasil.Chunk.Attribute.ShortName
import Language.Drasil.Chunk.Change
import Language.Drasil.Chunk.Citation (
-- Types
Expand Down
4 changes: 2 additions & 2 deletions code/Language/Drasil/Chunk/AssumpChunk.hs
Original file line number Diff line number Diff line change
Expand Up @@ -5,7 +5,7 @@ module Language.Drasil.Chunk.AssumpChunk
) where

import Language.Drasil.Classes (HasUID(uid), HasAttributes(attributes))
import Language.Drasil.Chunk.Attribute (shortname)
import Language.Drasil.Chunk.Attribute (shortname')
import Language.Drasil.Chunk.Attribute.Core (Attributes)
import Language.Drasil.Spec (Sentence(..), RefName)

Expand All @@ -28,4 +28,4 @@ instance Eq AssumpChunk where a == b = a ^. uid == b ^. uid
-- | Smart constructor for Assumption chunks. The second 'Sentence' here is
-- a short name (attribute).
assump :: String -> Sentence -> RefName -> Attributes -> AssumpChunk
assump i a s att = AC i a s ((shortname s):att)
assump i a s att = AC i a s ((shortname' s):att)
6 changes: 3 additions & 3 deletions code/Language/Drasil/Chunk/Attribute.hs
Original file line number Diff line number Diff line change
@@ -1,6 +1,6 @@
module Language.Drasil.Chunk.Attribute
( getSource, getDerivation, getShortName
, shortname, sourceref
, shortname', sourceref
) where

import Control.Lens ((^.))
Expand Down Expand Up @@ -36,8 +36,8 @@ getShortName c = shortName $ c ^. attributes
shortName ((ShortName s):_) = Just (S s)
shortName (_:xs) = shortName xs

shortname :: String -> Attribute
shortname = ShortName
shortname' :: String -> Attribute
shortname' = ShortName

sourceref :: Sentence -> Reference
sourceref = SourceRef
Expand Down
90 changes: 88 additions & 2 deletions code/Language/Drasil/Chunk/Attribute/ShortName.hs
Original file line number Diff line number Diff line change
@@ -1,6 +1,92 @@
{-# Language TemplateHaskell #-}
module Language.Drasil.Chunk.Attribute.ShortName where

import Language.Drasil.Spec (Sentence(..))

data ShortNm = ShortName Sentence
import Language.Drasil.Classes (HasUID(uid))
import Language.Drasil.Chunk.AssumpChunk as A
import Language.Drasil.Chunk.Change as Ch
import Language.Drasil.Chunk.Citation as Ci
import Language.Drasil.Chunk.Eq
import Language.Drasil.Chunk.GenDefn
import Language.Drasil.Chunk.Goal as G
import Language.Drasil.Chunk.InstanceModel
import Language.Drasil.Chunk.PhysSystDesc as PD
import Language.Drasil.Chunk.ReqChunk as R
import Language.Drasil.Chunk.Theory
import Language.Drasil.Document
import Control.Lens ((^.))
import Language.Drasil.Spec (Sentence(..), RefName)

--data ShortNm = ShortName String

class HasShortName s where
shortname :: s -> RefName -- String; The text to be displayed for the link.
-- A short name used for referencing within a document that can
-- include symbols and whatnot if required.
-- Visible in the typeset documents (pdf)


instance HasShortName Goal where
shortname g = g ^. G.refAddr

instance HasShortName PhysSystDesc where
shortname p = p ^. PD.refAddr

instance HasShortName AssumpChunk where
shortname (AC _ _ sn _) = sn

instance HasShortName ReqChunk where
shortname (RC _ _ _ sn _) = sn

instance HasShortName Change where
shortname (ChC _ _ _ sn _) = sn

instance HasShortName Section where
shortname (Section _ _ _ sn) = sn

instance HasShortName Citation where
shortname c = citeID c

-- error used below is on purpose. These shortnames should be made explicit as necessary
instance HasShortName TheoryModel where
shortname _ = error "No explicit name given for theory model -- build a custom Ref"

instance HasShortName GenDefn where
shortname _ = error "No explicit name given for general definition -- build a custom Ref"

instance HasShortName QDefinition where -- FIXME: This could lead to trouble; need
-- to ensure sanity checking when building
-- Refs. Double-check QDef is a DD before allowing
shortname _ = error "No explicit name given for data definition -- build a custom Ref"

instance HasShortName InstanceModel where
shortname _ = error "No explicit name given for instance model -- build a custom Ref"

instance HasShortName Contents where
shortname (Table _ _ _ _ r) = "Table:" ++ r
shortname (Figure _ _ _ r) = "Figure:" ++ r
shortname (Graph _ _ _ _ r) = "Figure:" ++ r
shortname (EqnBlock _ r) = "Equation:" ++ r
shortname (Definition d) = getDefName d
shortname (Defnt _ _ r) = r
shortname (Requirement rc) = shortname rc
shortname (Assumption ca) = shortname ca
shortname (Change lcc) = shortname lcc
shortname (Enumeration _) = error "Can't reference lists"
shortname (Paragraph _) = error "Can't reference paragraphs"
shortname (Bib _) = error $
"Bibliography list of references cannot be referenced. " ++
"You must reference the Section or an individual citation."

-- | Automatically create the label for a definition
getDefName :: DType -> String
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 TM = "T:"
getDefName DD = "DD:"
getDefName Instance = "IM:"
getDefName General = "GD:"

repUnd :: Char -> String
repUnd '_' = "."
repUnd c = c : []
4 changes: 2 additions & 2 deletions code/Language/Drasil/Chunk/Change.hs
Original file line number Diff line number Diff line change
Expand Up @@ -5,7 +5,7 @@ module Language.Drasil.Chunk.Change

import Language.Drasil.Classes (HasUID(uid),HasAttributes(attributes))
import Language.Drasil.Chunk.Attribute.Core(Attributes)
import Language.Drasil.Chunk.Attribute(shortname)
import Language.Drasil.Chunk.Attribute(shortname')
import Language.Drasil.Spec (Sentence, RefName)

import Control.Lens (set, (^.))
Expand Down Expand Up @@ -43,7 +43,7 @@ chc :: String -> ChngType -> Sentence -> RefName -> Attributes -> Change
chc = ChC

chc' :: Change -> String -> Change
chc' c s = set attributes ([shortname s] ++ (c ^. attributes)) c
chc' c s = set attributes ([shortname' s] ++ (c ^. attributes)) c

lc, ulc :: String -> Sentence -> RefName -> Attributes -> Change
-- | Smart constructor for functional requirement chunks.
Expand Down
4 changes: 2 additions & 2 deletions code/Language/Drasil/Chunk/ReqChunk.hs
Original file line number Diff line number Diff line change
Expand Up @@ -4,7 +4,7 @@ module Language.Drasil.Chunk.ReqChunk
) where

import Language.Drasil.Classes (HasUID(uid), HasAttributes(attributes))
import Language.Drasil.Chunk.Attribute (shortname)
import Language.Drasil.Chunk.Attribute (shortname')
import Language.Drasil.Chunk.Attribute.Core (Attributes)
import Language.Drasil.Spec (Sentence, RefName)

Expand Down Expand Up @@ -47,7 +47,7 @@ rc :: String -> ReqType -> Sentence -> RefName -> Attributes -> ReqChunk
rc = RC

rc' :: ReqChunk -> String -> ReqChunk
rc' r s = set attributes (shortname s : (r ^. attributes)) r
rc' r s = set attributes (shortname' s : (r ^. attributes)) r

frc, nfrc :: String -> Sentence -> RefName -> Attributes -> ReqChunk
-- | Smart constructor for functional requirement chunks.
Expand Down
4 changes: 2 additions & 2 deletions code/Language/Drasil/Printing/Import.hs
Original file line number Diff line number Diff line change
Expand Up @@ -31,7 +31,7 @@ import Language.Drasil.Spec (Sentence(..))
import Language.Drasil.Misc (unit'2Contents)
import Language.Drasil.NounPhrase (phrase, titleize)
import Language.Drasil.Reference

import Language.Drasil.Chunk.Attribute.ShortName
import Language.Drasil.Document

import Control.Lens ((^.))
Expand Down Expand Up @@ -268,7 +268,7 @@ sec sm depth x@(Section title contents _ _) = --FIXME: should ShortName be used
map (layout sm depth) contents) ref

getSN :: HasAttributes c => c -> Sentence
getSN c = maybe (error "missing attribute ShortName") id $ getShortName c
getSN c = maybe (error "missing attribute refAdd") id $ getShortName c

-- | Translates from Contents to the Printing Representation of LayoutObj.
-- Called internally by layout.
Expand Down
52 changes: 7 additions & 45 deletions code/Language/Drasil/Reference.hs
Original file line number Diff line number Diff line change
Expand Up @@ -13,10 +13,10 @@ import Language.Drasil.Chunk.PhysSystDesc as PD
import Language.Drasil.Chunk.ReqChunk as R
import Language.Drasil.Chunk.Theory
import Language.Drasil.Document
import Language.Drasil.Spec (Sentence(..),RefName)
import Language.Drasil.Spec (Sentence(..))
import Language.Drasil.RefTypes (RefType(..))
import Control.Lens ((^.), Simple, Lens, makeLenses)

import Language.Drasil.Chunk.Attribute.ShortName
import Data.List (partition, sortBy)
import qualified Data.Map as Map
import Data.Function (on)
Expand Down Expand Up @@ -151,85 +151,60 @@ instance HasCitationRefs ReferenceDB where citationRefTable = citationDB


class Referable s where
refName :: s -> RefName -- Sentence; The text to be displayed for the link.
refAdd :: s -> String -- The reference address (what we're linking to).
refAdd :: s -> String -- The plaintext referencing address (what we're linking to).
-- Should be string with no spaces/special chars.
-- Only visible in the source (tex/html).
rType :: s -> RefType -- The reference type (referencing namespace?)

instance Referable Goal where
refName g = g ^. G.refAddr
refAdd g = "GS:" ++ g ^. G.refAddr
rType _ = Goal

instance Referable PhysSystDesc where
refName p = p ^. PD.refAddr
refAdd p = "PS:" ++ p ^. PD.refAddr
rType _ = PSD

instance Referable AssumpChunk where
refName (AC _ _ sn _) = sn
refAdd x = "A:" ++ concatMap repUnd (x ^. uid)
rType _ = Assump

instance Referable ReqChunk where
refName (RC _ _ _ sn _) = sn
refAdd r@(RC _ rt _ _ _) = show rt ++ ":" ++ concatMap repUnd (r ^. uid)
rType _ = Req

instance Referable Change where
refName (ChC _ _ _ sn _) = sn
refAdd r@(ChC _ rt _ _ _) = show rt ++ ":" ++ concatMap repUnd (r ^. uid)
rType (ChC _ Likely _ _ _) = LC
rType (ChC _ Unlikely _ _ _) = UC

instance Referable Section where
refName (Section _ _ _ sn) = sn
refAdd (Section _ _ r _) = "Sec:" ++ r
rType _ = Sect

instance Referable Citation where
refName c = citeID c
refAdd c = concatMap repUnd $ citeID c -- citeID should be unique.
rType _ = Cite

-- error used below is on purpose. These refNames should be made explicit as necessary
instance Referable TheoryModel where
refName _ = error "No explicit name given for theory model -- build a custom Ref"
refAdd t = "T:" ++ t ^. uid
rType _ = Def

instance Referable GenDefn where
refName _ = error "No explicit name given for theory model -- build a custom Ref"
refAdd g = "GD:" ++ g ^. uid
rType _ = Def

instance Referable QDefinition where -- FIXME: This could lead to trouble; need
-- to ensure sanity checking when building
-- Refs. Double-check QDef is a DD before allowing
refName _ = error "No explicit name given for theory model -- build a custom Ref"
refAdd d = "DD:" ++ concatMap repUnd (d ^. uid)
rType _ = Def

instance Referable InstanceModel where
refName _ = error "No explicit name given for theory model -- build a custom Ref"
refAdd i = "IM:" ++ i^.uid
rType _ = Def

instance Referable Contents where
refName (Table _ _ _ _ r) = "Table:" ++ r
refName (Figure _ _ _ r) = "Figure:" ++ r
refName (Graph _ _ _ _ r) = "Figure:" ++ r
refName (EqnBlock _ r) = "Equation:" ++ r
refName (Definition d) = getDefName d
refName (Defnt _ _ r) = r
refName (Requirement rc) = refName rc
refName (Assumption ca) = refName ca
refName (Change lcc) = refName lcc
refName (Enumeration _) = error "Can't reference lists"
refName (Paragraph _) = error "Can't reference paragraphs"
refName (Bib _) = error $
"Bibliography list of references cannot be referenced. " ++
"You must reference the Section or an individual citation."
rType (Table _ _ _ _ _) = Tab
rType (Figure _ _ _ _) = Fig
rType (Definition (Data _)) = Def
Expand Down Expand Up @@ -258,15 +233,6 @@ instance Referable Contents where
"Bibliography list of references cannot be referenced. " ++
"You must reference the Section or an individual citation."

-- | Automatically create the label for a definition
getDefName :: DType -> String
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 TM = "T:"
getDefName DD = "DD:"
getDefName Instance = "IM:"
getDefName General = "GD:"

citeSort :: Citation -> Citation -> Ordering
citeSort = compare `on` (^. uid)

Expand All @@ -280,19 +246,15 @@ assumptionsFromDB am = dropNums $ sortBy (compare `on` snd) assumptions
where assumptions = Map.elems am
dropNums = map fst

repUnd :: Char -> String
repUnd '_' = "."
repUnd c = c : []

-- | Create References to a given 'LayoutObj'
-- This should not be exported to the end-user, but should be usable
-- within the recipe (we want to force reference creation to check if the given
-- item exists in our database of referable objects.
makeRef :: (Referable l) => l -> Sentence
makeRef r = customRef r (refName r)
makeRef :: (HasShortName l, Referable l) => l -> Sentence
makeRef r = customRef r (shortname r)

-- | Create a reference with a custom 'RefName'
customRef :: (Referable l) => l -> String -> Sentence
customRef :: (HasShortName l, Referable l) => l -> String -> Sentence
customRef r n = Ref (rType r) (refAdd r) n

-- This works for passing the correct id to the reference generator for Assumptions,
Expand Down
1 change: 1 addition & 0 deletions code/drasil.cabal
Original file line number Diff line number Diff line change
Expand Up @@ -86,6 +86,7 @@ library
, Language.Drasil.Chunk.Attribute.Core
, Language.Drasil.Chunk.Attribute.Derivation
, Language.Drasil.Chunk.Attribute.References
, Language.Drasil.Chunk.Attribute.ShortName
, Language.Drasil.Chunk.Change
, Language.Drasil.Chunk.Citation
, Language.Drasil.Chunk.Code
Expand Down

0 comments on commit 9dc128c

Please sign in to comment.