Copyright | (c) Galois Inc 2014-2019 |
---|---|
Maintainer | Joe Hendrix <jhendrix@galois.com> |
Safe Haskell | Safe-Inferred |
Language | Haskell2010 |
This module provides Some
, a GADT that hides a type parameter.
Synopsis
- data Some (f :: k -> Type) = forall x. Some (f x)
- viewSome :: (forall tp. f tp -> r) -> Some f -> r
- mapSome :: (forall tp. f tp -> g tp) -> Some f -> Some g
- traverseSome :: Functor m => (forall tp. f tp -> m (g tp)) -> Some f -> m (Some g)
- traverseSome_ :: Functor m => (forall tp. f tp -> m ()) -> Some f -> m ()
Documentation
data Some (f :: k -> Type) Source #
forall x. Some (f x) |
Instances
TraversableF (Some :: (k -> Type) -> Type) Source # | |
Defined in Data.Parameterized.Some | |
FoldableF (Some :: (k -> Type) -> Type) Source # | |
Defined in Data.Parameterized.Some foldMapF :: Monoid m => (forall (s :: k0). e s -> m) -> Some e -> m Source # foldrF :: (forall (s :: k0). e s -> b -> b) -> b -> Some e -> b Source # foldlF :: (forall (s :: k0). b -> e s -> b) -> b -> Some e -> b Source # foldrF' :: (forall (s :: k0). e s -> b -> b) -> b -> Some e -> b Source # foldlF' :: (forall (s :: k0). b -> e s -> b) -> b -> Some e -> b Source # toListF :: (forall (tp :: k0). f tp -> a) -> Some f -> [a] Source # | |
FunctorF (Some :: (k -> Type) -> Type) Source # | |
OrdC (Some :: (k -> Type) -> Type) Source # | |
TestEqualityC (Some :: (k -> Type) -> Type) Source # | This instance demonstrates where the above class is useful: namely, in types with existential quantification. |
Defined in Data.Parameterized.ClassesC | |
TestEquality f => Eq (Some f) Source # | |
OrdF f => Ord (Some f) Source # | |
ShowF f => Show (Some f) Source # | |
HashableF f => Hashable (Some f) Source # | |
Defined in Data.Parameterized.Some |
traverseSome :: Functor m => (forall tp. f tp -> m (g tp)) -> Some f -> m (Some g) Source #
Modify the inner value.
traverseSome_ :: Functor m => (forall tp. f tp -> m ()) -> Some f -> m () Source #
Modify the inner value.