#ifdef __GLASGOW_HASKELL__
# if __GLASGOW_HASKELL__ >= 704
# endif
#if defined(__GLASGOW_HASKELL__) && __GLASGOW_HASKELL__ >= 702
#endif
#endif
module Bound.Name
( Name(..)
, _Name
, name
, abstractName
, abstract1Name
, instantiateName
, instantiate1Name
) where
import Bound.Scope
import Bound.Var
import Control.Applicative
import Control.Comonad
import Control.Monad (liftM, liftM2)
import Data.Foldable
import Data.Traversable
import Data.Monoid
import Data.Bifunctor
import Data.Bifoldable
import qualified Data.Binary as Binary
import Data.Binary (Binary)
import Data.Bitraversable
import Data.Bytes.Serial
#ifdef __GLASGOW_HASKELL__
import Data.Data
# if __GLASGOW_HASKELL__ >= 704
import GHC.Generics
# endif
#endif
import Data.Hashable
import Data.Hashable.Extras
import Data.Profunctor
import qualified Data.Serialize as Serialize
import Data.Serialize (Serialize)
import Prelude.Extras
data Name n b = Name n b deriving
( Show
, Read
#ifdef __GLASGOW_HASKELL__
, Typeable
, Data
# if __GLASGOW_HASKELL__ >= 704
, Generic
# endif
#endif
)
name :: Name n b -> n
name (Name n _) = n
_Name :: (Profunctor p, Functor f) => p (n, a) (f (m,b)) -> p (Name n a) (f (Name m b))
_Name = dimap (\(Name n a) -> (n, a)) (fmap (uncurry Name))
instance Eq b => Eq (Name n b) where
Name _ a == Name _ b = a == b
instance Hashable2 Name where
hashWithSalt2 m (Name _ a) = hashWithSalt m a
instance Hashable1 (Name n) where
hashWithSalt1 m (Name _ a) = hashWithSalt m a
instance Hashable a => Hashable (Name n a) where
hashWithSalt m (Name _ a) = hashWithSalt m a
instance Ord b => Ord (Name n b) where
Name _ a `compare` Name _ b = compare a b
instance Functor (Name n) where
fmap f (Name n a) = Name n (f a)
instance Foldable (Name n) where
foldMap f (Name _ a) = f a
instance Traversable (Name n) where
traverse f (Name n a) = Name n <$> f a
instance Bifunctor Name where
bimap f g (Name n a) = Name (f n) (g a)
instance Bifoldable Name where
bifoldMap f g (Name n a) = f n `mappend` g a
instance Bitraversable Name where
bitraverse f g (Name n a) = Name <$> f n <*> g a
instance Comonad (Name n) where
extract (Name _ b) = b
extend f w@(Name n _) = Name n (f w)
instance Eq1 (Name b) where
(==#) = (==)
instance Ord1 (Name b) where
compare1 = compare
instance Show b => Show1 (Name b) where showsPrec1 = showsPrec
instance Read b => Read1 (Name b) where readsPrec1 = readsPrec
instance Eq2 Name where
(==##) = (==)
instance Ord2 Name where
compare2 = compare
instance Show2 Name where showsPrec2 = showsPrec
instance Read2 Name where readsPrec2 = readsPrec
instance Serial2 Name where
serializeWith2 pb pf (Name b a) = pb b >> pf a
deserializeWith2 = liftM2 Name
instance Serial b => Serial1 (Name b) where
serializeWith = serializeWith2 serialize
deserializeWith = deserializeWith2 deserialize
instance (Serial b, Serial a) => Serial (Name b a) where
serialize = serializeWith2 serialize serialize
deserialize = deserializeWith2 deserialize deserialize
instance (Binary b, Binary a) => Binary (Name b a) where
put = serializeWith2 Binary.put Binary.put
get = deserializeWith2 Binary.get Binary.get
instance (Serialize b, Serialize a) => Serialize (Name b a) where
put = serializeWith2 Serialize.put Serialize.put
get = deserializeWith2 Serialize.get Serialize.get
abstractName :: Monad f => (a -> Maybe b) -> f a -> Scope (Name a b) f a
abstractName f t = Scope (liftM k t) where
k a = case f a of
Just b -> B (Name a b)
Nothing -> F (return a)
abstract1Name :: (Monad f, Eq a) => a -> f a -> Scope (Name a ()) f a
abstract1Name a = abstractName (\b -> if a == b then Just () else Nothing)
instantiateName :: (Monad f, Comonad n) => (b -> f a) -> Scope (n b) f a -> f a
instantiateName k e = unscope e >>= \v -> case v of
B b -> k (extract b)
F a -> a
instantiate1Name :: Monad f => f a -> Scope n f a -> f a
instantiate1Name = instantiate1