smash-0.1.2: Combinators for Maybe types
Copyright(c) 2020-2021 Emily Pillmore
LicenseBSD-3-Clause
MaintainerEmily Pillmore <emilypi@cohomolo.gy>
StabilityExperimental
PortabilityCPP, RankNTypes, TypeApplications
Safe HaskellSafe
LanguageHaskell2010

Data.Can

Description

This module contains the definition for the Can datatype. In practice, this type is isomorphic to Maybe These - the type with two possibly non-exclusive values and an empty case.

Synopsis

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. Maybe a in Hask. Hence, the product is (1 + a) * (1 + b) ~ 1 + a + b + a*b, or Maybe (These a b) in Hask. Pictorially, you can visualize this as:

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.

data Can a b Source #

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, Can a b, which is isomorphic to Maybe (These a b).

Constructors

Non 
One a 
Eno b 
Two a b 

Instances

Instances details
Bitraversable Can Source # 
Instance details

Defined in Data.Can

Methods

bitraverse :: Applicative f => (a -> f c) -> (b -> f d) -> Can a b -> f (Can c d) #

Bifoldable Can Source # 
Instance details

Defined in Data.Can

Methods

bifold :: Monoid m => Can m m -> m #

bifoldMap :: Monoid m => (a -> m) -> (b -> m) -> Can a b -> m #

bifoldr :: (a -> c -> c) -> (b -> c -> c) -> c -> Can a b -> c #

bifoldl :: (c -> a -> c) -> (c -> b -> c) -> c -> Can a b -> c #

Bifunctor Can Source # 
Instance details

Defined in Data.Can

Methods

bimap :: (a -> b) -> (c -> d) -> Can a c -> Can b d #

first :: (a -> b) -> Can a c -> Can b c #

second :: (b -> c) -> Can a b -> Can a c #

Eq2 Can Source # 
Instance details

Defined in Data.Can

Methods

liftEq2 :: (a -> b -> Bool) -> (c -> d -> Bool) -> Can a c -> Can b d -> Bool #

Ord2 Can Source # 
Instance details

Defined in Data.Can

Methods

liftCompare2 :: (a -> b -> Ordering) -> (c -> d -> Ordering) -> Can a c -> Can b d -> Ordering #

Read2 Can Source # 
Instance details

Defined in Data.Can

Methods

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

Defined in Data.Can

Methods

liftShowsPrec2 :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> (Int -> b -> ShowS) -> ([b] -> ShowS) -> Int -> Can a b -> ShowS #

liftShowList2 :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> (Int -> b -> ShowS) -> ([b] -> ShowS) -> [Can a b] -> ShowS #

Biapplicative Can Source # 
Instance details

Defined in Data.Can

Methods

bipure :: a -> b -> Can a b #

(<<*>>) :: Can (a -> b) (c -> d) -> Can a c -> Can b d #

biliftA2 :: (a -> b -> c) -> (d -> e -> f) -> Can a d -> Can b e -> Can c f #

(*>>) :: Can a b -> Can c d -> Can c d #

(<<*) :: Can a b -> Can c d -> Can a b #

NFData2 Can Source # 
Instance details

Defined in Data.Can

Methods

liftRnf2 :: (a -> ()) -> (b -> ()) -> Can a b -> () #

Hashable2 Can Source # 
Instance details

Defined in Data.Can

Methods

liftHashWithSalt2 :: (Int -> a -> Int) -> (Int -> b -> Int) -> Int -> Can a b -> Int #

(Lift a, Lift b) => Lift (Can a b :: Type) Source # 
Instance details

Defined in Data.Can

Methods

lift :: Can a b -> Q Exp #

liftTyped :: Can a b -> Q (TExp (Can a b)) #

Semigroup a => Monad (Can a) Source # 
Instance details

Defined in Data.Can

Methods

(>>=) :: Can a a0 -> (a0 -> Can a b) -> Can a b #

(>>) :: Can a a0 -> Can a b -> Can a b #

return :: a0 -> Can a a0 #

Functor (Can a) Source # 
Instance details

Defined in Data.Can

Methods

