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 :: Foldable t => Alternative f => t (Smash a b) -> (f a, f b)
- mapSmashes :: Alternative f => Traversable t => (a -> Smash b c) -> t a -> (f b, f c)
- 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
Bitraversable Smash Source # | |
Defined in Data.Smash bitraverse :: Applicative f => (a -> f c) -> (b -> f d) -> Smash a b -> f (Smash c d) # | |
Bifoldable Smash Source # | |
Bifunctor Smash Source # | |
Eq2 Smash Source # | |
Ord2 Smash Source # | |
Defined in Data.Smash | |
Read2 Smash Source # | |
Defined in Data.Smash liftReadsPrec2 :: (Int -> ReadS a) -> ReadS [a] -> (Int -> ReadS b) -> ReadS [b] -> Int -> ReadS (Smash a b) # liftReadList2 :: (Int -> ReadS a) -> ReadS [a] -> (Int -> ReadS b) -> ReadS [b] -> ReadS [Smash a b] # liftReadPrec2 :: ReadPrec a -> ReadPrec [a] -> ReadPrec b -> ReadPrec [b] -> ReadPrec (Smash a b) # liftReadListPrec2 :: ReadPrec a -> ReadPrec [a] -> ReadPrec b -> ReadPrec [b] -> ReadPrec [Smash a b] # | |
Show2 Smash Source # | |
NFData2 Smash Source # | |
Defined in Data.Smash | |
Biapplicative Smash Source # | |
Hashable2 Smash Source # | |
Defined in Data.Smash | |
Monoid a => Monad (Smash a) Source # | |
Functor (Smash a) Source # | |
Monoid a => Applicative (Smash a) Source # | |
Eq a => Eq1 (Smash a) Source # | |
Ord a => Ord1 (Smash a) Source # | |
Defined in Data.Smash | |
Read a => Read1 (Smash a) Source # | |
Defined in Data.Smash | |
Show a => Show1 (Smash a) Source # | |
Monoid a => MonadZip (Smash a) Source # | |
Monoid a => Alternative (Smash a) Source # | |
Monoid a => MonadPlus (Smash a) Source # | |
NFData a => NFData1 (Smash a) Source # | |
Defined in Data.Smash | |
Hashable a => Hashable1 (Smash a) Source # | |
Defined in Data.Smash | |
Generic1 (Smash a :: Type -> Type) Source # | |
(Eq a, Eq b) => Eq (Smash a b) Source # | |
(Data a, Data b) => Data (Smash a b) Source # | |
Defined in Data.Smash gfoldl :: (forall d b0. Data d => c (d -> b0) -> d -> c b0) -> (forall g. g -> c g) -> Smash a b -> c (Smash a b) # gunfold :: (forall b0 r. Data b0 => c (b0 -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Smash a b) # toConstr :: Smash a b -> Constr # dataTypeOf :: Smash a b -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Smash a b)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Smash a b)) # gmapT :: (forall b0. Data b0 => b0 -> b0) -> Smash a b -> Smash a b # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Smash a b -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Smash a b -> r # gmapQ :: (forall d. Data d => d -> u) -> Smash a b -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Smash a b -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Smash a b -> m (Smash a b) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Smash a b -> m (Smash a b) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Smash a b -> m (Smash a b) # | |
(Ord a, Ord b) => Ord (Smash a b) Source # | |
Defined in Data.Smash | |
(Read a, Read b) => Read (Smash a b) Source # | |
(Show a, Show b) => Show (Smash a b) Source # | |
Generic (Smash a b) Source # | |
(Semigroup a, Semigroup b) => Semigroup (Smash a b) Source # | |
(Semigroup a, Semigroup b) => Monoid (Smash a b) Source # | |
(Lift a, Lift b) => Lift (Smash a b) Source # | |
(Binary a, Binary b) => Binary (Smash a b) Source # | |
(NFData a, NFData b) => NFData (Smash a b) Source # | |
Defined in Data.Smash | |
(Hashable a, Hashable b) => Hashable (Smash a b) Source # | |
Defined in Data.Smash | |
type Rep1 (Smash a :: Type -> Type) Source # | |
Defined in Data.Smash type Rep1 (Smash a :: Type -> Type) = D1 ('MetaData "Smash" "Data.Smash" "smash-0.1.2-inplace" 'False) (C1 ('MetaCons "Nada" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Smash" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) Par1)) | |
type Rep (Smash a b) Source # | |
Defined in Data.Smash type Rep (Smash a b) = D1 ('MetaData "Smash" "Data.Smash" "smash-0.1.2-inplace" 'False) (C1 ('MetaCons "Nada" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Smash" '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
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 :: Foldable t => Alternative f => 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 #
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.