{-# Language TemplateHaskell #-}
-- | Define concept-related chunks. A concept is usually something that has
-- a term, definition, and comes from some domain of knowledge.
module Language.Drasil.Chunk.Concept.Core(
  -- * Concept-related Datatypes
  ConceptChunk(ConDict)
  , ConceptInstance(ConInst)
  , sDom)
  where
import Language.Drasil.ShortName (HasShortName(..), ShortName)
import Language.Drasil.Classes (NamedIdea(term), Idea(getA),
  Definition(defn), ConceptDomain(cdom))
import Language.Drasil.Chunk.NamedIdea (IdeaDict)
import Language.Drasil.Label.Type ((+::+), defer, name, raw,
  LblType(..), Referable(..), HasRefAddress(..))
import Language.Drasil.Sentence (Sentence)
import Language.Drasil.UID (UID, HasUID(..))

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

-- | Check if something has one domain. Throws an error if there is more than one.
sDom :: [UID] -> UID
sDom :: [UID] -> UID
sDom [UID
d] = UID
d
sDom [UID]
d = forall a. HasCallStack => [Char] -> a
error forall a b. (a -> b) -> a -> b
$ [Char]
"Expected ConceptDomain to have a single domain, found " forall a. [a] -> [a] -> [a]
++
  forall a. Show a => a -> [Char]
show (forall (t :: * -> *) a. Foldable t => t a -> Int
length [UID]
d) forall a. [a] -> [a] -> [a]
++ [Char]
" instead."

-- | The ConceptChunk datatype records a concept that contains an idea ('IdeaDict'),
-- a definition ('Sentence'), and an associated domain of knowledge (['UID']).
--
-- Ex. The concept of "Accuracy" may be defined as the quality or state of being correct or precise.
data ConceptChunk = ConDict { ConceptChunk -> IdeaDict
_idea :: IdeaDict -- ^ Contains the idea of the concept.
                            , ConceptChunk -> Sentence
_defn' :: Sentence -- ^ The definition of the concept.
                            , ConceptChunk -> [UID]
cdom' :: [UID] -- ^ Domain of the concept.
                            }
makeLenses ''ConceptChunk

-- | Equal if 'UID's are equal.
instance Eq            ConceptChunk where ConceptChunk
c1 == :: ConceptChunk -> ConceptChunk -> Bool
== ConceptChunk
c2 = (ConceptChunk
c1 forall s a. s -> Getting a s a -> a
^. forall c. HasUID c => Lens' c UID
uid) forall a. Eq a => a -> a -> Bool
== (ConceptChunk
c2 forall s a. s -> Getting a s a -> a
^. forall c. HasUID c => Lens' c UID
uid)
-- | Finds 'UID' of the 'IdeaDict' used to make the 'ConceptChunk'.
instance HasUID        ConceptChunk where uid :: Lens' ConceptChunk UID
uid = Lens' ConceptChunk IdeaDict
idea forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall c. HasUID c => Lens' c UID
uid
-- | Finds term ('NP') of the 'IdeaDict' used to make the 'ConceptChunk'.
instance NamedIdea     ConceptChunk where term :: Lens' ConceptChunk NP
term = Lens' ConceptChunk IdeaDict
idea forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall c. NamedIdea c => Lens' c NP
term
-- | Finds the idea contained in the 'IdeaDict' used to make the 'ConceptChunk'.
instance Idea          ConceptChunk where getA :: ConceptChunk -> Maybe [Char]
getA = forall c. Idea c => c -> Maybe [Char]
getA forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall s (m :: * -> *) a. MonadReader s m => Getting a s a -> m a
view Lens' ConceptChunk IdeaDict
idea
-- | Finds definition of a 'ConceptChunk'.
instance Definition    ConceptChunk where defn :: Lens' ConceptChunk Sentence
defn = Lens' ConceptChunk Sentence
defn'
-- | Finds the domain of 'UID's of a 'ConceptChunk'.
instance ConceptDomain ConceptChunk where cdom :: ConceptChunk -> [UID]
cdom = ConceptChunk -> [UID]
cdom'

-- | Contains a 'ConceptChunk', reference address, and a 'ShortName'.
-- It is a concept that can be referred to, or rather, a instance of where a concept is applied.
-- Often used in Goal Statements, Assumptions, Requirements, etc.
--
-- Ex. Something like the assumption that gravity is 9.81 m/s. When we write our equations,
-- we can then link this assumption so that we do not have to explicitly define
-- that assumption when needed to verify our work.
data ConceptInstance = ConInst { ConceptInstance -> ConceptChunk
_cc :: ConceptChunk , ConceptInstance -> [Char]
ra :: String, ConceptInstance -> ShortName
shnm :: ShortName}
makeLenses ''ConceptInstance

-- | Equal if 'UID's are equal.
instance Eq            ConceptInstance where ConceptInstance
c1 == :: ConceptInstance -> ConceptInstance -> Bool
== ConceptInstance
c2 = (ConceptInstance
c1 forall s a. s -> Getting a s a -> a
^. forall c. HasUID c => Lens' c UID
uid) forall a. Eq a => a -> a -> Bool
== (ConceptInstance
c2 forall s a. s -> Getting a s a -> a
^. forall c. HasUID c => Lens' c UID
uid)
-- | Finds 'UID' of the 'ConceptChunk' used to make the 'ConceptInstance'.
instance HasUID        ConceptInstance where uid :: Lens' ConceptInstance UID
uid = Lens' ConceptInstance ConceptChunk
cc forall b c a. (b -> c) -> (a -> b) -> a -> c
. Lens' ConceptChunk IdeaDict
idea forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall c. HasUID c => Lens' c UID
uid
-- | Finds term ('NP') of the 'ConceptChunk' used to make the 'ConceptInstance'.
instance NamedIdea     ConceptInstance where term :: Lens' ConceptInstance NP
term = Lens' ConceptInstance ConceptChunk
cc forall b c a. (b -> c) -> (a -> b) -> a -> c
. Lens' ConceptChunk IdeaDict
idea forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall c. NamedIdea c => Lens' c NP
term
-- | Finds the idea contained in the 'ConceptChunk' used to make the 'ConceptInstance'.
instance Idea          ConceptInstance where getA :: ConceptInstance -> Maybe [Char]
getA = forall c. Idea c => c -> Maybe [Char]
getA forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall s (m :: * -> *) a. MonadReader s m => Getting a s a -> m a
view (Lens' ConceptInstance ConceptChunk
cc forall b c a. (b -> c) -> (a -> b) -> a -> c
. Lens' ConceptChunk IdeaDict
idea)
-- | Finds the definition contained in the 'ConceptChunk' used to make the 'ConceptInstance'.
instance Definition    ConceptInstance where defn :: Lens' ConceptInstance Sentence
defn = Lens' ConceptInstance ConceptChunk
cc forall b c a. (b -> c) -> (a -> b) -> a -> c
. Lens' ConceptChunk Sentence
defn'
-- | Finds the domain contained in the 'ConceptChunk' used to make the 'ConceptInstance'.
instance ConceptDomain ConceptInstance where cdom :: ConceptInstance -> [UID]
cdom = ConceptChunk -> [UID]
cdom' forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall s (m :: * -> *) a. MonadReader s m => Getting a s a -> m a
view Lens' ConceptInstance ConceptChunk
cc
-- | Finds the 'ShortName' contained in a 'ConceptInstance'.
instance HasShortName  ConceptInstance where shortname :: ConceptInstance -> ShortName
shortname = ConceptInstance -> ShortName
shnm
-- | Finds the reference address contained in a 'ConceptInstance'.
instance HasRefAddress ConceptInstance where getRefAdd :: ConceptInstance -> LblType
getRefAdd ConceptInstance
l = IRefProg -> [Char] -> LblType
RP (UID -> IRefProg
defer ([UID] -> UID
sDom forall a b. (a -> b) -> a -> b
$ forall c. ConceptDomain c => c -> [UID]
cdom ConceptInstance
l) IRefProg -> IRefProg -> IRefProg
+::+ [Char] -> IRefProg
raw [Char]
":" IRefProg -> IRefProg -> IRefProg
+::+ IRefProg
name) (ConceptInstance -> [Char]
ra ConceptInstance
l)
-- | Finds the reference information contained in a 'ConceptInstance'.
instance Referable     ConceptInstance where
  refAdd :: ConceptInstance -> [Char]
refAdd      = ConceptInstance -> [Char]
ra        -- Finds the reference address contained in a ConceptInstance.
  renderRef :: ConceptInstance -> LblType
renderRef   = forall b. HasRefAddress b => b -> LblType
getRefAdd -- Finds the reference address but in a diferent form.