Skip to content

Commit

Permalink
Removed D Derivation from Attribute.hs as per issue #537 (#556)
Browse files Browse the repository at this point in the history
  • Loading branch information
elwazana authored and samm82 committed May 31, 2018
1 parent 985bb42 commit 6c3386e
Show file tree
Hide file tree
Showing 11 changed files with 40 additions and 39 deletions.
2 changes: 1 addition & 1 deletion code/Example/Drasil/DocumentLanguage/Definitions.hs
Original file line number Diff line number Diff line change
Expand Up @@ -62,7 +62,7 @@ instanceModel fs m i = Defnt Instance (foldr (mkIMField i m) [] fs) (refAdd i)

-- | Create a derivation from a chunk's attributes. This follows the TM, DD, GD,
-- or IM definition automatically (called automatically by 'SCSSub' program)
derivation :: HasAttributes c => c -> [Contents]
derivation :: HasDerivation c => c -> [Contents]
derivation g = map makeDerivationContents (getDerivation g)

-- | Helper function for creating the layout objects
Expand Down
2 changes: 1 addition & 1 deletion code/Example/Drasil/GlassBR/IMods.hs
Original file line number Diff line number Diff line change
Expand Up @@ -26,7 +26,7 @@ iModels = [probOfBr, calOfCap, calOfDe]

probOfBreak :: InstanceModel
probOfBreak = im probOfBr [qw risk]
[TCon AssumedCon $ sy risk $> 0] (qw prob_br) [TCon AssumedCon $ sy prob_br $> 0] [] []
[TCon AssumedCon $ sy risk $> 0] (qw prob_br) [TCon AssumedCon $ sy prob_br $> 0] []

{--}

