{-# Language TemplateHaskell #-}
module Language.Drasil.Reference (
Reference(Reference),
HasReference(..),
ref, refS, namedRef, complexRef, namedComplexRef
) where
import Language.Drasil.Label.Type (LblType, HasRefAddress(..))
import Language.Drasil.ShortName (HasShortName(..), ShortName)
import Language.Drasil.Sentence (Sentence(Ref, EmptyS), RefInfo(..))
import Language.Drasil.UID (UID, HasUID(..))
import Control.Lens ((^.), makeLenses, Lens')
data Reference = Reference
{ Reference -> UID
_ui :: UID
, Reference -> LblType
ra :: LblType
, Reference -> ShortName
sn :: ShortName}
makeLenses ''Reference
class HasReference c where
getReferences :: Lens' c [Reference]
instance Eq Reference where Reference
a == :: Reference -> Reference -> Bool
== Reference
b = (Reference
a forall s a. s -> Getting a s a -> a
^. forall c. HasUID c => Lens' c UID
uid) forall a. Eq a => a -> a -> Bool
== (Reference
b forall s a. s -> Getting a s a -> a
^. forall c. HasUID c => Lens' c UID
uid)
instance HasUID Reference where uid :: Lens' Reference UID
uid = Lens' Reference UID
ui
instance HasRefAddress Reference where getRefAdd :: Reference -> LblType
getRefAdd = Reference -> LblType
ra
instance HasShortName Reference where shortname :: Reference -> ShortName
shortname = Reference -> ShortName
sn
ref :: (HasUID r, HasRefAddress r, HasShortName r) => r -> Reference
ref :: forall r.
(HasUID r, HasRefAddress r, HasShortName r) =>
r -> Reference
ref r
r = UID -> LblType -> ShortName -> Reference
Reference (r
r forall s a. s -> Getting a s a -> a
^. forall c. HasUID c => Lens' c UID
uid) (forall b. HasRefAddress b => b -> LblType
getRefAdd r
r) (forall s. HasShortName s => s -> ShortName
shortname r
r)
refS :: (HasUID r, HasRefAddress r, HasShortName r) => r -> Sentence
refS :: forall r.
(HasUID r, HasRefAddress r, HasShortName r) =>
r -> Sentence
refS r
r = forall r.
(HasUID r, HasRefAddress r, HasShortName r) =>
r -> Sentence -> Sentence
namedRef r
r Sentence
EmptyS
namedRef :: (HasUID r, HasRefAddress r, HasShortName r) => r -> Sentence -> Sentence
namedRef :: forall r.
(HasUID r, HasRefAddress r, HasShortName r) =>
r -> Sentence -> Sentence
namedRef r
r Sentence
s = forall r.
(HasUID r, HasRefAddress r, HasShortName r) =>
r -> Sentence -> RefInfo -> Sentence
namedComplexRef r
r Sentence
s RefInfo
None
complexRef :: (HasUID r, HasRefAddress r, HasShortName r) => r -> RefInfo -> Sentence
complexRef :: forall r.
(HasUID r, HasRefAddress r, HasShortName r) =>
r -> RefInfo -> Sentence
complexRef r
r = UID -> Sentence -> RefInfo -> Sentence
Ref (forall r.
(HasUID r, HasRefAddress r, HasShortName r) =>
r -> Reference
ref r
r forall s a. s -> Getting a s a -> a
^. forall c. HasUID c => Lens' c UID
uid) Sentence
EmptyS
namedComplexRef :: (HasUID r, HasRefAddress r, HasShortName r) => r -> Sentence -> RefInfo -> Sentence
namedComplexRef :: forall r.
(HasUID r, HasRefAddress r, HasShortName r) =>
r -> Sentence -> RefInfo -> Sentence
namedComplexRef r
r = UID -> Sentence -> RefInfo -> Sentence
Ref (forall r.
(HasUID r, HasRefAddress r, HasShortName r) =>
r -> Reference
ref r
r forall s a. s -> Getting a s a -> a
^. forall c. HasUID c => Lens' c UID
uid)