Copyright | (c) 2020-2021 Emily Pillmore |
---|---|
License | BSD-3-Clause |
Maintainer | Emily Pillmore <emilypi@cohomolo.gy> |
Stability | Experimental |
Portability | CPP, RankNTypes, TypeApplications |
Safe Haskell | Safe |
Language | Haskell2010 |
Synopsis
- data Can a b
- type (⊗) a b = Can a b
- canFst :: Can a b -> Maybe a
- canSnd :: Can a b -> Maybe b
- isOne :: Can a b -> Bool
- isEno :: Can a b -> Bool
- isTwo :: Can a b -> Bool
- isNon :: Can a b -> Bool
- can :: c -> (a -> c) -> (b -> c) -> (a -> b -> c) -> Can a b -> c
- canWithMerge :: c -> (a -> c) -> (b -> c) -> (c -> c -> c) -> Can a b -> c
- canEach :: Monoid c => (a -> c) -> (b -> c) -> Can a b -> c
- canEachA :: Applicative m => Monoid c => (a -> m c) -> (b -> m c) -> Can a b -> m c
- foldOnes :: Foldable f => (a -> m -> m) -> m -> f (Can a b) -> m
- foldEnos :: Foldable f => (b -> m -> m) -> m -> f (Can a b) -> m
- foldTwos :: Foldable f => (a -> b -> m -> m) -> m -> f (Can a b) -> m
- gatherCans :: Can [a] [b] -> [Can a b]
- unfoldr :: Alternative f => (b -> Can a b) -> b -> f a
- unfoldrM :: (Monad m, Alternative f) => (b -> m (Can a b)) -> b -> m (f a)
- iterateUntil :: Alternative f => (b -> Can a b) -> b -> f a
- iterateUntilM :: Monad m => Alternative f => (b -> m (Can a b)) -> b -> m (f a)
- accumUntil :: Alternative f => Monoid b => (b -> Can a b) -> f a
- accumUntilM :: Monad m => Alternative f => Monoid b => (b -> m (Can a b)) -> m (f a)
- ones :: Foldable f => f (Can a b) -> [a]
- enos :: Foldable f => f (Can a b) -> [b]
- twos :: Foldable f => f (Can a b) -> [(a, b)]
- filterOnes :: Foldable f => f (Can a b) -> [Can a b]
- filterEnos :: Foldable f => f (Can a b) -> [Can a b]
- filterTwos :: Foldable f => f (Can a b) -> [Can a b]
- filterNons :: Foldable f => f (Can a b) -> [Can a b]
- canCurry :: (Can a b -> Maybe c) -> Maybe a -> Maybe b -> Maybe c
- canUncurry :: (Maybe a -> Maybe b -> Maybe c) -> Can a b -> Maybe c
- partitionCans :: Foldable t => Alternative f => t (Can a b) -> (f a, f b)
- partitionAll :: Foldable f => f (Can a b) -> ([a], [b], [(a, b)])
- partitionEithers :: Foldable f => f (Either a b) -> Can [a] [b]
- mapCans :: Traversable t => Alternative f => (a -> Can b c) -> t a -> (f b, f c)
- distributeCan :: Can (a, b) c -> (Can a c, Can b c)
- codistributeCan :: Either (Can a c) (Can b c) -> Can (Either a b) c
- reassocLR :: Can (Can a b) c -> Can a (Can b c)
- reassocRL :: Can a (Can b c) -> Can (Can a b) c
- swapCan :: Can a b -> Can b a
Datatypes
Categorically, the Can
datatype represents the
pointed product
in the category Hask* of pointed Hask types. The category Hask* consists of
Hask types affixed with a dedicated base point of an object along with the object - i.e.
in Hask. Hence, the product is
Maybe
a(1 + a) * (1 + b) ~ 1 + a + b + a*b
, or
in Hask. Pictorially, you can visualize
this as:Maybe
(These
a b)
Can
:
a
|
Non +---+---+ (a,b)
|
b
The fact that we can think about Can
as your average product gives us
some reasoning power about how this thing will be able to interact with the
coproduct in Hask*, called Wedge
. Namely, facts about currying
Can a b -> c ~ a -> b -> c
and distributivity over Wedge
along with other facts about its associativity, commutativity, and
any other analogy with (',')
that you can think of.
The Can
data type represents values with two non-exclusive
possibilities, as well as an empty case. This is a product of pointed types -
i.e. of Maybe
values. The result is a type,
, which is isomorphic
to Can
a b
.Maybe
(These
a b)
Instances
Bitraversable Can Source # | |
Defined in Data.Can bitraverse :: Applicative f => (a -> f c) -> (b -> f d) -> Can a b -> f (Can c d) # | |
Bifoldable Can Source # | |
Bifunctor Can Source # | |
Eq2 Can Source # | |
Ord2 Can Source # | |
Read2 Can Source # | |
Defined in Data.Can liftReadsPrec2 :: (Int -> ReadS a) -> ReadS [a] -> (Int -> ReadS b) -> ReadS [b] -> Int -> ReadS (Can a b) # liftReadList2 :: (Int -> ReadS a) -> ReadS [a] -> (Int -> ReadS b) -> ReadS [b] -> ReadS [Can a b] # liftReadPrec2 :: ReadPrec a -> ReadPrec [a] -> ReadPrec b -> ReadPrec [b] -> ReadPrec (Can a b) # liftReadListPrec2 :: ReadPrec a -> ReadPrec [a] -> ReadPrec b -> ReadPrec [b] -> ReadPrec [Can a b] # | |
Show2 Can Source # | |
NFData2 Can Source # | |
Biapplicative Can Source # | |
Hashable2 Can Source # | |
Semigroup a => Monad (Can a) Source # | |
Functor (Can a) Source # | |
Semigroup a => Applicative (Can a) Source # | |
Foldable (Can a) Source # | |
Defined in Data.Can fold :: Monoid m => Can a m -> m # foldMap :: Monoid m => (a0 -> m) -> Can a a0 -> m # foldMap' :: Monoid m => (a0 -> m) -> Can a a0 -> m # foldr :: (a0 -> b -> b) -> b -> Can a a0 -> b # foldr' :: (a0 -> b -> b) -> b -> Can a a0 -> b # foldl :: (b -> a0 -> b) -> b -> Can a a0 -> b # foldl' :: (b -> a0 -> b) -> b -> Can a a0 -> b # foldr1 :: (a0 -> a0 -> a0) -> Can a a0 -> a0 # foldl1 :: (a0 -> a0 -> a0) -> Can a a0 -> a0 # elem :: Eq a0 => a0 -> Can a a0 -> Bool # maximum :: Ord a0 => Can a a0 -> a0 # minimum :: Ord a0 => Can a a0 -> a0 # | |
Traversable (Can a) Source # | |
Eq a => Eq1 (Can a) Source # | |
Ord a => Ord1 (Can a) Source # | |
Read a => Read1 (Can a) Source # | |
Defined in Data.Can | |
Show a => Show1 (Can a) Source # | |
Semigroup a => MonadZip (Can a) Source # | |
Semigroup a => Alternative (Can a) Source # | |
Semigroup a => MonadPlus (Can a) Source # | |
NFData a => NFData1 (Can a) Source # | |
Hashable a => Hashable1 (Can a) Source # | |
Generic1 (Can a :: Type -> Type) Source # | |
(Eq a, Eq b) => Eq (Can a b) Source # | |
(Data a, Data b) => Data (Can a b) Source # | |
Defined in Data.Can gfoldl :: (forall d b0. Data d => c (d -> b0) -> d -> c b0) -> (forall g. g -> c g) -> Can a b -> c (Can a b) # gunfold :: (forall b0 r. Data b0 => c (b0 -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Can a b) # toConstr :: Can a b -> Constr # dataTypeOf :: Can a b -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Can a b)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Can a b)) # gmapT :: (forall b0. Data b0 => b0 -> b0) -> Can a b -> Can a b # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Can a b -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Can a b -> r # gmapQ :: (forall d. Data d => d -> u) -> Can a b -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Can a b -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Can a b -> m (Can a b) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Can a b -> m (Can a b) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Can a b -> m (Can a b) # | |
(Ord a, Ord b) => Ord (Can a b) Source # | |
(Read a, Read b) => Read (Can a b) Source # | |
(Show a, Show b) => Show (Can a b) Source # | |
Generic (Can a b) Source # | |
(Semigroup a, Semigroup b) => Semigroup (Can a b) Source # | |
(Semigroup a, Semigroup b) => Monoid (Can a b) Source # | |
(Lift a, Lift b) => Lift (Can a b) Source # | |
(Binary a, Binary b) => Binary (Can a b) Source # | |
(NFData a, NFData b) => NFData (Can a b) Source # | |
(Hashable a, Hashable b) => Hashable (Can a b) Source # | |
type Rep1 (Can a :: Type -> Type) Source # | |
Defined in Data.Can type Rep1 (Can a :: Type -> Type) = D1 ('MetaData "Can" "Data.Can" "smash-0.1.2-inplace" 'False) ((C1 ('MetaCons "Non" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "One" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a))) :+: (C1 ('MetaCons "Eno" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) Par1) :+: C1 ('MetaCons "Two" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) Par1))) | |
type Rep (Can a b) Source # | |
Defined in Data.Can type Rep (Can a b) = D1 ('MetaData "Can" "Data.Can" "smash-0.1.2-inplace" 'False) ((C1 ('MetaCons "Non" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "One" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a))) :+: (C1 ('MetaCons "Eno" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 b)) :+: C1 ('MetaCons "Two" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 b)))) |
Type synonyms
Combinators
Eliminators
:: c | default value to supply for the |
-> (a -> c) | eliminator for the |
-> (b -> c) | eliminator for the |
-> (a -> b -> c) | eliminator for the |
-> Can a b | |
-> c |
Case elimination for the Can
datatype
:: c | default value to supply for the |
-> (a -> c) | eliminator for the |
-> (b -> c) | eliminator for the |
-> (c -> c -> c) | merger for the |
-> Can a b | |
-> c |
Case elimination for the Can
datatype, with uniform behaviour.
:: Applicative m | |
=> Monoid c | |
=> (a -> m c) | eliminator for the |
-> (b -> m c) | eliminator for the |
-> Can a b | |
-> m c |
Case elimination for the Can
datatype, with uniform behaviour over a
Monoid
result in the context of an Applicative
.
Folding and Unfolding
gatherCans :: Can [a] [b] -> [Can a b] Source #
unfoldr :: Alternative f => (b -> Can a b) -> b -> f a Source #
Unfold from right to left into a pointed product. For a variant
that accumulates in the seed instead of just updating with a
new value, see accumUntil
and accumUntilM
.
unfoldrM :: (Monad m, Alternative f) => (b -> m (Can a b)) -> b -> m (f a) Source #
Unfold from right to left into a monadic computation over a pointed product
iterateUntil :: Alternative f => (b -> Can a b) -> b -> f a Source #
Iterate on a seed, accumulating a result. See iterateUntilM
for
more details.
iterateUntilM :: Monad m => Alternative f => (b -> m (Can a b)) -> b -> m (f a) Source #
Iterate on a seed, which may result in one of four scenarios:
- The function yields a
Non
value, which terminates the iteration. - The function yields a
One
value. - The function yields a
Eno
value, which changes the seed and iteration continues with the new seed. - The function yields the
a
value of aTwo
case.
accumUntil :: Alternative f => Monoid b => (b -> Can a b) -> f a Source #
Iterate on a seed, accumulating values and monoidally updating the seed with each update.
accumUntilM :: Monad m => Alternative f => Monoid b => (b -> m (Can a b)) -> m (f a) Source #
Iterate on a seed, accumulating values and monoidally updating a seed within a monad.
Filtering
Curry & Uncurry
Partitioning
partitionCans :: Foldable t => Alternative f => t (Can a b) -> (f a, f b) Source #
partitionAll :: Foldable f => f (Can a b) -> ([a], [b], [(a, b)]) Source #
Partition a list of Can
values into a triple of lists of
all of their constituent parts
mapCans :: Traversable t => Alternative f => (a -> Can b c) -> t a -> (f b, f c) Source #
Distributivity
codistributeCan :: Either (Can a c) (Can b c) -> Can (Either a b) c Source #
Codistribute a coproduct over a Can
value.
Associativity
reassocLR :: Can (Can a b) c -> Can a (Can b c) Source #
Re-associate a Can
of cans from left to right.
reassocRL :: Can a (Can b c) -> Can (Can a b) c Source #
Re-associate a Can
of cans from right to left.