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 Smash a b
- type (⨳) a b = Smash a b
- toSmash :: Maybe (a, b) -> Smash a b
- fromSmash :: Smash a b -> Maybe (a, b)
- smashFst :: Smash a b -> Maybe a
- smashSnd :: Smash a b -> Maybe b
- quotSmash :: Can a b -> Smash a b
- hulkSmash :: a -> b -> Wedge a b -> Smash a b
- isSmash :: Smash a b -> Bool
- isNada :: Smash a b -> Bool
- smashDiag :: Maybe a -> Smash a a
- smashDiag' :: a -> Smash a a
- smash :: c -> (a -> b -> c) -> Smash a b -> c
- smashes :: Foldable f => f (Smash a b) -> [(a, b)]
- filterNadas :: Foldable f => f (Smash a b) -> [Smash a b]
- foldSmashes :: Foldable f => (a -> b -> m -> m) -> m -> f (Smash a b) -> m
- gatherSmashes :: Smash [a] [b] -> [Smash a b]
- unfoldr :: Alternative f => (b -> Smash a b) -> b -> f a
- unfoldrM :: (Monad m, Alternative f) => (b -> m (Smash a b)) -> b -> m (f a)
- iterateUntil :: Alternative f => (b -> Smash a b) -> b -> f a
- iterateUntilM :: Monad m => Alternative f => (b -> m (Smash a b)) -> b -> m (f a)
- accumUntil :: Alternative f => Monoid b => (b -> Smash a b) -> f a
- accumUntilM :: Monad m => Alternative f => Monoid b => (b -> m (Smash a b)) -> m (f a)
- partitionSmashes :: Alternative f => Foldable t => t (Smash a b) -> (f a, f b)
- mapSmashes :: Alternative f => Traversable t => (a -> Smash b c) -> t a -> (f b, f c)
- eqSmash :: Equivalence (Smash a b)
- smashCurry :: (Smash a b -> Maybe c) -> Maybe a -> Maybe b -> Maybe c
- smashUncurry :: (Maybe a -> Maybe b -> Maybe c) -> Smash a b -> Maybe c
- distributeSmash :: Smash (Wedge a b) c -> Wedge (Smash a c) (Smash b c)
- undistributeSmash :: Wedge (Smash a c) (Smash b c) -> Smash (Wedge a b) c
- pairSmash :: Smash (a, b) c -> (Smash a c, Smash b c)
- unpairSmash :: (Smash a c, Smash b c) -> Smash (a, b) c
- pairSmashCan :: Smash (Can a b) c -> Can (Smash a c) (Smash b c)
- unpairSmashCan :: Can (Smash a c) (Smash b c) -> Smash (Can a b) c
- reassocLR :: Smash (Smash a b) c -> Smash a (Smash b c)
- reassocRL :: Smash a (Smash b c) -> Smash (Smash a b) c
- swapSmash :: Smash a b -> Smash b a
Datatypes
Categorically, the Smash
datatype represents a special type of product, a
smash product, in the category Hask*
of pointed Hask types. The category Hask* consists of Hask types affixed with
a dedicated base point - i.e. all objects look like
. The smash product is a symmetric, monoidal tensor in Hask* that plays
nicely with the product, Maybe
aCan
, and coproduct, Wedge
. Pictorially,
these datatypes look like this:
Can
: a | Non +---+---+ (a,b) | bWedge
: a | Nowhere +-------+ | bSmash
: Nada +--------+ (a,b)
The fact that smash products form a closed, symmetric monoidal tensor for Hask*
means that we can speak in terms of the language of linear logic for this category.
Namely, we can understand how Smash
, Wedge
, and Can
interact. Can
and Wedge
distribute nicely over each other, and Smash
distributes well over Wedge
, but
is only semi-distributable over Wedge'
s linear counterpart, which is left
out of the api. In this library, we focus on the fragment of this pointed linear logic
that makes sense to use, and that will be useful to us as Haskell developers.
The Smash
data type represents A value which has either an
empty case, or two values. The result is a type, 'Smash a b', which is
isomorphic to
.Maybe
(a,b)
Categorically, the smash product (the quotient of a pointed product by
a wedge sum) has interesting properties. It forms a closed
symmetric-monoidal tensor in the category Hask* of pointed haskell
types (i.e. Maybe
values).
Instances
Type synonyms
Combinators
hulkSmash :: a -> b -> Wedge a b -> Smash a b Source #
Take the smash product of a wedge and two default values to place in either the left or right side of the final product
smashDiag :: Maybe a -> Smash a a Source #
Create a smash product of self-similar values from a pointed object.
This is the diagonal morphism in Hask*.
Eliminators
Filtering
Folding and Unfolding
foldSmashes :: Foldable f => (a -> b -> m -> m) -> m -> f (Smash a b) -> m Source #
gatherSmashes :: Smash [a] [b] -> [Smash a b] Source #
unfoldr :: Alternative f => (b -> Smash a b) -> b -> f a Source #
Unfold from right to left into a smash product
unfoldrM :: (Monad m, Alternative f) => (b -> m (Smash a b)) -> b -> m (f a) Source #
Unfold from right to left into a monadic computation over a smash product
iterateUntil :: Alternative f => (b -> Smash 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 (Smash a b)) -> b -> m (f a) Source #
Iterate on a seed, which may result in one of two scenarios:
- The function yields a
Nada
value, which terminates the iteration. - The function yields a
Smash
value.
accumUntil :: Alternative f => Monoid b => (b -> Smash 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 (Smash a b)) -> m (f a) Source #
Iterate on a seed, accumulating values and monoidally updating a seed within a monad.
Partitioning
partitionSmashes :: Alternative f => Foldable t => t (Smash a b) -> (f a, f b) Source #
mapSmashes :: Alternative f => Traversable t => (a -> Smash b c) -> t a -> (f b, f c) Source #
eqSmash :: Equivalence (Smash a b) Source #
Equivalence relation formed by grouping of equal Smash
constructors.
Currying & Uncurrying
Distributivity
distributeSmash :: Smash (Wedge a b) c -> Wedge (Smash a c) (Smash b c) Source #
A smash product of wedges is a wedge of smash products.
Smash products distribute over coproducts (Wedge
s) in pointed Hask
undistributeSmash :: Wedge (Smash a c) (Smash b c) -> Smash (Wedge a b) c Source #
A wedge of smash products is a smash product of wedges.
Smash products distribute over coproducts (Wedge
s) in pointed Hask
Associativity
reassocLR :: Smash (Smash a b) c -> Smash a (Smash b c) Source #
Reassociate a Smash
product from left to right.
reassocRL :: Smash a (Smash b c) -> Smash (Smash a b) c Source #
Reassociate a Smash
product from right to left.