smash-0.1.1.0: Combinators for Maybe types

Copyright(c) 2020 Emily Pillmore
LicenseBSD-3-Clause
MaintainerEmily Pillmore <emilypi@cohomolo.gy>
StabilityExperimental
PortabilityCPP, RankNTypes, TypeApplications
Safe HaskellSafe
LanguageHaskell2010

Data.Smash

Contents

Description

This module contains the definition for the Smash datatype. In practice, this type is isomorphic to 'Maybe (a,b)' - the type with two possibly non-exclusive values and an empty case.

Synopsis

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 'Maybe a'. The smash product is a symmetric, monoidal tensor in Hask* that plays nicely with the product, Can, and coproduct, Wedge. Pictorially, these datatypes look like this:

Can:
        a
        |
Non +---+---+ (a,b)
        |
        b

Wedge:
                a
                |
Nowhere +-------+
                |
                b


Smash:


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.

data Smash a b Source #

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

Constructors

Nada 
Smash a b 
Instances
Bitraversable Smash Source # 
Instance details

Defined in Data.Smash

Methods

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

Bifoldable Smash Source # 
Instance details

Defined in Data.Smash

Methods

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

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

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

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

Bifunctor Smash Source # 
Instance details

Defined in Data.Smash

Methods

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

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

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

Monoid a => Monad (Smash a) Source # 
Instance details

Defined in Data.Smash

Methods

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

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

return :: a0 -> Smash a a0 #

fail :: String -> Smash a a0 #

Functor (Smash a) Source # 
Instance details

Defined in Data.Smash

Methods

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

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

Monoid a => Applicative (Smash a) Source # 
Instance details

Defined in Data.Smash

Methods

pure :: a0 -> Smash a a0 #

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

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

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

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

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

Defined in Data.Smash

Associated Types

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

Methods

from1 :: Smash a a0 -> Rep1 (Smash a) a0 #

to1 :: Rep1 (Smash a) a0 -> Smash a a0 #

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

Defined in Data.Smash

Methods

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

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

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

Defined in Data.Smash

Methods

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

Defined in Data.Smash

Methods

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

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

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

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

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

max :: Smash a b -> Smash a b -> Smash a b #

min :: Smash a b -> Smash a b -> Smash a b #

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

Defined in Data.Smash

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

Defined in Data.Smash

Methods

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

show :: Smash a b -> String #

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

Generic (Smash a b) Source # 
Instance details

Defined in Data.Smash

Associated Types

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

Methods

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

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

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

Defined in Data.Smash

Methods

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

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

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

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

Defined in Data.Smash

Methods

mempty :: Smash a b #

mappend :: Smash a b -> Smash a b -> Smash a b #

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

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

Defined in Data.Smash

Methods

put :: Smash a b -> Put #

get :: Get (Smash a b) #

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

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

Defined in Data.Smash

Methods

rnf :: Smash a b -> () #

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

Defined in Data.Smash

Methods

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

hash :: Smash a b -> Int #

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

Defined in Data.Smash

type Rep (Smash a b) Source # 
Instance details

Defined in Data.Smash

type Rep (Smash a b) = D1 (MetaData "Smash" "Data.Smash" "smash-0.1.1.0-8T61bCPN60yH3RLoZzb2ua" 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)))

Combinators

toSmash :: Maybe (a, b) -> Smash a b Source #

Convert a Maybe value into a Smash value

fromSmash :: Smash a b -> Maybe (a, b) Source #

Convert a Smash value into a Maybe value

smashFst :: Smash a b -> Maybe a Source #

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

smashSnd :: Smash a b -> Maybe b Source #

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

quotSmash :: Can a b -> Smash a b Source #

Smash product of pointed type modulo its wedge

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

isSmash :: Smash a b -> Bool Source #

Detect whether a Smash value is not empty

isNada :: Smash a b -> Bool Source #

Detect whether a Smash value is empty

Eliminators

smash :: c -> (a -> b -> c) -> Smash a b -> c Source #

Case elimination for the Smash datatype

Filtering

smashes :: Foldable f => f (Smash a b) -> [(a, b)] Source #

Given a Foldable of Smashs, collect the values of the Smash cases, if any.

filterNadas :: Foldable f => f (Smash a b) -> [Smash a b] Source #

Filter the Nada cases of a Foldable of Smash values.

Folding

foldSmashes :: Foldable f => (a -> b -> m -> m) -> m -> f (Smash a b) -> m Source #

Fold over the Smash case of a Foldable of Smash products by some accumulatig function.

gatherSmashes :: Smash [a] [b] -> [Smash a b] Source #

Gather a Smash product of two lists and product a list of Smash values, mapping the Nada case to the empty list and zipping the two lists together with the Smash constructor otherwise.

Partitioning

partitionSmashes :: forall f t a b. (Foldable t, Alternative f) => t (Smash a b) -> (f a, f b) Source #

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

mapSmashes :: forall f t a b c. (Alternative f, Traversable t) => (a -> Smash b c) -> t a -> (f b, f c) Source #

Partition a structure by mapping its contents into Smashs, and folding over '(|)'.

Currying & Uncurrying

smashCurry :: (Smash a b -> Maybe c) -> Maybe a -> Maybe b -> Maybe c Source #

Curry a map from a smash product to a pointed type. This is analogous to curry for '(->)'.

smashUncurry :: (Maybe a -> Maybe b -> Maybe c) -> Smash a b -> Maybe c Source #

Uncurry a map of pointed types to a map of a smash product to a pointed type. This is analogous to uncurry for '(->)'.

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 (Wedges) 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 (Wedges) in pointed Hask

pairSmash :: Smash (a, b) c -> (Smash a c, Smash b c) Source #

Distribute a Smash of a pair into a pair of Smashs

unpairSmash :: (Smash a c, Smash b c) -> Smash (a, b) c Source #

Distribute a Smash of a pair into a pair of Smashs

pairSmashCan :: Smash (Can a b) c -> Can (Smash a c) (Smash b c) Source #

Distribute a Smash of a Can into a Can of Smashs

unpairSmashCan :: Can (Smash a c) (Smash b c) -> Smash (Can a b) c Source #

Unistribute a Can of Smashs into a Smash of Cans.

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.

Symmetry

swapSmash :: Smash a b -> Smash b a Source #

Swap the positions of values in a 'Smash a b' to form a 'Smash b a'.