{-# LANGUAGE TemplateHaskell #-}
module Language.Drasil.Chunk.NamedArgument (
NamedArgument(..),
narg) where
import Language.Drasil (QuantityDict, HasSpace(..), HasSymbol(..), HasUID(..),
Idea(..), MayHaveUnit(..), NamedIdea(..), Quantity, qw, IsArgumentName)
import Control.Lens ((^.), makeLenses, view)
newtype NamedArgument = NA {NamedArgument -> QuantityDict
_qtd :: QuantityDict}
makeLenses ''NamedArgument
instance HasUID NamedArgument where uid :: Getter NamedArgument UID
uid = (QuantityDict -> f QuantityDict)
-> NamedArgument -> f NamedArgument
Iso' NamedArgument QuantityDict
qtd ((QuantityDict -> f QuantityDict)
-> NamedArgument -> f NamedArgument)
-> ((UID -> f UID) -> QuantityDict -> f QuantityDict)
-> (UID -> f UID)
-> NamedArgument
-> f NamedArgument
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (UID -> f UID) -> QuantityDict -> f QuantityDict
forall c. HasUID c => Getter c UID
Getter QuantityDict UID
uid
instance NamedIdea NamedArgument where term :: Lens' NamedArgument NP
term = (QuantityDict -> f QuantityDict)
-> NamedArgument -> f NamedArgument
Iso' NamedArgument QuantityDict
qtd ((QuantityDict -> f QuantityDict)
-> NamedArgument -> f NamedArgument)
-> ((NP -> f NP) -> QuantityDict -> f QuantityDict)
-> (NP -> f NP)
-> NamedArgument
-> f NamedArgument
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (NP -> f NP) -> QuantityDict -> f QuantityDict
forall c. NamedIdea c => Lens' c NP
Lens' QuantityDict NP
term
instance Idea NamedArgument where getA :: NamedArgument -> Maybe String
getA = QuantityDict -> Maybe String
forall c. Idea c => c -> Maybe String
getA (QuantityDict -> Maybe String)
-> (NamedArgument -> QuantityDict) -> NamedArgument -> Maybe String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Getting QuantityDict NamedArgument QuantityDict
-> NamedArgument -> QuantityDict
forall s (m :: * -> *) a. MonadReader s m => Getting a s a -> m a
view Getting QuantityDict NamedArgument QuantityDict
Iso' NamedArgument QuantityDict
qtd
instance HasSpace NamedArgument where typ :: Getter NamedArgument Space
typ = (QuantityDict -> f QuantityDict)
-> NamedArgument -> f NamedArgument
Iso' NamedArgument QuantityDict
qtd ((QuantityDict -> f QuantityDict)
-> NamedArgument -> f NamedArgument)
-> ((Space -> f Space) -> QuantityDict -> f QuantityDict)
-> (Space -> f Space)
-> NamedArgument
-> f NamedArgument
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Space -> f Space) -> QuantityDict -> f QuantityDict
forall c. HasSpace c => Getter c Space
Getter QuantityDict Space
typ
instance HasSymbol NamedArgument where symbol :: NamedArgument -> Stage -> Symbol
symbol = QuantityDict -> Stage -> Symbol
forall c. HasSymbol c => c -> Stage -> Symbol
symbol (QuantityDict -> Stage -> Symbol)
-> (NamedArgument -> QuantityDict)
-> NamedArgument
-> Stage
-> Symbol
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Getting QuantityDict NamedArgument QuantityDict
-> NamedArgument -> QuantityDict
forall s (m :: * -> *) a. MonadReader s m => Getting a s a -> m a
view Getting QuantityDict NamedArgument QuantityDict
Iso' NamedArgument QuantityDict
qtd
instance Quantity NamedArgument where
instance IsArgumentName NamedArgument where
instance Eq NamedArgument where NamedArgument
a == :: NamedArgument -> NamedArgument -> Bool
== NamedArgument
b = (NamedArgument
a NamedArgument -> Getting UID NamedArgument UID -> UID
forall s a. s -> Getting a s a -> a
^. Getting UID NamedArgument UID
forall c. HasUID c => Getter c UID
Getter NamedArgument UID
uid) UID -> UID -> Bool
forall a. Eq a => a -> a -> Bool
== (NamedArgument
b NamedArgument -> Getting UID NamedArgument UID -> UID
forall s a. s -> Getting a s a -> a
^. Getting UID NamedArgument UID
forall c. HasUID c => Getter c UID
Getter NamedArgument UID
uid)
instance MayHaveUnit NamedArgument where getUnit :: NamedArgument -> Maybe UnitDefn
getUnit = QuantityDict -> Maybe UnitDefn
forall u. MayHaveUnit u => u -> Maybe UnitDefn
getUnit (QuantityDict -> Maybe UnitDefn)
-> (NamedArgument -> QuantityDict)
-> NamedArgument
-> Maybe UnitDefn
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Getting QuantityDict NamedArgument QuantityDict
-> NamedArgument -> QuantityDict
forall s (m :: * -> *) a. MonadReader s m => Getting a s a -> m a
view Getting QuantityDict NamedArgument QuantityDict
Iso' NamedArgument QuantityDict
qtd
narg :: (Quantity q, MayHaveUnit q) => q -> NamedArgument
narg :: forall q. (Quantity q, MayHaveUnit q) => q -> NamedArgument
narg = QuantityDict -> NamedArgument
NA (QuantityDict -> NamedArgument)
-> (q -> QuantityDict) -> q -> NamedArgument
forall b c a. (b -> c) -> (a -> b) -> a -> c
. q -> QuantityDict
forall q. (Quantity q, MayHaveUnit q) => q -> QuantityDict
qw