Skip to content

Commit

Permalink
Change instances of String to UID to make progress towards obscuring …
Browse files Browse the repository at this point in the history
…the implementation of UID. (Comment 6, Bullet 1, Issue #562)
  • Loading branch information
Mornix authored and samm82 committed Jun 11, 2018
1 parent 7152261 commit 4391781
Show file tree
Hide file tree
Showing 19 changed files with 49 additions and 29 deletions.
2 changes: 1 addition & 1 deletion code/Example/Drasil/Sections/SolutionCharacterSpec.hs
Original file line number Diff line number Diff line change
Expand Up @@ -88,7 +88,7 @@ siUQO xs = UnQuantO xs
-- HELPER FUNCTION --
----------------------

compareID :: (NamedIdea a) => a -> String -> Bool
compareID :: (NamedIdea a) => a -> UID -> Bool
compareID c1 c2 = (c1 ^. uid) == c2

-----------------------
Expand Down
3 changes: 2 additions & 1 deletion code/Language/Drasil/Chunk/Code.hs
Original file line number Diff line number Diff line change
Expand Up @@ -14,6 +14,7 @@ import Language.Drasil.Chunk.Constrained.Core (Constraint, isPhysC)
import Language.Drasil.Chunk.Quantity
import Language.Drasil.Chunk.Eq (QDefinition)
import Language.Drasil.Chunk.SymbolForm (codeSymb)
import Language.Drasil.UID (UID)
import Language.Drasil.Classes (HasUID(uid), NamedIdea(term), Idea(getA),
HasSymbol(symbol), CommonIdea(abrv), Constrained(constraints), relat)
import Language.Drasil.Space as S
Expand Down Expand Up @@ -196,7 +197,7 @@ qtov q = CD (qw q) (symbToCodeName (codeSymb q)) (q ^. relat)
codeEquat :: CodeDefinition -> Expr
codeEquat cd = cd ^. def

type ConstraintMap = Map.Map String [Constraint]
type ConstraintMap = Map.Map UID [Constraint]

constraintMap :: (HasUID c, Constrained c) => [c] -> ConstraintMap
constraintMap = Map.fromList . map (\x -> ((x ^. uid), (x ^. constraints)))
Expand Down
1 change: 1 addition & 0 deletions code/Language/Drasil/Code/Imperative/Import.hs
Original file line number Diff line number Diff line change
Expand Up @@ -16,6 +16,7 @@ import Language.Drasil.Expr.Extract hiding (vars)
import Language.Drasil.CodeSpec hiding (codeSpec, Mod(..))
import qualified Language.Drasil.CodeSpec as CS (Mod(..))
import Language.Drasil.DataDesc
import Language.Drasil.UID (UID)
import Language.Drasil.Classes (HasUID, HasSymbol)

import Prelude hiding (log, exp, const)
Expand Down
3 changes: 3 additions & 0 deletions code/Language/Drasil/UID.hs
Original file line number Diff line number Diff line change
@@ -0,0 +1,3 @@
module Language.Drasil.UID (UID) where

type UID = String
3 changes: 3 additions & 0 deletions code/Language/Language/Drasil.hs
Original file line number Diff line number Diff line change
Expand Up @@ -25,6 +25,8 @@ module Language.Drasil (
, DerUChunk(..), UnitDefn(..), unitWrapper
, makeDerU, unitCon, fund, comp_unitdefn
, (^:), (/:), (*:), (*$), (/$), new_unit
-- UID
, UID
-- Classes
, HasUID(uid)
, NamedIdea(term)
Expand Down Expand Up @@ -207,6 +209,7 @@ import Language.Drasil.Document (Document(..), DType(..)
import Language.Drasil.Unicode -- all of it
import Language.Drasil.UnitLang -- all of it
import Language.Drasil.Unit -- all of it
import Language.Drasil.UID (UID)
import Language.Drasil.Classes (HasUID(uid), NamedIdea(term), Idea(getA),
Definition(defn), ConceptDomain(cdom), Concept, HasSymbol(symbol), HasUnitSymbol(usymb),
IsUnit, CommonIdea(abrv),
Expand Down
4 changes: 3 additions & 1 deletion code/Language/Language/Drasil/Chunk/AssumpChunk.hs
Original file line number Diff line number Diff line change
Expand Up @@ -4,15 +4,17 @@ module Language.Drasil.Chunk.AssumpChunk
, assump
) where

import Language.Drasil.UID (UID)
import Language.Drasil.Classes (HasUID(uid))
import Language.Drasil.Spec (Sentence(..))
import Language.Drasil.Chunk.Attribute.ShortName

import Control.Lens (makeLenses, (^.))

-- | Assumption chunk type. Has id, what is being assumed, and a shortname.
-- Presently assumptions are captured as sentences.
data AssumpChunk = AC
{ _aid :: String
{ _aid :: UID
, assuming :: Sentence
, _refName :: ShortName
}
Expand Down
3 changes: 2 additions & 1 deletion code/Language/Language/Drasil/Chunk/Change.hs
Original file line number Diff line number Diff line change
Expand Up @@ -4,6 +4,7 @@ module Language.Drasil.Chunk.Change
) where

import Language.Drasil.Classes (HasUID(uid))
import Language.Drasil.UID (UID)
import Language.Drasil.Chunk.Attribute.ShortName
import Language.Drasil.Spec (Sentence)

Expand All @@ -26,7 +27,7 @@ instance Show ChngType where
-- (Functional/Non-Functional) from 'ChngType', a sentence describing what is
-- required (TODO: Change this), and a short name for reference display.
data Change = ChC
{ _id :: String
{ _id :: UID
, chngType :: ChngType
, chng :: Sentence
, _refName :: ShortName
Expand Down
3 changes: 2 additions & 1 deletion code/Language/Language/Drasil/Chunk/Citation.hs
Original file line number Diff line number Diff line change
Expand Up @@ -24,6 +24,7 @@ module Language.Drasil.Chunk.Citation

import Language.Drasil.People
import Language.Drasil.Spec (Sentence(..))
import Language.Drasil.UID (UID)
import Language.Drasil.Classes (HasUID(uid))
import Language.Drasil.Printing.Helpers (noSpaces)
import Language.Drasil.Chunk.Attribute.ShortName
Expand Down Expand Up @@ -90,7 +91,7 @@ instance Show Month where
-- We will also have an EntryID (String) used for creating reference links.
-- Finally we will have the reference information (type and fields).
data Citation = Cite
{ _id :: String
{ _id :: UID
, citeID :: EntryID
, externRefT :: CitationKind
, fields :: [CiteField]
Expand Down
3 changes: 2 additions & 1 deletion code/Language/Language/Drasil/Chunk/CommonIdea.hs
Original file line number Diff line number Diff line change
@@ -1,6 +1,7 @@
{-# Language TemplateHaskell #-}
module Language.Drasil.Chunk.CommonIdea ( CI, commonIdea , getAcc) where

import Language.Drasil.UID (UID)
import Language.Drasil.Classes (HasUID(uid), NamedIdea(term), Idea(getA), CommonIdea(abrv))
import Language.Drasil.Spec (Sentence(S))
import Language.Drasil.NounPhrase (NP)
Expand All @@ -9,7 +10,7 @@ import Control.Lens (makeLenses, view)

-- | The common idea (with nounPhrase) data type. It must have a
-- 'NounPhrase' for its 'term'.
data CI = CI { _cid :: String, _ni :: NP, _ab :: String}
data CI = CI { _cid :: UID, _ni :: NP, _ab :: String}
makeLenses ''CI

instance HasUID CI where uid = cid
Expand Down
3 changes: 2 additions & 1 deletion code/Language/Language/Drasil/Chunk/Goal.hs
Original file line number Diff line number Diff line change
Expand Up @@ -8,6 +8,7 @@ module Language.Drasil.Chunk.Goal
, refAddr
) where

import Language.Drasil.UID (UID)
import Language.Drasil.Classes (HasUID(uid))
import Language.Drasil.Spec (Sentence)
import Language.Drasil.RefTypes (RefAdd)
Expand All @@ -16,7 +17,7 @@ import Language.Drasil.Chunk.Attribute.ShortName
import Control.Lens (makeLenses, (^.))

data Goal = GS
{ _gid :: String
{ _gid :: UID
, goal :: Sentence
, _refAddr :: RefAdd
}
Expand Down
15 changes: 8 additions & 7 deletions code/Language/Language/Drasil/Chunk/NamedIdea.hs
Original file line number Diff line number Diff line change
Expand Up @@ -4,6 +4,7 @@ module Language.Drasil.Chunk.NamedIdea (
compoundNC, compoundNC', compoundNC'', compoundNC''',
the, theCustom) where

import Language.Drasil.UID (UID)
import Language.Drasil.Classes (HasUID(uid), NamedIdea(term), Idea(getA))
import Control.Lens ((^.), makeLenses, view)

Expand All @@ -17,7 +18,7 @@ short c = maybe (phrase (c ^. term)) id (fmap S $ getA c)
-- === DATA TYPES/INSTANCES === --
-- | Note that a |NamedChunk| does not have an acronym/abbreviation
-- as that's a |CommonIdea|, which has its own representation
data NamedChunk = NC {_uu :: String, _np :: NP}
data NamedChunk = NC {_uu :: UID, _np :: NP}
makeLenses ''NamedChunk

instance Eq NamedChunk where c1 == c2 = (c1 ^. uid) == (c2 ^. uid)
Expand Down Expand Up @@ -54,12 +55,12 @@ nw c = IdeaDict (NC (c^.uid) (c^.term)) (getA c)
-- | Combinator for combining two 'NamedChunk's into one.
-- /Does not preserve abbreviations/
compoundNC :: (NamedIdea a, NamedIdea b) => a -> b -> NamedChunk
compoundNC t1 t2 = nc
compoundNC t1 t2 = nc
(t1^.uid ++ t2^.uid) (compoundPhrase (t1 ^. term) (t2 ^. term))

compoundNC' :: (NamedIdea a, NamedIdea b) => a -> b -> NamedChunk
compoundNC' t1 t2 = nc
(t1^.uid ++ t2^.uid) (compoundPhrase'' plural plural (t1 ^. term) (t2 ^. term))
compoundNC' t1 t2 = nc
(t1^.uid ++ t2^.uid) (compoundPhrase'' plural plural (t1 ^. term) (t2 ^. term))

compoundNC'' :: (NamedIdea a, NamedIdea b) =>
(NP -> Sentence) -> (NP -> Sentence) -> a -> b -> NamedChunk
Expand All @@ -69,14 +70,14 @@ compoundNC'' f1 f2 t1 t2 = nc
-- hack for Solution Characteristics Specification, calling upon plural will pluralize
-- Characteristics as it is the end of the first term (solutionCharacteristic)
compoundNC''' :: (NamedIdea a, NamedIdea b) => (NP -> Sentence) -> a -> b -> NamedChunk
compoundNC''' f1 t1 t2 = nc
compoundNC''' f1 t1 t2 = nc
(t1^.uid ++ t2^.uid) (compoundPhrase''' f1 (t1 ^. term) (t2 ^. term))

the :: (NamedIdea c) => c -> NamedChunk
the t = nc ("the" ++ t ^. uid) (nounPhrase''
the t = nc ("the" ++ t ^. uid) (nounPhrase''
(S "the" +:+ (phrase $ t ^. term)) (S "the" +:+ (plural $ t ^. term))
CapFirst CapWords)

theCustom :: (NamedIdea c) => (c -> Sentence) -> c -> NamedChunk
theCustom f t = nc ("the" ++ t ^. uid) (nounPhrase''(S "the" +:+ (f t))
theCustom f t = nc ("the" ++ t ^. uid) (nounPhrase''(S "the" +:+ (f t))
(S "the" +:+ (f t)) CapFirst CapWords)
3 changes: 2 additions & 1 deletion code/Language/Language/Drasil/Chunk/PhysSystDesc.hs
Original file line number Diff line number Diff line change
Expand Up @@ -9,14 +9,15 @@ module Language.Drasil.Chunk.PhysSystDesc
, refAddr
) where

import Language.Drasil.UID (UID)
import Language.Drasil.Classes (HasUID(uid))
import Language.Drasil.Spec (Sentence)
import Language.Drasil.RefTypes (RefAdd)
import Language.Drasil.Chunk.Attribute.ShortName
import Control.Lens (makeLenses, (^.))

data PhysSystDesc = PSD
{ _did :: String
{ _did :: UID
, pSysDes :: Sentence
, _refAddr :: RefAdd
}
Expand Down
3 changes: 2 additions & 1 deletion code/Language/Language/Drasil/Chunk/ReqChunk.hs
Original file line number Diff line number Diff line change
Expand Up @@ -3,6 +3,7 @@ module Language.Drasil.Chunk.ReqChunk
, frc, nfrc
) where

import Language.Drasil.UID (UID)
import Language.Drasil.Classes (HasUID(uid))
import Language.Drasil.Chunk.Attribute.ShortName
import Language.Drasil.Spec (Sentence)
Expand Down Expand Up @@ -30,7 +31,7 @@ instance Show ReqType where
-- (Functional/Non-Functional) from 'ReqType', a sentence describing what is
-- required (TODO: Change this), and a short name.
data ReqChunk = RC
{ _id :: String
{ _id :: UID
, reqType :: ReqType
, requires :: Sentence
, _refName :: ShortName
Expand Down
3 changes: 2 additions & 1 deletion code/Language/Language/Drasil/Chunk/Theory.hs
Original file line number Diff line number Diff line change
Expand Up @@ -4,6 +4,7 @@ module Language.Drasil.Chunk.Theory
Theory(..), TheoryChunk, TheoryModel, tm,
)where

import Language.Drasil.UID (UID)
import Language.Drasil.Classes (HasUID(uid), NamedIdea(term), Idea(getA),
Definition(defn), ConceptDomain(cdom,DOM), Concept, HasReference(getReferences))
import Language.Drasil.Chunk.Concept
Expand All @@ -26,7 +27,7 @@ class HasUID t => Theory t where

data SpaceDefn -- FIXME: This should be defined.

data TheoryChunk = TC { _tid :: String
data TheoryChunk = TC { _tid :: UID
, _vctx :: [TheoryChunk]
, _spc :: [SpaceDefn]
, _quan :: [QuantityDict]
Expand Down
11 changes: 6 additions & 5 deletions code/Language/Language/Drasil/ChunkDB.hs
Original file line number Diff line number Diff line change
Expand Up @@ -7,6 +7,7 @@ module Language.Drasil.ChunkDB
, HasUnitTable(..), unitMap
) where

import Language.Drasil.UID (UID)
import Language.Drasil.Classes (HasUID(uid), Idea, Concept, DOM, IsUnit)
import Language.Drasil.Chunk.NamedIdea (IdeaDict, nw)
import Language.Drasil.Chunk.Quantity
Expand All @@ -23,19 +24,19 @@ import qualified Data.Map as Map

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

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

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

-- | Again a bit of a misnomer as it's really a map of all NamedIdeas.
-- 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 = Map.Map String IdeaDict
type TermMap = Map.Map UID IdeaDict

-- | Smart constructor for a 'SymbolMap'
symbolMap :: (Quantity c) => [c] -> SymbolMap
Expand All @@ -54,7 +55,7 @@ unitMap :: (IsUnit u, DOM u ~ ConceptChunk) => [u] -> UnitMap
unitMap = Map.fromList . map (\x -> (x ^. uid, unitWrapper x))

-- | Looks up an uid in the symbol table. If nothing is found, an error is thrown
symbLookup :: String -> SymbolMap -> QuantityDict
symbLookup :: UID -> SymbolMap -> QuantityDict
symbLookup c m = getS $ Map.lookup c m
where getS (Just x) = x
getS Nothing = error $ "Symbol: " ++ c ++ " not found in SymbolMap"
Expand Down
7 changes: 3 additions & 4 deletions code/Language/Language/Drasil/Classes.hs
Original file line number Diff line number Diff line change
@@ -1,7 +1,7 @@
{-# Language TypeFamilies #-}
-- | Defining all the classes which represent knowledge-about-knowledge
module Language.Drasil.Classes (
HasUID(uid), UID
HasUID(uid)
, NamedIdea(term)
, Idea(getA)
, Definition(defn)
Expand All @@ -25,16 +25,15 @@ import Language.Drasil.Spec (Sentence)
import Language.Drasil.Symbol (Stage, Symbol)
import Language.Drasil.Space (Space)
import Language.Drasil.UnitLang (USymb, UDefn)
import Language.Drasil.UID (UID)
import Language.Drasil.Chunk.Attribute.References (References)
import Language.Drasil.Chunk.Constrained.Core (Constraint)
import Language.Drasil.Expr (Expr)
import Language.Drasil.Chunk.Attribute.Derivation

import Control.Lens (Lens')

type UID = String

-- | The most basic item: having a unique key, here a UID (as a String)
-- | The most basic item: having a unique key, here a UID
class HasUID c where
-- | Provides a /unique/ id for internal Drasil use
uid :: Lens' c UID
Expand Down
2 changes: 1 addition & 1 deletion code/Language/Language/Drasil/Expr.hs
Original file line number Diff line number Diff line change
Expand Up @@ -6,11 +6,11 @@ import Data.Ratio (numerator,denominator)
import Prelude hiding (sqrt)
import Language.Drasil.Symbol
import Language.Drasil.Space (Space(..))
import Language.Drasil.UID (UID)

--FIXME: Haddock open issue #43 seems to make it so GADT constructors cannot
-- be documented properly

type UID = String
type Relation = Expr

infixr 8 $^
Expand Down
3 changes: 2 additions & 1 deletion code/Language/Language/Drasil/Printing/Import.hs
Original file line number Diff line number Diff line change
Expand Up @@ -2,14 +2,15 @@ module Language.Drasil.Printing.Import(space,expr,symbol,spec,makeDocument) wher

import Language.Drasil.Expr (Expr(..), BinOp(..), UFunc(..), ArithOper(..),
BoolOper(..), RTopology(..),
DerivType(..), DomainDesc(..), UID,
DerivType(..), DomainDesc(..),
RealInterval(..),Inclusive(..),
($=))
import Language.Drasil.Expr.Precedence (precA, precB, eprec)
import qualified Language.Drasil.Printing.AST as P
import qualified Language.Drasil.Printing.Citation as P
import qualified Language.Drasil.Printing.LayoutObj as T

import Language.Drasil.UID (UID)
import Language.Drasil.Classes (term, defn, usymb, relat)
import qualified Language.Drasil.Chunk.SymbolForm as SF
import Language.Drasil.Chunk.AssumpChunk
Expand Down
3 changes: 2 additions & 1 deletion code/Language/Language/Drasil/Reference.hs
Original file line number Diff line number Diff line change
@@ -1,6 +1,7 @@
{-# Language TemplateHaskell #-}
module Language.Drasil.Reference where

import Language.Drasil.UID (UID)
import Language.Drasil.Classes (HasUID(uid))
import Language.Drasil.Chunk.AssumpChunk as A
import Language.Drasil.Chunk.Change as Ch
Expand All @@ -26,7 +27,7 @@ import Data.Function (on)
-- Maintains access to both num and chunk for easy reference swapping
-- between number and shortname/refname when necessary (or use of number
-- if no shortname exists)
type RefMap a = Map.Map String (a, Int)
type RefMap a = Map.Map UID (a, Int)

-- | Physical System Description Database
type PhysSystDescMap = RefMap PhysSystDesc
Expand Down

0 comments on commit 4391781

Please sign in to comment.