fmap :: (a0 -> b) -> Can a a0 -> Can a b #

(<$) :: a0 -> Can a b -> Can a a0 #

Semigroup a => Applicative (Can a) Source # 
Instance details

Defined in Data.Can

Methods

pure :: a0 -> Can a a0 #

(<*>) :: Can a (a0 -> b) -> Can a a0 -> Can a b #

liftA2 :: (a0 -> b -> c) -> Can a a0 -> Can a b -> Can a c #

(*>) :: Can a a0 -> Can a b -> Can a b #

(<*) :: Can a a0 -> Can a b -> Can a a0 #

Foldable (Can a) Source # 
Instance details

Defined in Data.Can

Methods

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 #

toList :: Can a a0 -> [a0] #

null :: Can a a0 -> Bool #

length :: Can a a0 -> Int #

elem :: Eq a0 => a0 -> Can a a0 -> Bool #

maximum :: Ord a0 => Can a a0 -> a0 #

minimum :: Ord a0 => Can a a0 -> a0 #

sum :: Num a0 => Can a a0 -> a0 #

product :: Num a0 => Can a a0 -> a0 #

Traversable (Can a) Source # 
Instance details

Defined in Data.Can

Methods

traverse :: Applicative f => (a0 -> f b) -> Can a a0 -> f (Can a b) #

sequenceA :: Applicative f => Can a (f a0) -> f (Can a a0) #

mapM :: Monad m => (a0 -> m b) -> Can a a0 -> m (Can a b) #

sequence :: Monad m => Can a (m a0) -> m (Can a a0) #

Eq a => Eq1 (Can a) Source # 
Instance details

Defined in Data.Can

Methods

liftEq :: (a0 -> b -> Bool) -> Can a a0 -> Can a b -> Bool #

Ord a => Ord1 (Can a) Source # 
Instance details

Defined in Data.Can

Methods

liftCompare :: (a0 -> b -> Ordering) -> Can a a0 -> Can a b -> Ordering #

Read a => Read1 (Can a) Source # 
Instance details

Defined in Data.Can

Methods

liftReadsPrec :: (Int -> ReadS a0) -> ReadS [a0] -> Int -> ReadS (Can a a0) #

liftReadList :: (Int -> ReadS a0) -> ReadS [a0] -> ReadS [Can a a0] #

liftReadPrec :: ReadPrec a0 -> ReadPrec [a0] -> ReadPrec (Can a a0) #

liftReadListPrec :: ReadPrec a0 -> ReadPrec [a0] -> ReadPrec [Can a a0] #

Show a => Show1 (Can a) Source # 
Instance details

Defined in Data.Can

Methods

liftShowsPrec :: (Int -> a0 -> ShowS) -> ([a0] -> ShowS) -> Int -> Can a a0 -> ShowS #

liftShowList :: (Int -> a0 -> ShowS) -> ([a0] -> ShowS) -> [Can a a0] -> ShowS #

Semigroup a => MonadZip (Can a) Source # 
Instance details

Defined in Data.Can

Methods

mzip :: Can a a0 -> Can a b -> Can a (a0, b) #

mzipWith :: (a0 -> b -> c) -> Can a a0 -> Can a b -> Can a c #

munzip :: Can a (a0, b) -> (Can a a0, Can a b) #

Semigroup a => Alternative (Can a) Source # 
Instance details

Defined in Data.Can

Methods

empty :: Can a a0 #

(<|>) :: Can a a0 -> Can a a0 -> Can a a0 #

some :: Can a a0 -> Can a [a0] #

many :: Can a a0 -> Can a [a0] #

Semigroup a => MonadPlus (Can a) Source # 
Instance details

Defined in Data.Can

Methods

mzero :: Can a a0 #

mplus :: Can a a0 -> Can a a0 -> Can a a0 #

NFData a => NFData1 (Can a) Source # 
Instance details

Defined in Data.Can

Methods

liftRnf :: (a0 -> ()) -> Can a a0 -> () #

Hashable a => Hashable1 (Can a) Source # 
Instance details

Defined in Data.Can

Methods

liftHashWithSalt :: (Int -> a0 -> Int) -> Int -> Can a a0 -> Int #

