Safe Haskell | None |
---|---|
Language | Haskell2010 |
Data.Generics.PlateTypeable
Description
Deprecated: Use Data.Generics.Uniplate.Typeable instead
DEPRECATED: Use Data.Generics.Uniplate.Typeable instead.
This module supplies a method for writing Biplate
instances more easily.
To take an example:
data Expr = Var Int | Neg Expr | Add Expr Expr instance Typeable Expr where ... instance (Typeable a, Uniplate a) => PlateAll Expr a where plateAll (Var x ) = plate Var |- x plateAll (Neg x ) = plate Neg |+ x plateAll (Add x y) = plate Add |+ x |+ y instance Uniplate Expr where uniplate = uniplateAll
Synopsis
- module Data.Generics.Biplate
- class Typeable (a :: k)
- data TyCon
- cast :: (Typeable a, Typeable b) => a -> Maybe b
- decT :: forall {k} (a :: k) (b :: k). (Typeable a, Typeable b) => Either ((a :~: b) -> Void) (a :~: b)
- eqT :: forall {k} (a :: k) (b :: k). (Typeable a, Typeable b) => Maybe (a :~: b)
- funResultTy :: TypeRep -> TypeRep -> Maybe TypeRep
- gcast :: forall {k} (a :: k) (b :: k) c. (Typeable a, Typeable b) => c a -> Maybe (c b)
- gcast1 :: forall {k1} {k2} c (t :: k2 -> k1) (t' :: k2 -> k1) (a :: k2). (Typeable t, Typeable t') => c (t a) -> Maybe (c (t' a))
- gcast2 :: forall {k1} {k2} {k3} c (t :: k2 -> k3 -> k1) (t' :: k2 -> k3 -> k1) (a :: k2) (b :: k3). (Typeable t, Typeable t') => c (t a b) -> Maybe (c (t' a b))
- hdecT :: forall {k1} {k2} (a :: k1) (b :: k2). (Typeable a, Typeable b) => Either ((a :~~: b) -> Void) (a :~~: b)
- heqT :: forall {k1} {k2} (a :: k1) (b :: k2). (Typeable a, Typeable b) => Maybe (a :~~: b)
- mkFunTy :: TypeRep -> TypeRep -> TypeRep
- rnfTypeRep :: TypeRep -> ()
- showsTypeRep :: TypeRep -> ShowS
- splitTyConApp :: TypeRep -> (TyCon, [TypeRep])
- typeOf :: Typeable a => a -> TypeRep
- typeOf1 :: Typeable t => t a -> TypeRep
- typeOf2 :: Typeable t => t a b -> TypeRep
- typeOf3 :: Typeable t => t a b c -> TypeRep
- typeOf4 :: Typeable t => t a b c d -> TypeRep
- typeOf5 :: Typeable t => t a b c d e -> TypeRep
- typeOf6 :: Typeable t => t a b c d e f -> TypeRep
- typeOf7 :: Typeable t => t a b c d e f g -> TypeRep
- typeRep :: forall {k} proxy (a :: k). Typeable a => proxy a -> TypeRep
- typeRepArgs :: TypeRep -> [TypeRep]
- typeRepFingerprint :: TypeRep -> Fingerprint
- typeRepTyCon :: TypeRep -> TyCon
- rnfTyCon :: TyCon -> ()
- trLiftedRep :: TypeRep LiftedRep
- tyConFingerprint :: TyCon -> Fingerprint
- tyConModule :: TyCon -> String
- tyConName :: TyCon -> String
- tyConPackage :: TyCon -> String
- data Proxy (t :: k) = Proxy
- data (a :: k) :~: (b :: k) where
- data (a :: k1) :~~: (b :: k2) where
- type TypeRep = SomeTypeRep
- class PlateAll from to where
- plateAll :: from -> Type from to
- uniplateAll :: PlateAll a b => a -> (Str b, Str b -> a)
- plate :: from -> Type from to
- (|+) :: (Typeable item, Typeable to, PlateAll item to) => Type (item -> from) to -> item -> Type from to
- (|-) :: Type (item -> from) to -> item -> Type from to
Documentation
module Data.Generics.Biplate
decT :: forall {k} (a :: k) (b :: k). (Typeable a, Typeable b) => Either ((a :~: b) -> Void) (a :~: b) #
funResultTy :: TypeRep -> TypeRep -> Maybe TypeRep #
gcast1 :: forall {k1} {k2} c (t :: k2 -> k1) (t' :: k2 -> k1) (a :: k2). (Typeable t, Typeable t') => c (t a) -> Maybe (c (t' a)) #
gcast2 :: forall {k1} {k2} {k3} c (t :: k2 -> k3 -> k1) (t' :: k2 -> k3 -> k1) (a :: k2) (b :: k3). (Typeable t, Typeable t') => c (t a b) -> Maybe (c (t' a b)) #
hdecT :: forall {k1} {k2} (a :: k1) (b :: k2). (Typeable a, Typeable b) => Either ((a :~~: b) -> Void) (a :~~: b) #
rnfTypeRep :: TypeRep -> () #
showsTypeRep :: TypeRep -> ShowS #
splitTyConApp :: TypeRep -> (TyCon, [TypeRep]) #
typeRepArgs :: TypeRep -> [TypeRep] #
typeRepFingerprint :: TypeRep -> Fingerprint #
typeRepTyCon :: TypeRep -> TyCon #
trLiftedRep :: TypeRep LiftedRep #
tyConFingerprint :: TyCon -> Fingerprint #
tyConModule :: TyCon -> String #
tyConPackage :: TyCon -> String #
Constructors
Proxy |
Instances
Generic1 (Proxy :: k -> Type) | |||||
Defined in GHC.Internal.Generics Associated Types
| |||||
MonadZip (Proxy :: Type -> Type) | |||||
Eq1 (Proxy :: Type -> Type) | |||||
Defined in Data.Functor.Classes | |||||
Ord1 (Proxy :: Type -> Type) | |||||
Defined in Data.Functor.Classes Methods liftCompare :: (a -> b -> Ordering) -> Proxy a -> Proxy b -> Ordering | |||||
Read1 (Proxy :: Type -> Type) | |||||
Defined in Data.Functor.Classes Methods liftReadsPrec :: (Int -> ReadS a) -> ReadS [a] -> Int -> ReadS (Proxy a) liftReadList :: (Int -> ReadS a) -> ReadS [a] -> ReadS [Proxy a] liftReadPrec :: ReadPrec a -> ReadPrec [a] -> ReadPrec (Proxy a) liftReadListPrec :: ReadPrec a -> ReadPrec [a] -> ReadPrec [Proxy a] | |||||
Show1 (Proxy :: Type -> Type) | |||||
Defined in Data.Functor.Classes Methods liftShowsPrec :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> Int -> Proxy a -> ShowS liftShowList :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> [Proxy a] -> ShowS | |||||
Contravariant (Proxy :: Type -> Type) | |||||
Alternative (Proxy :: Type -> Type) | |||||
Applicative (Proxy :: Type -> Type) | |||||
Functor (Proxy :: Type -> Type) | |||||
Monad (Proxy :: Type -> Type) | |||||
MonadPlus (Proxy :: Type -> Type) | |||||
Foldable (Proxy :: Type -> Type) | |||||
Defined in GHC.Internal.Data.Foldable Methods fold :: Monoid m => Proxy m -> m foldMap :: Monoid m => (a -> m) -> Proxy a -> m foldMap' :: Monoid m => (a -> m) -> Proxy a -> m foldr :: (a -> b -> b) -> b -> Proxy a -> b foldr' :: (a -> b -> b) -> b -> Proxy a -> b foldl :: (b -> a -> b) -> b -> Proxy a -> b foldl' :: (b -> a -> b) -> b -> Proxy a -> b foldr1 :: (a -> a -> a) -> Proxy a -> a foldl1 :: (a -> a -> a) -> Proxy a -> a elem :: Eq a => a -> Proxy a -> Bool maximum :: Ord a => Proxy a -> a | |||||
Traversable (Proxy :: Type -> Type) | |||||
Hashable1 (Proxy :: Type -> Type) | |||||
Defined in Data.Hashable.Class Methods liftHashWithSalt :: (Int -> a -> Int) -> Int -> Proxy a -> Int | |||||
Monoid (Proxy s) | |||||
Semigroup (Proxy s) | |||||
Data t => Data (Proxy t) | |||||
Defined in GHC.Internal.Data.Data Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Proxy t -> c (Proxy t) gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Proxy t) dataTypeOf :: Proxy t -> DataType dataCast1 :: Typeable t0 => (forall d. Data d => c (t0 d)) -> Maybe (c (Proxy t)) dataCast2 :: Typeable t0 => (forall d e. (Data d, Data e) => c (t0 d e)) -> Maybe (c (Proxy t)) gmapT :: (forall b. Data b => b -> b) -> Proxy t -> Proxy t gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Proxy t -> r gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Proxy t -> r gmapQ :: (forall d. Data d => d -> u) -> Proxy t -> [u] gmapQi :: Int -> (forall d. Data d => d -> u) -> Proxy t -> u gmapM :: Monad m => (forall d. Data d => d -> m d) -> Proxy t -> m (Proxy t) gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Proxy t -> m (Proxy t) gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Proxy t -> m (Proxy t) | |||||
Bounded (Proxy t) | |||||
Defined in GHC.Internal.Data.Proxy | |||||
Enum (Proxy s) | |||||
Defined in GHC.Internal.Data.Proxy | |||||
Generic (Proxy t) | |||||
Defined in GHC.Internal.Generics Associated Types
| |||||
Ix (Proxy s) | |||||
Defined in GHC.Internal.Data.Proxy | |||||
Read (Proxy t) | |||||
Defined in GHC.Internal.Data.Proxy | |||||
Show (Proxy s) | |||||
Eq (Proxy s) | |||||
Ord (Proxy s) | |||||
Hashable (Proxy a) | |||||
Defined in Data.Hashable.Class | |||||
type Rep1 (Proxy :: k -> Type) | |||||
Defined in GHC.Internal.Generics type Rep1 (Proxy :: k -> Type) = D1 ('MetaData "Proxy" "GHC.Internal.Data.Proxy" "ghc-internal" 'False) (C1 ('MetaCons "Proxy" 'PrefixI 'False) (U1 :: k -> Type)) | |||||
type Rep (Proxy t) | |||||
Defined in GHC.Internal.Generics type Rep (Proxy t) = D1 ('MetaData "Proxy" "GHC.Internal.Data.Proxy" "ghc-internal" 'False) (C1 ('MetaCons "Proxy" 'PrefixI 'False) (U1 :: Type -> Type)) |
data (a :: k) :~: (b :: k) where #
Instances
TestCoercion ((:~:) a :: k -> Type) | |
Defined in GHC.Internal.Data.Type.Coercion Methods testCoercion :: forall (a0 :: k) (b :: k). (a :~: a0) -> (a :~: b) -> Maybe (Coercion a0 b) | |
TestEquality ((:~:) a :: k -> Type) | |
Defined in GHC.Internal.Data.Type.Equality Methods testEquality :: forall (a0 :: k) (b :: k). (a :~: a0) -> (a :~: b) -> Maybe (a0 :~: b) | |
(a ~ b, Data a) => Data (a :~: b) | |
Defined in GHC.Internal.Data.Data Methods gfoldl :: (forall d b0. Data d => c (d -> b0) -> d -> c b0) -> (forall g. g -> c g) -> (a :~: b) -> c (a :~: b) gunfold :: (forall b0 r. Data b0 => c (b0 -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (a :~: b) toConstr :: (a :~: b) -> Constr dataTypeOf :: (a :~: b) -> DataType dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (a :~: b)) dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (a :~: b)) gmapT :: (forall b0. Data b0 => b0 -> b0) -> (a :~: b) -> a :~: b gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> (a :~: b) -> r gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> (a :~: b) -> r gmapQ :: (forall d. Data d => d -> u) -> (a :~: b) -> [u] gmapQi :: Int -> (forall d. Data d => d -> u) -> (a :~: b) -> u gmapM :: Monad m => (forall d. Data d => d -> m d) -> (a :~: b) -> m (a :~: b) gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> (a :~: b) -> m (a :~: b) gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> (a :~: b) -> m (a :~: b) | |
a ~ b => Bounded (a :~: b) | |
Defined in GHC.Internal.Data.Type.Equality | |
a ~ b => Enum (a :~: b) | |
Defined in GHC.Internal.Data.Type.Equality | |
a ~ b => Read (a :~: b) | |
Defined in GHC.Internal.Data.Type.Equality | |
Show (a :~: b) | |
Eq (a :~: b) | |
Ord (a :~: b) | |
Defined in GHC.Internal.Data.Type.Equality |
data (a :: k1) :~~: (b :: k2) where #
Instances
TestCoercion ((:~~:) a :: k -> Type) | |
Defined in GHC.Internal.Data.Type.Coercion Methods testCoercion :: forall (a0 :: k) (b :: k). (a :~~: a0) -> (a :~~: b) -> Maybe (Coercion a0 b) | |
TestEquality ((:~~:) a :: k -> Type) | |
Defined in GHC.Internal.Data.Type.Equality Methods testEquality :: forall (a0 :: k) (b :: k). (a :~~: a0) -> (a :~~: b) -> Maybe (a0 :~: b) | |
(Typeable i, Typeable j, Typeable a, Typeable b, a ~~ b) => Data (a :~~: b) | |
Defined in GHC.Internal.Data.Data Methods gfoldl :: (forall d b0. Data d => c (d -> b0) -> d -> c b0) -> (forall g. g -> c g) -> (a :~~: b) -> c (a :~~: b) gunfold :: (forall b0 r. Data b0 => c (b0 -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (a :~~: b) toConstr :: (a :~~: b) -> Constr dataTypeOf :: (a :~~: b) -> DataType dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (a :~~: b)) dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (a :~~: b)) gmapT :: (forall b0. Data b0 => b0 -> b0) -> (a :~~: b) -> a :~~: b gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> (a :~~: b) -> r gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> (a :~~: b) -> r gmapQ :: (forall d. Data d => d -> u) -> (a :~~: b) -> [u] gmapQi :: Int -> (forall d. Data d => d -> u) -> (a :~~: b) -> u gmapM :: Monad m => (forall d. Data d => d -> m d) -> (a :~~: b) -> m (a :~~: b) gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> (a :~~: b) -> m (a :~~: b) gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> (a :~~: b) -> m (a :~~: b) | |
a ~~ b => Bounded (a :~~: b) | |
Defined in GHC.Internal.Data.Type.Equality | |
a ~~ b => Enum (a :~~: b) | |
Defined in GHC.Internal.Data.Type.Equality | |
a ~~ b => Read (a :~~: b) | |
Defined in GHC.Internal.Data.Type.Equality | |
Show (a :~~: b) | |
Eq (a :~~: b) | |
Ord (a :~~: b) | |
Defined in GHC.Internal.Data.Type.Equality |
The Class
class PlateAll from to where Source #
This class represents going from the container type to the target.
Instances
The Combinators
plate :: from -> Type from to Source #
The main combinator used to start the chain.
The following rule can be used for optimisation:
plate Ctor |- x == plate (Ctor x)
(|+) :: (Typeable item, Typeable to, PlateAll item to) => Type (item -> from) to -> item -> Type from to Source #
the field to the right may contain the target.
(|-) :: Type (item -> from) to -> item -> Type from to Source #
The field to the right does not contain the target. This can be used as either an optimisation, or more commonly for excluding primitives such as Int.
Orphan instances
Uniplate Integer Source # | |
Methods uniplate :: UniplateType Integer Source # | |
Uniplate () Source # | |
Methods uniplate :: UniplateType () Source # | |
Uniplate Bool Source # | |
Methods uniplate :: UniplateType Bool Source # | |
Uniplate Char Source # | |
Methods uniplate :: UniplateType Char Source # | |
Uniplate Double Source # | |
Methods uniplate :: UniplateType Double Source # | |
Uniplate Float Source # | |
Methods uniplate :: UniplateType Float Source # | |
Uniplate Int Source # | |
Methods uniplate :: UniplateType Int Source # | |
(Typeable a, Typeable b, Uniplate b, PlateAll a b) => Biplate a b Source # | |
Methods biplate :: BiplateType a b Source # |