Safe Haskell | None |
---|---|
Language | Haskell2010 |
Prologue.Type.Reflection
Synopsis
- class TypeableMany (ls :: [*]) where
- type family Typeables ls :: Constraint where ...
- someTypeRep :: forall a. Typeable a => SomeTypeRep
- typeOfProxy :: forall proxy a. Typeable a => proxy a -> TypeRep a
- class Typeable (a :: k)
- data TypeRep (a :: k) :: forall k. k -> *
- data SomeTypeRep
- typeOf :: Typeable a => a -> TypeRep a
- typeRep :: Typeable a => TypeRep a
- withTypeable :: TypeRep a -> (Typeable a -> r) -> r
- data Proxy (t :: k) :: forall k. k -> * = Proxy
Documentation
class TypeableMany (ls :: [*]) where Source #
Minimal complete definition
Methods
someTypeReps :: [SomeTypeRep] Source #
Instances
TypeableMany ([] :: [*]) Source # | |
Defined in Prologue.Type.Reflection Methods someTypeReps :: [SomeTypeRep] Source # | |
(Typeable l, TypeableMany ls) => TypeableMany (l ': ls) Source # | |
Defined in Prologue.Type.Reflection Methods someTypeReps :: [SomeTypeRep] Source # |
type family Typeables ls :: Constraint where ... Source #
someTypeRep :: forall a. Typeable a => SomeTypeRep Source #
typeOfProxy :: forall proxy a. Typeable a => proxy a -> TypeRep a Source #
The class Typeable
allows a concrete representation of a type to
be calculated.
Minimal complete definition
typeRep#
data TypeRep (a :: k) :: forall k. k -> * #
A concrete representation of a (monomorphic) type.
TypeRep
supports reasonably efficient equality.
Instances
TestEquality (TypeRep :: k -> *) | |
Defined in Data.Typeable.Internal | |
Eq (TypeRep a) | Since: base-2.1 |
Ord (TypeRep a) | Since: base-4.4.0.0 |
Show (TypeRep a) | |
Hashable (TypeRep a) | |
Defined in Data.Hashable.Class |
data SomeTypeRep #
A non-indexed type representation.
Instances
Eq SomeTypeRep | |
Defined in Data.Typeable.Internal | |
Ord SomeTypeRep | |
Defined in Data.Typeable.Internal Methods compare :: SomeTypeRep -> SomeTypeRep -> Ordering # (<) :: SomeTypeRep -> SomeTypeRep -> Bool # (<=) :: SomeTypeRep -> SomeTypeRep -> Bool # (>) :: SomeTypeRep -> SomeTypeRep -> Bool # (>=) :: SomeTypeRep -> SomeTypeRep -> Bool # max :: SomeTypeRep -> SomeTypeRep -> SomeTypeRep # min :: SomeTypeRep -> SomeTypeRep -> SomeTypeRep # | |
Show SomeTypeRep | Since: base-4.10.0.0 |
Defined in Data.Typeable.Internal Methods showsPrec :: Int -> SomeTypeRep -> ShowS # show :: SomeTypeRep -> String # showList :: [SomeTypeRep] -> ShowS # | |
Hashable SomeTypeRep | |
Defined in Data.Hashable.Class | |
NFData TypeRep | NOTE: Only defined for Since: deepseq-1.4.0.0 |
Defined in Control.DeepSeq |
data Proxy (t :: k) :: forall k. k -> * #
Proxy
is a type that holds no data, but has a phantom parameter of
arbitrary type (or even kind). Its use is to provide type information, even
though there is no value available of that type (or it may be too costly to
create one).
Historically,
is a safer alternative to the
Proxy
:: Proxy
a'undefined :: a'
idiom.
>>>
Proxy :: Proxy (Void, Int -> Int)
Proxy
Proxy can even hold types of higher kinds,
>>>
Proxy :: Proxy Either
Proxy
>>>
Proxy :: Proxy Functor
Proxy
>>>
Proxy :: Proxy complicatedStructure
Proxy
Constructors
Proxy |
Instances
Generic1 (Proxy :: k -> *) | |
FunctorWithIndex Void (Proxy :: * -> *) | |
FoldableWithIndex Void (Proxy :: * -> *) | |
Defined in Control.Lens.Indexed Methods ifoldMap :: Monoid m => (Void -> a -> m) -> Proxy a -> m # ifolded :: (Indexable Void p, Contravariant f, Applicative f) => p a (f a) -> Proxy a -> f (Proxy a) # ifoldr :: (Void -> a -> b -> b) -> b -> Proxy a -> b # ifoldl :: (Void -> b -> a -> b) -> b -> Proxy a -> b # | |
TraversableWithIndex Void (Proxy :: * -> *) | |
Defined in Control.Lens.Indexed Methods itraverse :: Applicative f => (Void -> a -> f b) -> Proxy a -> f (Proxy b) # itraversed :: (Indexable Void p, Applicative f) => p a (f b) -> Proxy a -> f (Proxy b) # | |
Monad (Proxy :: * -> *) | Since: base-4.7.0.0 |
Functor (Proxy :: * -> *) | Since: base-4.7.0.0 |
Applicative (Proxy :: * -> *) | Since: base-4.7.0.0 |
Foldable (Proxy :: * -> *) | Since: base-4.7.0.0 |
Defined in Data.Foldable Methods fold :: Monoid m => Proxy m -> 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 # minimum :: Ord a => Proxy a -> a # | |
Traversable (Proxy :: * -> *) | Since: base-4.7.0.0 |
Contravariant (Proxy :: * -> *) | |
Representable (Proxy :: * -> *) | |
Alternative (Proxy :: * -> *) | Since: base-4.9.0.0 |
MonadPlus (Proxy :: * -> *) | Since: base-4.9.0.0 |
Eq1 (Proxy :: * -> *) | Since: base-4.9.0.0 |
Ord1 (Proxy :: * -> *) | Since: base-4.9.0.0 |
Defined in Data.Functor.Classes | |
Read1 (Proxy :: * -> *) | Since: base-4.9.0.0 |
Defined in Data.Functor.Classes | |
Show1 (Proxy :: * -> *) | Since: base-4.9.0.0 |
NFData1 (Proxy :: * -> *) | Since: deepseq-1.4.3.0 |
Defined in Control.DeepSeq | |
Hashable1 (Proxy :: * -> *) | |
Defined in Data.Hashable.Class | |
Apply (Proxy :: * -> *) | |
Pointed (Proxy :: * -> *) | |
Defined in Data.Pointed | |
Alt (Proxy :: * -> *) | |
Bind (Proxy :: * -> *) | |
Bounded (Proxy t) | |
Enum (Proxy s) | Since: base-4.7.0.0 |
Eq (Proxy s) | Since: base-4.7.0.0 |
Data t => Data (Proxy t) | Since: base-4.7.0.0 |
Defined in 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) # toConstr :: Proxy t -> Constr # 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 :: (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) # | |
Ord (Proxy s) | Since: base-4.7.0.0 |
Read (Proxy t) | Since: base-4.7.0.0 |
Show (Proxy s) | Since: base-4.7.0.0 |
Ix (Proxy s) | Since: base-4.7.0.0 |
Defined in Data.Proxy | |
Generic (Proxy t) | |
Semigroup (Proxy s) | Since: base-4.9.0.0 |
Monoid (Proxy s) | Since: base-4.7.0.0 |
Hashable (Proxy a) | |
Defined in Data.Hashable.Class | |
NFData (Proxy a) | Since: deepseq-1.4.0.0 |
Defined in Control.DeepSeq | |
type Rep1 (Proxy :: k -> *) | |
type Rep (Proxy :: * -> *) | |
type Rep (Proxy t) | |