{-# LANGUAGE TemplateHaskell #-}
module Language.Drasil.Chunk.Relation (
RelationConcept,
makeRC) where
import Control.Lens (makeLenses, (^.), view)
import Language.Drasil.Chunk.Concept (ConceptChunk, dccWDS)
import Language.Drasil.Classes (Express(..),
ConceptDomain(..), Definition(..), Idea(..), NamedIdea(..))
import Language.Drasil.ModelExpr.Lang (ModelExpr)
import Language.Drasil.NounPhrase.Core (NP)
import Language.Drasil.Sentence (Sentence)
import Language.Drasil.UID (HasUID(..))
data RelationConcept = RC { RelationConcept -> ConceptChunk
_conc :: ConceptChunk
, RelationConcept -> ModelExpr
_rel :: ModelExpr
}
makeLenses ''RelationConcept
instance HasUID RelationConcept where uid :: Getter RelationConcept UID
uid = (ConceptChunk -> f ConceptChunk)
-> RelationConcept -> f RelationConcept
Lens' RelationConcept ConceptChunk
conc ((ConceptChunk -> f ConceptChunk)
-> RelationConcept -> f RelationConcept)
-> ((UID -> f UID) -> ConceptChunk -> f ConceptChunk)
-> (UID -> f UID)
-> RelationConcept
-> f RelationConcept
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (UID -> f UID) -> ConceptChunk -> f ConceptChunk
forall c. HasUID c => Getter c UID
Getter ConceptChunk UID
uid
instance Eq RelationConcept where RelationConcept
a == :: RelationConcept -> RelationConcept -> Bool
== RelationConcept
b = (RelationConcept
a RelationConcept -> Getting UID RelationConcept UID -> UID
forall s a. s -> Getting a s a -> a
^. Getting UID RelationConcept UID
forall c. HasUID c => Getter c UID
Getter RelationConcept UID
uid) UID -> UID -> Bool
forall a. Eq a => a -> a -> Bool
== (RelationConcept
b RelationConcept -> Getting UID RelationConcept UID -> UID
forall s a. s -> Getting a s a -> a
^. Getting UID RelationConcept UID
forall c. HasUID c => Getter c UID
Getter RelationConcept UID
uid)
instance NamedIdea RelationConcept where term :: Lens' RelationConcept NP
term = (ConceptChunk -> f ConceptChunk)
-> RelationConcept -> f RelationConcept
Lens' RelationConcept ConceptChunk
conc ((ConceptChunk -> f ConceptChunk)
-> RelationConcept -> f RelationConcept)
-> ((NP -> f NP) -> ConceptChunk -> f ConceptChunk)
-> (NP -> f NP)
-> RelationConcept
-> f RelationConcept
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (NP -> f NP) -> ConceptChunk -> f ConceptChunk
forall c. NamedIdea c => Lens' c NP
Lens' ConceptChunk NP
term
instance Idea RelationConcept where getA :: RelationConcept -> Maybe String
getA = ConceptChunk -> Maybe String
forall c. Idea c => c -> Maybe String
getA (ConceptChunk -> Maybe String)
-> (RelationConcept -> ConceptChunk)
-> RelationConcept
-> Maybe String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Getting ConceptChunk RelationConcept ConceptChunk
-> RelationConcept -> ConceptChunk
forall s (m :: * -> *) a. MonadReader s m => Getting a s a -> m a
view Getting ConceptChunk RelationConcept ConceptChunk
Lens' RelationConcept ConceptChunk
conc
instance Definition RelationConcept where defn :: Lens' RelationConcept Sentence
defn = (ConceptChunk -> f ConceptChunk)
-> RelationConcept -> f RelationConcept
Lens' RelationConcept ConceptChunk
conc ((ConceptChunk -> f ConceptChunk)
-> RelationConcept -> f RelationConcept)
-> ((Sentence -> f Sentence) -> ConceptChunk -> f ConceptChunk)
-> (Sentence -> f Sentence)
-> RelationConcept
-> f RelationConcept
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Sentence -> f Sentence) -> ConceptChunk -> f ConceptChunk
forall c. Definition c => Lens' c Sentence
Lens' ConceptChunk Sentence
defn
instance ConceptDomain RelationConcept where cdom :: RelationConcept -> [UID]
cdom = ConceptChunk -> [UID]
forall c. ConceptDomain c => c -> [UID]
cdom (ConceptChunk -> [UID])
-> (RelationConcept -> ConceptChunk) -> RelationConcept -> [UID]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Getting ConceptChunk RelationConcept ConceptChunk
-> RelationConcept -> ConceptChunk
forall s (m :: * -> *) a. MonadReader s m => Getting a s a -> m a
view Getting ConceptChunk RelationConcept ConceptChunk
Lens' RelationConcept ConceptChunk
conc
instance Express RelationConcept where express :: RelationConcept -> ModelExpr
express = (RelationConcept
-> Getting ModelExpr RelationConcept ModelExpr -> ModelExpr
forall s a. s -> Getting a s a -> a
^. Getting ModelExpr RelationConcept ModelExpr
Lens' RelationConcept ModelExpr
rel)
makeRC :: Express e => String -> NP -> Sentence -> e -> RelationConcept
makeRC :: forall e.
Express e =>
String -> NP -> Sentence -> e -> RelationConcept
makeRC String
rID NP
rTerm Sentence
rDefn = ConceptChunk -> ModelExpr -> RelationConcept
RC (String -> NP -> Sentence -> ConceptChunk
dccWDS String
rID NP
rTerm Sentence
rDefn) (ModelExpr -> RelationConcept)
-> (e -> ModelExpr) -> e -> RelationConcept
forall b c a. (b -> c) -> (a -> b) -> a -> c
. e -> ModelExpr
forall c. Express c => c -> ModelExpr
express