Expand Down
4 changes: 2 additions & 2 deletions code/Example/Drasil/NoPCM/Body.hs
Original file line number Diff line number Diff line change
Expand Up @@ -156,8 +156,8 @@ mkSRS = RefSec (RefProg intro
map Verbatim [s5, s6, s7, s8] ++ (Bibliography : [])

generalDefinitions :: [GenDefn]
generalDefinitions = [gd nwtnCooling (Just thermal_flux) ([] :: Attributes),
gd rocTempSimp (Nothing :: Maybe DerUChunk) [derivationsteps roc_temp_simp_deriv]]
generalDefinitions = [gd nwtnCooling (Just thermal_flux) ([] :: Derivation),
gd rocTempSimp (Nothing :: Maybe DerUChunk) roc_temp_simp_deriv]

nopcm_si :: SystemInformation
nopcm_si = SI {
Expand Down
6 changes: 4 additions & 2 deletions code/Language/Language/Drasil.hs
Original file line number Diff line number Diff line change
Expand Up @@ -39,6 +39,7 @@ module Language.Drasil (
, Constrained(constraints)
, HasReasVal(reasVal)
, ExprRelat(relat)
, HasDerivation(derivations)
-- Chunk.VarChunk
, VarChunk
, vc, implVar
Expand Down Expand Up @@ -88,7 +89,7 @@ module Language.Drasil (
-- Chunk.Attributes
, getSource
, Derivation, getDerivation, getShortName, shortname
, sourceref, derivationsteps
, sourceref
, References
--Citations
, Citation, BibRef, CiteField, Month(..), HP
Expand Down Expand Up @@ -213,7 +214,8 @@ import Language.Drasil.Unit -- all of it
import Language.Drasil.Classes (HasUID(uid), NamedIdea(term), Idea(getA),
Definition(defn), ConceptDomain(cdom), Concept, HasSymbol(symbol), HasUnitSymbol(usymb),
IsUnit, HasAttributes(attributes), CommonIdea(abrv),
Constrained(constraints), HasReasVal(reasVal), ExprRelat(relat), HasReference(getReferences))
Constrained(constraints), HasReasVal(reasVal), ExprRelat(relat), HasDerivation(derivations),
HasReference(getReferences))
import Language.Drasil.Chunk.AssumpChunk
import Language.Drasil.Chunk.Attribute
import Language.Drasil.Chunk.Attribute.Core (Attributes)
Expand Down
17 changes: 5 additions & 12 deletions code/Language/Language/Drasil/Chunk/Attribute.hs
Original file line number Diff line number Diff line change
@@ -1,13 +1,14 @@
module Language.Drasil.Chunk.Attribute
( getSource, getDerivation, getShortName
, shortname, sourceref, derivationsteps
, shortname, sourceref
) where

import Control.Lens ((^.))
import Language.Drasil.Spec (Sentence(EmptyS, S), (+:+))
import Language.Drasil.Chunk.Attribute.Core (Attributes, Attribute(..))
import Language.Drasil.Chunk.Attribute.Derivation (Derivation)
import Language.Drasil.Classes (HasAttributes(attributes), HasReference(getReferences))
import Language.Drasil.Classes (HasAttributes(attributes), HasDerivation(derivations),
HasReference(getReferences))
import Language.Drasil.Chunk.Attribute.References

--------------------------------------------------------------------------------
Expand All @@ -24,13 +25,8 @@ getSource c = sourceRef $ c ^. getReferences
sourceRef ((SourceRef x):xs) = x +:+ (sourceRef xs)
sourceRef (_:xs) = sourceRef xs

getDerivation :: HasAttributes c => c -> Derivation
getDerivation c = deriv $ c ^. attributes
where
deriv :: Attributes -> Derivation
deriv [] = []
deriv ((D der):_) = der
deriv (_:xs) = deriv xs
getDerivation :: HasDerivation c => c -> Derivation
getDerivation c = c ^. derivations

getShortName :: HasAttributes c => c -> Maybe Sentence
getShortName c = shortName $ c ^. attributes
Expand All @@ -46,6 +42,3 @@ shortname = ShortName
sourceref :: Sentence -> Reference
sourceref = SourceRef

derivationsteps :: Derivation -> Attribute
derivationsteps = D

5 changes: 1 addition & 4 deletions code/Language/Language/Drasil/Chunk/Attribute/Core.hs
Original file line number Diff line number Diff line change
Expand Up @@ -14,7 +14,4 @@ data Attribute =
ShortName String
-- | SourceRef Sentence -- Source to reference for this knowledge chunk
-- FIXME: Allow URLs/Citations here
| D Derivation -- Makes sense for now
--(derivations are just document sections at the moment),
-- but we may need to create a new representation for it in the future.
-- To collapse Attributes into QDefinitions, can't use Contents
| Uses [String] -- Which chunks does this one rely on?
4 changes: 2 additions & 2 deletions code/Language/Language/Drasil/Chunk/DefinedQuantity.hs
Original file line number Diff line number Diff line change
Expand Up @@ -6,7 +6,7 @@ module Language.Drasil.Chunk.DefinedQuantity

import Language.Drasil.Classes (HasUID(uid), NamedIdea(term), Idea(getA),
Definition(defn), ConceptDomain(cdom, DOM), Concept, HasSymbol(symbol),
HasAttributes(attributes), HasSpace(typ), IsUnit, HasDerivation(derivation))
HasAttributes(attributes), HasSpace(typ), IsUnit, HasDerivation(derivations))
import Language.Drasil.Chunk.Concept (ConceptChunk, cw)
import qualified Language.Drasil.Chunk.Quantity as Q

Expand Down Expand Up @@ -42,7 +42,7 @@ instance Q.HasSpace DefinedQuantityDict where typ = spa
instance HasSymbol DefinedQuantityDict where symbol = view symb
instance HasAttributes DefinedQuantityDict where attributes = attribs
instance Q.Quantity DefinedQuantityDict where getUnit = view unit'
instance HasDerivation DefinedQuantityDict where derivation = deri
instance HasDerivation DefinedQuantityDict where derivations = deri

-- For when the symbol is constant through stages
dqd :: ConceptChunk -> Symbol -> Space -> Maybe UnitDefn -> Attributes -> DefinedQuantityDict
Expand Down
5 changes: 3 additions & 2 deletions code/Language/Language/Drasil/Chunk/Eq.hs
Original file line number Diff line number Diff line change
Expand Up @@ -6,7 +6,8 @@ module Language.Drasil.Chunk.Eq
import Control.Lens ((^.), makeLenses)
import Language.Drasil.Expr (Expr)
import Language.Drasil.Classes (HasUID(uid),NamedIdea(term), Idea(getA), DOM,
HasSymbol(symbol), IsUnit, HasAttributes(attributes), ExprRelat(relat), HasReference(getReferences), HasDerivation(derivation))
HasSymbol(symbol), IsUnit, HasAttributes(attributes), ExprRelat(relat), HasDerivation(derivations),
HasReference(getReferences))
import Language.Drasil.Chunk.Attribute.Core (Attributes)
import Language.Drasil.Chunk.Attribute.References (References)
import Language.Drasil.Chunk.Concept (ConceptChunk)
Expand Down Expand Up @@ -41,7 +42,7 @@ instance ExprRelat QDefinition where relat = equat
instance HasAttributes QDefinition where attributes = qua . attributes
instance HasReference QDefinition where getReferences = ref
instance Eq QDefinition where a == b = (a ^. uid) == (b ^. uid)
instance HasDerivation QDefinition where derivation = deri
instance HasDerivation QDefinition where derivations = deri

-- | Create a 'QDefinition' with an uid, noun phrase (term), definition, symbol,
-- unit, and defining equation. And it ignores the definition...
Expand Down
16 changes: 10 additions & 6 deletions code/Language/Language/Drasil/Chunk/GenDefn.hs
Original file line number Diff line number Diff line change
Expand Up @@ -5,35 +5,39 @@ module Language.Drasil.Chunk.GenDefn

import Language.Drasil.Classes (HasUID(uid), NamedIdea(term), Idea(getA),
Definition(defn), ConceptDomain(cdom,DOM), Concept, IsUnit,
HasAttributes(attributes), HasReference(getReferences), ExprRelat(relat))
HasAttributes(attributes), ExprRelat(relat), HasDerivation(derivations),
HasReference(getReferences))
import Language.Drasil.Chunk.Attribute.Core (Attributes)
import Language.Drasil.Chunk.Attribute.References (References)
import Language.Drasil.Chunk.Concept (ConceptChunk)
import Language.Drasil.Chunk.Relation (RelationConcept)
import Language.Drasil.Unit (unitWrapper, UnitDefn)
import Language.Drasil.Chunk.Attribute.Derivation

