{-# LANGUAGE TemplateHaskell #-}
module Language.Drasil.Chunk.DefinedQuantity (
DefinedQuantityDict,
dqd, dqdNoUnit, dqd',
dqdQd, dqdWr, tempdqdWr') where
import Language.Drasil.Symbol (HasSymbol(symbol), Symbol)
import Language.Drasil.Classes (NamedIdea(term), Idea(getA), Concept, Express(..),
Definition(defn), ConceptDomain(cdom), IsUnit, Quantity)
import Language.Drasil.Chunk.Concept (ConceptChunk, cw)
import Language.Drasil.Expr.Class (sy)
import Language.Drasil.Chunk.UnitDefn (UnitDefn, unitWrapper,
MayHaveUnit(getUnit))
import Language.Drasil.Space (Space, HasSpace(..))
import Language.Drasil.Stages (Stage)
import Language.Drasil.UID (HasUID(uid))
import Control.Lens ((^.), makeLenses, view)
data DefinedQuantityDict = DQD { DefinedQuantityDict -> ConceptChunk
_con :: ConceptChunk
, DefinedQuantityDict -> Stage -> Symbol
_symb :: Stage -> Symbol
, DefinedQuantityDict -> Space
_spa :: Space
, DefinedQuantityDict -> Maybe UnitDefn
_unit' :: Maybe UnitDefn
}
makeLenses ''DefinedQuantityDict
instance HasUID DefinedQuantityDict where uid :: Getter DefinedQuantityDict UID
uid = (ConceptChunk -> f ConceptChunk)
-> DefinedQuantityDict -> f DefinedQuantityDict
Lens' DefinedQuantityDict ConceptChunk
con ((ConceptChunk -> f ConceptChunk)
-> DefinedQuantityDict -> f DefinedQuantityDict)
-> ((UID -> f UID) -> ConceptChunk -> f ConceptChunk)
-> (UID -> f UID)
-> DefinedQuantityDict
-> f DefinedQuantityDict
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 DefinedQuantityDict where DefinedQuantityDict
a == :: DefinedQuantityDict -> DefinedQuantityDict -> Bool
== DefinedQuantityDict
b = (DefinedQuantityDict
a DefinedQuantityDict -> Getting UID DefinedQuantityDict UID -> UID
forall s a. s -> Getting a s a -> a
^. Getting UID DefinedQuantityDict UID
forall c. HasUID c => Getter c UID
Getter DefinedQuantityDict UID
uid) UID -> UID -> Bool
forall a. Eq a => a -> a -> Bool
== (DefinedQuantityDict
b DefinedQuantityDict -> Getting UID DefinedQuantityDict UID -> UID
forall s a. s -> Getting a s a -> a
^. Getting UID DefinedQuantityDict UID
forall c. HasUID c => Getter c UID
Getter DefinedQuantityDict UID
uid)
instance NamedIdea DefinedQuantityDict where term :: Lens' DefinedQuantityDict NP
term = (ConceptChunk -> f ConceptChunk)
-> DefinedQuantityDict -> f DefinedQuantityDict
Lens' DefinedQuantityDict ConceptChunk
con ((ConceptChunk -> f ConceptChunk)
-> DefinedQuantityDict -> f DefinedQuantityDict)
-> ((NP -> f NP) -> ConceptChunk -> f ConceptChunk)
-> (NP -> f NP)
-> DefinedQuantityDict
-> f DefinedQuantityDict
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 DefinedQuantityDict where getA :: DefinedQuantityDict -> Maybe String
getA = ConceptChunk -> Maybe String
forall c. Idea c => c -> Maybe String
getA (ConceptChunk -> Maybe String)
-> (DefinedQuantityDict -> ConceptChunk)
-> DefinedQuantityDict
-> Maybe String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Getting ConceptChunk DefinedQuantityDict ConceptChunk
-> DefinedQuantityDict -> ConceptChunk
forall s (m :: * -> *) a. MonadReader s m => Getting a s a -> m a
view Getting ConceptChunk DefinedQuantityDict ConceptChunk
Lens' DefinedQuantityDict ConceptChunk
con
instance Definition DefinedQuantityDict where defn :: Lens' DefinedQuantityDict Sentence
defn = (ConceptChunk -> f ConceptChunk)
-> DefinedQuantityDict -> f DefinedQuantityDict
Lens' DefinedQuantityDict ConceptChunk
con ((ConceptChunk -> f ConceptChunk)
-> DefinedQuantityDict -> f DefinedQuantityDict)
-> ((Sentence -> f Sentence) -> ConceptChunk -> f ConceptChunk)
-> (Sentence -> f Sentence)
-> DefinedQuantityDict
-> f DefinedQuantityDict
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 DefinedQuantityDict where cdom :: DefinedQuantityDict -> [UID]
cdom = ConceptChunk -> [UID]
forall c. ConceptDomain c => c -> [UID]
cdom (ConceptChunk -> [UID])
-> (DefinedQuantityDict -> ConceptChunk)
-> DefinedQuantityDict
-> [UID]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Getting ConceptChunk DefinedQuantityDict ConceptChunk
-> DefinedQuantityDict -> ConceptChunk
forall s (m :: * -> *) a. MonadReader s m => Getting a s a -> m a
view Getting ConceptChunk DefinedQuantityDict ConceptChunk
Lens' DefinedQuantityDict ConceptChunk
con
instance HasSpace DefinedQuantityDict where typ :: Getter DefinedQuantityDict Space
typ = (Space -> f Space) -> DefinedQuantityDict -> f DefinedQuantityDict
Lens' DefinedQuantityDict Space
spa
instance HasSymbol DefinedQuantityDict where symbol :: DefinedQuantityDict -> Stage -> Symbol
symbol = Getting (Stage -> Symbol) DefinedQuantityDict (Stage -> Symbol)
-> DefinedQuantityDict -> Stage -> Symbol
forall s (m :: * -> *) a. MonadReader s m => Getting a s a -> m a
view Getting (Stage -> Symbol) DefinedQuantityDict (Stage -> Symbol)
Lens' DefinedQuantityDict (Stage -> Symbol)
symb
instance Quantity DefinedQuantityDict where
instance MayHaveUnit DefinedQuantityDict where getUnit :: DefinedQuantityDict -> Maybe UnitDefn
getUnit = Getting (Maybe UnitDefn) DefinedQuantityDict (Maybe UnitDefn)
-> DefinedQuantityDict -> Maybe UnitDefn
forall s (m :: * -> *) a. MonadReader s m => Getting a s a -> m a
view Getting (Maybe UnitDefn) DefinedQuantityDict (Maybe UnitDefn)
Lens' DefinedQuantityDict (Maybe UnitDefn)
unit'
instance Express DefinedQuantityDict where express :: DefinedQuantityDict -> ModelExpr
express = DefinedQuantityDict -> ModelExpr
forall c. (HasUID c, HasSymbol c) => c -> ModelExpr
forall r c. (ExprC r, HasUID c, HasSymbol c) => c -> r
sy
dqd :: (IsUnit u) => ConceptChunk -> Symbol -> Space -> u -> DefinedQuantityDict
dqd :: forall u.
IsUnit u =>
ConceptChunk -> Symbol -> Space -> u -> DefinedQuantityDict
dqd ConceptChunk
c Symbol
s Space
sp = ConceptChunk
-> (Stage -> Symbol)
-> Space
-> Maybe UnitDefn
-> DefinedQuantityDict
DQD ConceptChunk
c (Symbol -> Stage -> Symbol
forall a b. a -> b -> a
const Symbol
s) Space
sp (Maybe UnitDefn -> DefinedQuantityDict)
-> (u -> Maybe UnitDefn) -> u -> DefinedQuantityDict
forall b c a. (b -> c) -> (a -> b) -> a -> c
. UnitDefn -> Maybe UnitDefn
forall a. a -> Maybe a
Just (UnitDefn -> Maybe UnitDefn)
-> (u -> UnitDefn) -> u -> Maybe UnitDefn
forall b c a. (b -> c) -> (a -> b) -> a -> c
. u -> UnitDefn
forall u. IsUnit u => u -> UnitDefn
unitWrapper
dqdNoUnit :: ConceptChunk -> Symbol -> Space -> DefinedQuantityDict
dqdNoUnit :: ConceptChunk -> Symbol -> Space -> DefinedQuantityDict
dqdNoUnit ConceptChunk
c Symbol
s Space
sp = ConceptChunk
-> (Stage -> Symbol)
-> Space
-> Maybe UnitDefn
-> DefinedQuantityDict
DQD ConceptChunk
c (Symbol -> Stage -> Symbol
forall a b. a -> b -> a
const Symbol
s) Space
sp Maybe UnitDefn
forall a. Maybe a
Nothing
dqd' :: ConceptChunk -> (Stage -> Symbol) -> Space -> Maybe UnitDefn -> DefinedQuantityDict
dqd' :: ConceptChunk
-> (Stage -> Symbol)
-> Space
-> Maybe UnitDefn
-> DefinedQuantityDict
dqd' = ConceptChunk
-> (Stage -> Symbol)
-> Space
-> Maybe UnitDefn
-> DefinedQuantityDict
DQD
dqdWr :: (Quantity c, Concept c, MayHaveUnit c) => c -> DefinedQuantityDict
dqdWr :: forall c.
(Quantity c, Concept c, MayHaveUnit c) =>
c -> DefinedQuantityDict
dqdWr c
c = ConceptChunk
-> (Stage -> Symbol)
-> Space
-> Maybe UnitDefn
-> DefinedQuantityDict
DQD (c -> ConceptChunk
forall c. Concept c => c -> ConceptChunk
cw c
c) (c -> Stage -> Symbol
forall c. HasSymbol c => c -> Stage -> Symbol
symbol c
c) (c
c c -> Getting Space c Space -> Space
forall s a. s -> Getting a s a -> a
^. Getting Space c Space
forall c. HasSpace c => Getter c Space
Getter c Space
typ) (c -> Maybe UnitDefn
forall u. MayHaveUnit u => u -> Maybe UnitDefn
getUnit c
c)
tempdqdWr' :: (Quantity c, Concept c, MayHaveUnit c) => c -> DefinedQuantityDict
tempdqdWr' :: forall c.
(Quantity c, Concept c, MayHaveUnit c) =>
c -> DefinedQuantityDict
tempdqdWr' c
c = ConceptChunk
-> (Stage -> Symbol)
-> Space
-> Maybe UnitDefn
-> DefinedQuantityDict
DQD (c -> ConceptChunk
forall c. Concept c => c -> ConceptChunk
cw c
c) (c -> Stage -> Symbol
forall c. HasSymbol c => c -> Stage -> Symbol
symbol c
c) (c
c c -> Getting Space c Space -> Space
forall s a. s -> Getting a s a -> a
^. Getting Space c Space
forall c. HasSpace c => Getter c Space
Getter c Space
typ) (c -> Maybe UnitDefn
forall u. MayHaveUnit u => u -> Maybe UnitDefn
getUnit c
c)
dqdQd :: (Quantity c, MayHaveUnit c) => c -> ConceptChunk -> DefinedQuantityDict
dqdQd :: forall c.
(Quantity c, MayHaveUnit c) =>
c -> ConceptChunk -> DefinedQuantityDict
dqdQd c
c ConceptChunk
cc = ConceptChunk
-> (Stage -> Symbol)
-> Space
-> Maybe UnitDefn
-> DefinedQuantityDict
DQD ConceptChunk
cc (c -> Stage -> Symbol
forall c. HasSymbol c => c -> Stage -> Symbol
symbol c
c) (c
c c -> Getting Space c Space -> Space
forall s a. s -> Getting a s a -> a
^. Getting Space c Space
forall c. HasSpace c => Getter c Space
Getter c Space
typ) (c -> Maybe UnitDefn
forall u. MayHaveUnit u => u -> Maybe UnitDefn
getUnit c
c)