unpacked-these-0.1.0.0: An unpacked these data type

Safe HaskellNone
LanguageHaskell2010

Data.These.Unpacked

Contents

Description

The These type and associated operations.

This module is intended to be a drop-in(*) replacement for Data.These. To shave off pointer chasing, it uses -XUnboxedSums to represent the These type as two machine words that are contiguous in memory, without loss of expressiveness that These provides.

This library provides pattern synonyms This, That, and Both(*), which allow users to pattern match on an Unpacked These in a familiar way.

Functions are also provided for converting an Unpacked These to the these library's These, and vice versa.

(*): pattern synonyms use the same namespace as type constructors, so pattern matching on an Unpacked These with the more familiar These data constructor is not possible, instead, Both is provided.

This library is in alpha, and the internals are likely to change.

Synopsis

Documentation

data These a b where Source #

The These type represents values with two non-exclusive possibilities.

This can be useful to represent combinations of two values, where the combination is defined if either input is. Algebraically, the type These A B represents (A + B + AB), which doesn't factor easily into sums and products--a type like Either A (B, Maybe A) is unclear and awkward to use.

These has straightforward instances of Functor, Monad, &c., and behaves like a hybrid error/writer monad, as would be expected.

Bundled Patterns

pattern This :: a -> These a b 
pattern That :: b -> These a b 
pattern Both :: a -> b -> These a b 

Instances

Bitraversable These Source # 

Methods

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

Bifoldable These Source # 

Methods

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

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

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

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

Bifunctor These Source # 

Methods

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

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

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

Semigroup a => Monad (These a) Source # 

Methods

(>>=) :: These a a -> (a -> These a b) -> These a b #

(>>) :: These a a -> These a b -> These a b #

return :: a -> These a a #

fail :: String -> These a a #

Functor (These a) Source # 

Methods

fmap :: (a -> b) -> These a a -> These a b #

(<$) :: a -> These a b -> These a a #

Semigroup a => Applicative (These a) Source # 

Methods

pure :: a -> These a a #

(<*>) :: These a (a -> b) -> These a a -> These a b #

liftA2 :: (a -> b -> c) -> These a a -> These a b -> These a c #

(*>) :: These a a -> These a b -> These a b #

(<*) :: These a a -> These a b -> These a a #

Foldable (These a) Source # 

Methods

fold :: Monoid m => These a m -> m #

foldMap :: Monoid m => (a -> m) -> These a a -> m #

foldr :: (a -> b -> b) -> b -> These a a -> b #

foldr' :: (a -> b -> b) -> b -> These a a -> b #

foldl :: (b -> a -> b) -> b -> These a a -> b #

foldl' :: (b -> a -> b) -> b -> These a a -> b #

foldr1 :: (a -> a -> a) -> These a a -> a #

foldl1 :: (a -> a -> a) -> These a a -> a #

toList :: These a a -> [a] #

null :: These a a -> Bool #

length :: These a a -> Int #

elem :: Eq a => a -> These a a -> Bool #

maximum :: Ord a => These a a -> a #

minimum :: Ord a => These a a -> a #

sum :: Num a => These a a -> a #

product :: Num a => These a a -> a #

Traversable (These a) Source # 

Methods

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

sequenceA :: Applicative f => These a (f a) -> f (These a a) #

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

sequence :: Monad m => These a (m a) -> m (These a a) #

(Eq a, Eq b) => Eq (These a b) Source # 

Methods

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

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

(Data a, Data b) => Data (These a b) Source # 

Methods

gfoldl :: (forall d c. Data d => c (d -> c) -> d -> c c) -> (forall g. g -> c g) -> These a b -> c (These a b) #

gunfold :: (forall c r. Data c => c (c -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (These a b) #

toConstr :: These a b -> Constr #

dataTypeOf :: These a b -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c (These a b)) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (These a b)) #

gmapT :: (forall c. Data c => c -> c) -> These a b -> These a b #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> These a b -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> These a b -> r #

gmapQ :: (forall d. Data d => d -> u) -> These a b -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> These a b -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> These a b -> m (These a b) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> These a b -> m (These a b) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> These a b -> m (These a b) #

(Ord a, Ord b) => Ord (These a b) Source # 

Methods

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

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

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

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

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

max :: These a b -> These a b -> These a b #

min :: These a b -> These a b -> These a b #

(Read a, Read b) => Read (These a b) Source # 
(Show a, Show b) => Show (These a b) Source # 

Methods

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

show :: These a b -> String #

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

(Semigroup a, Semigroup b) => Semigroup (These a b) Source # 

Methods

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

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

stimes :: Integral b => b -> These a b -> These a b #

(NFData a, NFData b) => NFData (These a b) Source # 

Methods

rnf :: These a b -> () #

Consumption

these :: (a -> c) -> (b -> c) -> (a -> b -> c) -> These a b -> c Source #

Case analysis for the These type.

fromThese :: a -> b -> These a b -> (a, b) Source #

Takes two default values and produces a tuple if the These value is not This or That.

mergeThese :: (a -> a -> a) -> These a a -> a Source #

Coalesce with the provided operation.

mergeTheseWith :: (a -> c) -> (b -> c) -> (c -> c -> c) -> These a b -> c Source #

bimap and coalesce results with the provided operation.

Traversals

here :: Applicative f => (a -> f b) -> These a t -> f (These b t) Source #

A Traversal of the first half of a These, suitable for use with Control.Lens.

there :: Applicative f => (a -> f b) -> These t a -> f (These t b) Source #

A Traversal of the second half of a These, suitable for use with Control.Lens.

Case selections

justThis :: These a b -> Maybe a Source #

justThis = these Just (_ -> Nothing) (_ _ -> Nothing)

justThat :: These a b -> Maybe b Source #

justThat = these (_ -> Nothing) Just (_ _ -> Nothing)

justThese :: These a b -> Maybe (a, b) Source #

justThese = these (_ -> Nothing) (_ -> Nothing) (a b -> Just (a, b))

catThis :: [These a b] -> [a] Source #

Select all This constructors from a list.

catThat :: [These a b] -> [b] Source #

Select all That constructors from a list.

catThese :: [These a b] -> [(a, b)] Source #

Select all Both constructors from a list.

partitionThese :: [These a b] -> ([(a, b)], ([a], [b])) Source #

Select each constructor and partition them into separate lists.

Case predicates

Map operations

mapThese :: (a -> c) -> (b -> d) -> These a b -> These c d Source #

Bifunctor's bimap

mapThis :: (a -> c) -> These a b -> These c b Source #

Bifunctor's first

mapThat :: (b -> d) -> These a b -> These a d Source #

Bifunctor's second

Conversions

fromBaseThese :: These a b -> These a b Source #

Convert a These from Data.These to a These

toBaseThese :: These a b -> These a b Source #

Convert a These to a These from Data.These