import Control.Lens (makeLenses)

-- | A GenDefn is a RelationConcept that may have units
data GenDefn = GD { _relC :: RelationConcept
, gdUnit :: Maybe UnitDefn
, _attribs :: Attributes
, _deri :: Derivation
, _ref :: References
, _attribs :: Attributes
}
makeLenses ''GenDefn

instance HasUID GenDefn where uid = relC . uid
instance NamedIdea GenDefn where term = relC . term
instance Idea GenDefn where getA (GD a _ _ _) = getA a
instance Idea GenDefn where getA (GD a _ _ _ _) = getA a
instance Concept GenDefn where
instance Definition GenDefn where defn = relC . defn
instance ConceptDomain GenDefn where
type DOM GenDefn = ConceptChunk
cdom = relC . cdom
instance ExprRelat GenDefn where relat = relC . relat
instance HasDerivation GenDefn where derivations = deri
instance HasAttributes GenDefn where attributes = attribs
instance HasReference GenDefn where getReferences = ref

gd :: (IsUnit u, DOM u ~ ConceptChunk) => RelationConcept -> Maybe u -> Attributes -> GenDefn
gd r (Just u) ats = GD r (Just (unitWrapper u)) [] ats
gd r Nothing ats = GD r Nothing [] ats
gd :: (IsUnit u, DOM u ~ ConceptChunk) => RelationConcept -> Maybe u -> Derivation -> GenDefn
gd r (Just u) derivs = GD r (Just (unitWrapper u)) [] derivs []
gd r Nothing derivs = GD r Nothing [] derivs []
14 changes: 9 additions & 5 deletions code/Language/Language/Drasil/Chunk/InstanceModel.hs
Original file line number Diff line number Diff line change
Expand Up @@ -6,7 +6,8 @@ module Language.Drasil.Chunk.InstanceModel