Generic1 (Can a :: Type -> Type) Source # 
Instance details

Defined in Data.Can

Associated Types

type Rep1 (Can a) :: k -> Type #

Methods

from1 :: forall (a0 :: k). Can a a0 -> Rep1 (Can a) a0 #

to1 :: forall (a0 :: k). Rep1 (Can a) a0 -> Can a a0 #

(Eq a, Eq b) => Eq (Can a b) Source # 
Instance details

Defined in Data.Can

Methods

(==) :: Can a b -> Can a b -> Bool #

(/=) :: Can a b -> Can a b -> Bool #

(Data a, Data b) => Data (Can a b) Source # 
Instance details

Defined in Data.Can

Methods

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

Defined in Data.Can

Methods

compare :: Can a b -> Can a b -> Ordering #

(<) :: Can a b -> Can a b -> Bool #

(<=) :: Can a b -> Can a b -> Bool #

(>) :: Can a b -> Can a b -> Bool #

(>=) :: Can a b -> Can a b -> Bool #

max :: Can a b -> Can a b -> Can a b #

min :: Can a b -> Can a b -> Can a b #

(Read a, Read b) => Read (Can a b) Source # 
Instance details

Defined in Data.Can

Methods

readsPrec :: Int -> ReadS (Can a b) #

readList :: ReadS [Can a b] #

readPrec :: ReadPrec (Can a b) #

readListPrec :: ReadPrec [Can a b] #

(Show a, Show b) => Show (Can a b) Source # 
Instance details

Defined in Data.Can

Methods

showsPrec :: Int -> Can a b -> ShowS #

show :: Can a b -> String #

showList :: [Can a b] -> ShowS #

Generic (Can a b) Source # 
Instance details

Defined in Data.Can

Associated Types

type Rep (Can a b) :: Type -> Type #

Methods

from :: Can a b -> Rep (Can a b) x #

to :: Rep (Can a b) x -> Can a b #

(Semigroup a, Semigroup b) => Semigroup (Can a b) Source # 
Instance details

Defined in Data.Can

Methods

(<>) :: Can a b -> Can a b -> Can a b #

sconcat :: NonEmpty (Can a b) -> Can a b #

stimes :: Integral b0 => b0 -> Can a b -> Can a b #

(Semigroup a, Semigroup b) => Monoid (Can a b) Source # 
Instance details

Defined in Data.Can

Methods

mempty :: Can a b #

mappend :: Can a b -> Can a b -> Can a b #

mconcat :: [Can a b] -> Can a b #

(Binary a, Binary b) => Binary (Can a b) Source # 
Instance details

Defined in Data.Can

Methods

put :: Can a b -> Put #

get :: Get (Can a b) #

putList :: [Can a b] -> Put #

(NFData a, NFData b) => NFData (Can a b) Source # 
Instance details

Defined in Data.Can

Methods

rnf :: Can a b -> () #

(Hashable a, Hashable b) => Hashable (Can a b) Source # 
Instance details

Defined in Data.Can

Methods

hashWithSalt :: Int -> Can a b -> Int #

hash :: Can a b -> Int #

type Rep1 (Can a :: Type -> Type) Source # 
Instance details

Defined in Data.Can

type Rep (Can a b) Source # 
Instance details

Defined in Data.Can

Type synonyms

type (⊗) a b = Can a b Source #

A type operator synonym for Can

Combinators

canFst :: Can a b -> Maybe a Source #

Project the left value of a Can datatype. This is analogous to fst for (',').

canSnd :: Can a b -> Maybe b Source #

Project the right value of a Can datatype. This is analogous to snd for (',').

isOne :: Can a b -> Bool Source #

Detect if a Can is a One case.

isEno :: Can a b -> Bool Source #

Detect if a Can is a Eno case.

isTwo :: Can a b -> Bool Source #

Detect if a Can is a Two case.

isNon :: Can a b -> Bool Source #

Detect if a Can is a Non case.

Eliminators

can Source #

Arguments

:: c

default value to supply for the Non case

-> (a -> c)

eliminator for the One case

-> (b -> c)

