Copyright | (c) 2020 Emily Pillmore |
---|---|
License | BSD-3-Clause |
Maintainer | Emily Pillmore <emilypi@cohomolo.gy> |
Stability | Experimental |
Portability | portable |
Safe Haskell | Safe |
Language | Haskell2010 |
This module contains the definition for the Wedge
datatype. In
practice, this type is isomorphic to 'Maybe (Either a b)' - the type with
two possibly non-exclusive values and an empty case.
Synopsis
- data Wedge a b
- quotWedge :: Either (Maybe a) (Maybe b) -> Wedge a b
- wedgeLeft :: Maybe a -> Wedge a b
- wedgeRight :: Maybe b -> Wedge a b
- fromWedge :: Wedge a b -> Maybe (Either a b)
- toWedge :: Maybe (Either a b) -> Wedge a b
- isHere :: Wedge a b -> Bool
- isThere :: Wedge a b -> Bool
- isNowhere :: Wedge a b -> Bool
- wedge :: c -> (a -> c) -> (b -> c) -> Wedge a b -> c
- heres :: Foldable f => f (Wedge a b) -> [a]
- theres :: Foldable f => f (Wedge a b) -> [b]
- filterHeres :: Foldable f => f (Wedge a b) -> [Wedge a b]
- filterTheres :: Foldable f => f (Wedge a b) -> [Wedge a b]
- filterNowheres :: Foldable f => f (Wedge a b) -> [Wedge a b]
- foldHeres :: Foldable f => (a -> m -> m) -> m -> f (Wedge a b) -> m
- foldTheres :: Foldable f => (b -> m -> m) -> m -> f (Wedge a b) -> m
- gatherWedges :: Wedge [a] [b] -> [Wedge a b]
- partitionWedges :: forall f t a b. (Foldable t, Alternative f) => t (Wedge a b) -> (f a, f b)
- mapWedges :: forall f t a b c. (Alternative f, Traversable t) => (a -> Wedge b c) -> t a -> (f b, f c)
- distributeWedge :: Wedge (a, b) c -> (Wedge a c, Wedge b c)
- codistributeWedge :: Either (Wedge a c) (Wedge b c) -> Wedge (Either a b) c
- reassocLR :: Wedge (Wedge a b) c -> Wedge a (Wedge b c)
- reassocRL :: Wedge a (Wedge b c) -> Wedge (Wedge a b) c
- swapWedge :: Wedge a b -> Wedge b a
Datatypes
Categorically, the Wedge
datatype represents the coproduct (like, Either
)
in the category Hask* of pointed Hask types, called a wedge sum.
The category Hask* consists of Hask types affixed with
a dedicated base point along with an object. In Hask, this is
equivalent to `1 + a`, also known as 'Maybe a'. Because we can conflate
basepoints of different types (there is only one Nothing
type), the wedge sum is
can be viewed as the type `1 + a + b`, or `Maybe (Either a b)` in Hask.
Pictorially, one can visualize this as:
Wedge
:
a
|
Nowhere +-------+
|
b
The fact that we can think about Wedge
as a coproduct gives us
some reasoning power about how a Wedge
will interact with the
product in Hask*, called Can
. Namely, we know that a product of a type and a
coproduct, `a * (b + c)`, is equivalent to `(a + b) * (a + c)`. Additioally,
we may derive other facts about its associativity, distributivity, commutativity, and
any more. As an exercise, think of soemthing Either
can do. Now do it with Wedge
!
The Wedge
data type represents values with two exclusive
possibilities, and an empty case. This is a coproduct of pointed
types - i.e. of Maybe
values. The result is a type, 'Wedge a b',
which is isomorphic to 'Maybe (Either a b)'.
Instances
Bitraversable Wedge Source # | |
Defined in Data.Wedge bitraverse :: Applicative f => (a -> f c) -> (b -> f d) -> Wedge a b -> f (Wedge c d) # | |
Bifoldable Wedge Source # | |
Bifunctor Wedge Source # | |
Semigroup a => Monad (Wedge a) Source # | |
Functor (Wedge a) Source # | |
Semigroup a => Applicative (Wedge a) Source # | |
Foldable (Wedge a) Source # | |
Defined in Data.Wedge fold :: Monoid m => Wedge a m -> m # foldMap :: Monoid m => (a0 -> m) -> Wedge a a0 -> m # foldr :: (a0 -> b -> b) -> b -> Wedge a a0 -> b # foldr' :: (a0 -> b -> b) -> b -> Wedge a a0 -> b # foldl :: (b -> a0 -> b) -> b -> Wedge a a0 -> b # foldl' :: (b -> a0 -> b) -> b -> Wedge a a0 -> b # foldr1 :: (a0 -> a0 -> a0) -> Wedge a a0 -> a0 # foldl1 :: (a0 -> a0 -> a0) -> Wedge a a0 -> a0 # toList :: Wedge a a0 -> [a0] # elem :: Eq a0 => a0 -> Wedge a a0 -> Bool # maximum :: Ord a0 => Wedge a a0 -> a0 # minimum :: Ord a0 => Wedge a a0 -> a0 # | |
Traversable (Wedge a) Source # | |
Generic1 (Wedge a :: Type -> Type) Source # | |
(Eq a, Eq b) => Eq (Wedge a b) Source # | |
(Data a, Data b) => Data (Wedge a b) Source # | |
Defined in Data.Wedge gfoldl :: (forall d b0. Data d => c (d -> b0) -> d -> c b0) -> (forall g. g -> c g) -> Wedge a b -> c (Wedge a b) # gunfold :: (forall b0 r. Data b0 => c (b0 -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Wedge a b) # toConstr :: Wedge a b -> Constr # dataTypeOf :: Wedge a b -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Wedge a b)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Wedge a b)) # gmapT :: (forall b0. Data b0 => b0 -> b0) -> Wedge a b -> Wedge a b # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Wedge a b -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Wedge a b -> r # gmapQ :: (forall d. Data d => d -> u) -> Wedge a b -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Wedge a b -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Wedge a b -> m (Wedge a b) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Wedge a b -> m (Wedge a b) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Wedge a b -> m (Wedge a b) # | |
(Ord a, Ord b) => Ord (Wedge a b) Source # | |
Defined in Data.Wedge | |
(Read a, Read b) => Read (Wedge a b) Source # | |
(Show a, Show b) => Show (Wedge a b) Source # | |
Generic (Wedge a b) Source # | |
(Semigroup a, Semigroup b) => Semigroup (Wedge a b) Source # | |
(Semigroup a, Semigroup b) => Monoid (Wedge a b) Source # | |
(Hashable a, Hashable b) => Hashable (Wedge a b) Source # | |
Defined in Data.Wedge | |
type Rep1 (Wedge a :: Type -> Type) Source # | |
Defined in Data.Wedge type Rep1 (Wedge a :: Type -> Type) = D1 (MetaData "Wedge" "Data.Wedge" "smash-0.1.0.0-inplace" False) (C1 (MetaCons "Nowhere" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "Here" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a)) :+: C1 (MetaCons "There" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) Par1))) | |
type Rep (Wedge a b) Source # | |
Defined in Data.Wedge type Rep (Wedge a b) = D1 (MetaData "Wedge" "Data.Wedge" "smash-0.1.0.0-inplace" False) (C1 (MetaCons "Nowhere" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "Here" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a)) :+: C1 (MetaCons "There" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 b)))) |
Combinators
wedgeRight :: Maybe b -> Wedge a b Source #
fromWedge :: Wedge a b -> Maybe (Either a b) Source #
Convert a 'Wedge a b' into a 'Maybe (Either a b)' value.
toWedge :: Maybe (Either a b) -> Wedge a b Source #
Convert a 'Maybe (Either a b)' value into a Wedge
Eliminators
wedge :: c -> (a -> c) -> (b -> c) -> Wedge a b -> c Source #
Case elimination for the Wedge
datatype.
Filtering
Folding
foldTheres :: Foldable f => (b -> m -> m) -> m -> f (Wedge a b) -> m Source #
gatherWedges :: Wedge [a] [b] -> [Wedge a b] Source #
Partitioning
partitionWedges :: forall f t a b. (Foldable t, Alternative f) => t (Wedge a b) -> (f a, f b) Source #
mapWedges :: forall f t a b c. (Alternative f, Traversable t) => (a -> Wedge b c) -> t a -> (f b, f c) Source #
Distributivity
distributeWedge :: Wedge (a, b) c -> (Wedge a c, Wedge b c) Source #
Distribute a Wedge
over a product.
codistributeWedge :: Either (Wedge a c) (Wedge b c) -> Wedge (Either a b) c Source #
Codistribute Wedge
s over a coproduct