import Language.Drasil.Classes (HasUID(uid), NamedIdea(term), Idea(getA),
Definition(defn),ConceptDomain(cdom,DOM), Concept, HasAttributes(attributes),
HasReference(getReferences), ExprRelat(relat))
ExprRelat(relat), HasDerivation(derivations),
HasReference(getReferences))
import Language.Drasil.Chunk.Attribute.Core (Attributes)
import Language.Drasil.Chunk.Attribute.References (References)
import Language.Drasil.Chunk.Concept
Expand All @@ -19,6 +20,7 @@ import Language.Drasil.Expr
import Language.Drasil.Expr.Math (sy)
import Language.Drasil.Expr.Extract (vars)
import Language.Drasil.Spec (Sentence)
import Language.Drasil.Chunk.Attribute.Derivation

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

Expand All @@ -37,28 +39,30 @@ data InstanceModel = IM { _rc :: RelationConcept
, _outCons :: OutputConstraints
, _ref :: References
, _attribs :: Attributes
, _deri :: Derivation
}
makeLenses ''InstanceModel

instance HasUID InstanceModel where uid = rc . uid
instance NamedIdea InstanceModel where term = rc . term
instance Idea InstanceModel where getA (IM a _ _ _ _ _ _) = getA a
instance Idea InstanceModel where getA (IM a _ _ _ _ _ _ _) = getA a
instance Concept InstanceModel where
instance Definition InstanceModel where defn = rc . defn
instance ConceptDomain InstanceModel where
type DOM InstanceModel = ConceptChunk
cdom = rc . cdom
instance ExprRelat InstanceModel where relat = rc . relat
instance HasAttributes InstanceModel where attributes = attribs
instance HasDerivation InstanceModel where derivations = deri
instance HasReference InstanceModel where getReferences = ref

-- | Smart constructor for instance models
im :: RelationConcept -> Inputs -> InputConstraints -> Output ->
OutputConstraints -> References -> Attributes -> InstanceModel
im = IM
OutputConstraints -> Attributes -> InstanceModel
im rc i ic o oc atts = IM rc i ic o oc [] atts []

-- | Smart constructor for instance model from qdefinition
-- (Sentence is the "concept" definition for the relation concept)
imQD :: HasSymbolTable ctx => ctx -> QDefinition -> Sentence -> InputConstraints -> OutputConstraints -> Attributes -> InstanceModel
imQD ctx qd dfn incon ocon atts = IM (makeRC (qd ^. uid) (qd ^. term) dfn
(sy qd $= qd ^. equat) atts) (vars (qd^.equat) ctx) incon (qw qd) ocon [] atts --FIXME: atts used twice?
(sy qd $= qd ^. equat) atts) (vars (qd^.equat) ctx) incon (qw qd) ocon [] atts []--FIXME: atts used twice?
4 changes: 2 additions & 2 deletions code/Language/Language/Drasil/Classes.hs
Original file line number Diff line number Diff line change
Expand Up @@ -18,7 +18,7 @@ module Language.Drasil.Classes (
, Constrained(constraints)
, HasReasVal(reasVal)
, ExprRelat(relat)
, HasDerivation(derivation)
, HasDerivation(derivations)
) where

import Language.Drasil.NounPhrase.Core (NP)
Expand Down Expand Up @@ -85,7 +85,7 @@ class HasReference c where
getReferences :: Lens' c References

class HasDerivation c where
derivation :: Lens' c Derivation
derivations :: Lens' c Derivation

-- | CommonIdea is a 'NamedIdea' with the additional
-- constraint that it __must__ have an abbreviation.
Expand Down

0 comments on commit 6c3386e

Please sign in to comment.