eliminator for the Eno case

-> (a -> b -> c)

eliminator for the Two case

-> Can a b 
-> c 

Case elimination for the Can datatype

canWithMerge Source #

Arguments

:: c

default value to supply for the Non case

-> (a -> c)

eliminator for the One case

-> (b -> c)

eliminator for the Eno case

-> (c -> c -> c)

merger for the Two case

-> Can a b 
-> c 

Case elimination for the Can datatype, with uniform behaviour.

canEach Source #

Arguments

:: Monoid c 
=> (a -> c)

eliminator for the One case

-> (b -> c)

eliminator for the Eno case

-> Can a b 
-> c 

Case elimination for the Can datatype, with uniform behaviour over a Monoid result.

canEachA Source #

Arguments

:: Applicative m 
=> Monoid c 
=> (a -> m c)

eliminator for the One case

-> (b -> m c)

eliminator for the Eno case

-> 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

foldOnes :: Foldable f => (a -> m -> m) -> m -> f (Can a b) -> m Source #

Fold over the One cases of a Foldable of Cans by some accumulating function.

foldEnos :: Foldable f => (b -> m -> m) -> m -> f (Can a b) -> m Source #

Fold over the Eno cases of a Foldable of Cans by some accumulating function.

foldTwos :: Foldable f => (a -> b -> m -> m) -> m -> f (Can a b) -> m Source #

Fold over the Two cases of a Foldable of Cans by some accumulating function.

gatherCans :: Can [a] [b] -> [Can a b] Source #

Gather a Can of two lists and produce a list of Can values, mapping the Non case to the empty list, One' case to a list of Ones, the Eno case to a list of Enos, or zipping Two along both lists.

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:

  1. The function yields a Non value, which terminates the iteration.
  2. The function yields a One value.
  3. The function yields a Eno value, which changes the seed and iteration continues with the new seed.
  4. The function yields the a value of a Two 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

ones :: Foldable f => f (Can a b) -> [a] Source #

Given a Foldable of Cans, collect the values of the One cases, if any.

enos :: Foldable f => f (Can a b) -> [b] Source #

Given a Foldable of Cans, collect the values of the Eno cases, if any.

twos :: Foldable f => f (Can a b) -> [(a, b)] Source #

Given a Foldable of Cans, collect the values of the Two cases, if any.

filterOnes :: Foldable f => f (Can a b) -> [Can a b] Source #

Filter the One cases of a Foldable of Can values.

filterEnos :: Foldable f => f (Can a b) -> [Can a b] Source #

Filter the Eno cases of a Foldable of Can values.

filterTwos :: Foldable f => f (Can a b) -> [Can a b] Source #

Filter the Two cases of a Foldable of Can values.

filterNons :: Foldable f => f (Can a b) -> [Can a b] Source #

Filter the Non cases of a Foldable of Can values.

Curry & Uncurry

canCurry :: (Can a b -> Maybe c) -> Maybe a -> Maybe b -> Maybe c Source #

Curry a function from a Can to a Maybe value, resulting in a function of curried Maybe values. This is analogous to currying for (->).

canUncurry :: (Maybe a -> Maybe b -> Maybe c) -> Can a b -> Maybe c Source #

Uncurry a function from a Can to a Maybe value, resulting in a function of curried Maybe values. This is analogous to uncurrying for (->).

Partitioning

partitionCans :: Foldable t => Alternative f => t (Can a b) -> (f a, f b) Source #

Given a Foldable of Cans, partition it into a tuple of alternatives their parts.

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

partitionEithers :: Foldable f => f (Either a b) -> Can [a] [b] Source #

Partition a list of Either values, separating them into a Can value of lists of left and right values, or Non in the case of an empty list.

mapCans :: Traversable t => Alternative f => (a -> Can b c) -> t a -> (f b, f c) Source #

Partition a structure by mapping its contents into Cans, and folding over (<|>).

Distributivity

distributeCan :: Can (a, b) c -> (Can a c, Can b c) Source #

Distribute a Can value over a product.

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.

Symmetry

swapCan :: Can a b -> Can b a Source #

Swap the positions of values in a Can.