parameterized-utils-2.1.5.0: Classes and data structures for working with data-kind indexed types
Copyright(c) Galois Inc 2014-2019
MaintainerJoe Hendrix <jhendrix@galois.com>
Safe HaskellSafe-Inferred
LanguageHaskell2010

Data.Parameterized.Some

Description

This module provides Some, a GADT that hides a type parameter.

Synopsis

Documentation

data Some (f :: k -> Type) Source #

Constructors

forall x. Some (f x) 

Instances

Instances details
TraversableF (Some :: (k -> Type) -> Type) Source # 
Instance details

Defined in Data.Parameterized.Some

Methods

traverseF :: Applicative m => (forall (s :: k0). e s -> m (f s)) -> Some e -> m (Some f) Source #

FoldableF (Some :: (k -> Type) -> Type) Source # 
Instance details

Defined in Data.Parameterized.Some

Methods

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 # 
Instance details

Defined in Data.Parameterized.Some

Methods

fmapF :: (forall (x :: k0). f x -> g x) -> Some f -> Some g Source #

OrdC (Some :: (k -> Type) -> Type) Source # 
Instance details

Defined in Data.Parameterized.ClassesC

Methods

compareC :: (forall (x :: k0) (y :: k0). f x -> g y -> OrderingF x y) -> Some f -> Some g -> Ordering Source #

TestEqualityC (Some :: (k -> Type) -> Type) Source #

This instance demonstrates where the above class is useful: namely, in types with existential quantification.

Instance details

Defined in Data.Parameterized.ClassesC

Methods

testEqualityC :: (forall (x :: k0) (y :: k0). f x -> f y -> Maybe (x :~: y)) -> Some f -> Some f -> Bool Source #

TestEquality f => Eq (Some f) Source # 
Instance details

Defined in Data.Parameterized.Some

Methods

(==) :: Some f -> Some f -> Bool #

(/=) :: Some f -> Some f -> Bool #

OrdF f => Ord (Some f) Source # 
Instance details

Defined in Data.Parameterized.Some

Methods

compare :: Some f -> Some f -> Ordering #

(<) :: Some f -> Some f -> Bool #

(<=) :: Some f -> Some f -> Bool #

(>) :: Some f -> Some f -> Bool #

(>=) :: Some f -> Some f -> Bool #

max :: Some f -> Some f -> Some f #

min :: Some f -> Some f -> Some f #

ShowF f => Show (Some f) Source # 
Instance details

Defined in Data.Parameterized.Some

Methods

showsPrec :: Int -> Some f -> ShowS #

show :: Some f -> String #

showList :: [Some f] -> ShowS #

HashableF f => Hashable (Some f) Source # 
Instance details

Defined in Data.Parameterized.Some

Methods

hashWithSalt :: Int -> Some f -> Int #

hash :: Some f -> Int #

viewSome :: (forall tp. f tp -> r) -> Some f -> r Source #

Project out of Some.

mapSome :: (forall tp. f tp -> g tp) -> Some f -> Some g Source #

Apply function to inner value.

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.