partial-semigroup-0.6.0.2: A partial binary associative operator
Safe HaskellSafe-Inferred
LanguageGHC2021

Data.PartialSemigroup

Description

A semigroup (Semigroup) is a set with a binary associative operation (<>).

This module defines a partial semigroup (PartialSemigroup), a semigroup for which <> is not required to be defined over all inputs.

Synopsis

Partial semigroup

class PartialSemigroup a where Source #

A PartialSemigroup is like a Semigroup, but with an operator returning Maybe a rather than a.

For comparison:

(<>)  :: Semigroup a        => a -> a -> a
(<>?) :: PartialSemigroup a => a -> a -> Maybe a

The associativity axiom for partial semigroups

For all x, y, z:

Relationship to the semigroup associativity axiom

The partial semigroup associativity axiom is a natural adaptation of the semigroup associativity axiom

x <> (y <> z) = (x <> y) <> z

with a slight modification to accommodate situations where <> is undefined. We may gain some insight into the connection between Semigroup and PartialSemigroup by rephrasing the partial semigroup associativity in terms of a partial <> operator thusly:

For all x, y, z:

  • If x <> y and y <> z are both defined, then

    • x <> (y <> z) is defined if and only if (x <> y) <> z is defined, and
    • if these things are all defined, then the axiom for total semigroups x <> (y <> z) = (x <> y) <> z must hold.

Methods

(<>?) :: a -> a -> Maybe a infixr 6 Source #

Instances

Instances details
PartialSemigroup () Source # 
Instance details

Defined in Data.PartialSemigroup

Methods

(<>?) :: () -> () -> Maybe () Source #

PartialSemigroup a => PartialSemigroup (ZipList a) Source #

partialZip

Instance details

Defined in Data.PartialSemigroup

Methods

(<>?) :: ZipList a -> ZipList a -> Maybe (ZipList a) Source #

PartialSemigroup a => PartialSemigroup (Identity a) Source # 
Instance details

Defined in Data.PartialSemigroup

Methods

(<>?) :: Identity a -> Identity a -> Maybe (Identity a) Source #

Num a => PartialSemigroup (Product a) Source # 
Instance details

Defined in Data.PartialSemigroup

Methods

(<>?) :: Product a -> Product a -> Maybe (Product a) Source #

Num a => PartialSemigroup (Sum a) Source # 
Instance details

Defined in Data.PartialSemigroup

Methods

(<>?) :: Sum a -> Sum a -> Maybe (Sum a) Source #

PartialSemigroup (AtMostOne a) Source # 
Instance details

Defined in Data.PartialSemigroup

Methods

(<>?) :: AtMostOne a -> AtMostOne a -> Maybe (AtMostOne a) Source #

PartialSemigroup (One a) Source # 
Instance details

Defined in Data.PartialSemigroup

Methods

(<>?) :: One a -> One a -> Maybe (One a) Source #

Semigroup a => PartialSemigroup (Total a) Source # 
Instance details

Defined in Data.PartialSemigroup

Methods

(<>?) :: Total a -> Total a -> Maybe (Total a) Source #

PartialSemigroup [a] Source # 
Instance details

Defined in Data.PartialSemigroup

Methods

(<>?) :: [a] -> [a] -> Maybe [a] Source #

(PartialSemigroup a, PartialSemigroup b) => PartialSemigroup (Either a b) Source # 
Instance details

Defined in Data.PartialSemigroup

Methods

(<>?) :: Either a b -> Either a b -> Maybe (Either a b) Source #

PartialSemigroup a => PartialSemigroup (AppendLeft a b) Source # 
Instance details

Defined in Data.PartialSemigroup

Methods

(<>?) :: AppendLeft a b -> AppendLeft a b -> Maybe (AppendLeft a b) Source #

PartialSemigroup b => PartialSemigroup (AppendRight a b) Source # 
Instance details

Defined in Data.PartialSemigroup

Methods

(<>?) :: AppendRight a b -> AppendRight a b -> Maybe (AppendRight a b) Source #

(PartialSemigroup a, PartialSemigroup b) => PartialSemigroup (a, b) Source # 
Instance details

Defined in Data.PartialSemigroup

Methods

(<>?) :: (a, b) -> (a, b) -> Maybe (a, b) Source #

(PartialSemigroup a, PartialSemigroup b, PartialSemigroup c) => PartialSemigroup (a, b, c) Source # 
Instance details

Defined in Data.PartialSemigroup

Methods

(<>?) :: (a, b, c) -> (a, b, c) -> Maybe (a, b, c) Source #

Either

The exemplary nontrivial PartialSemigroup is Either, for which the append operator produces a Just result only if both arguments are Left or both arguments are Right.

>>> Left "ab" <>? Left "cd"
Just (Left "abcd")
>>> Left "ab" <>? Right [1, 2]
Nothing

newtype AppendLeft a b Source #

A wrapper for Either where the PartialSemigroup operator is defined only over Left values.

Examples

Two Lefts make a Just.

>>> AppendLeft (Left "ab") <>? AppendLeft (Left "cd")
Just (AppendLeft {unAppendLeft = Left "abcd"})

Anything else produces Nothing

>>> AppendLeft (Right "ab") <>? AppendLeft (Right "cd")
Nothing

groupAndConcat combines consecutive Left values, leaving the Right values unmodified.

>>> xs = [Left "a", Left "b", Right "c", Right "d", Left "e", Left "f"]
>>> fmap unAppendLeft . groupAndConcat . fmap AppendLeft $ xs
[Left "ab",Right "c",Right "d",Left "ef"]

Constructors

AppendLeft 

Fields

Instances

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

Defined in Data.PartialSemigroup

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

Defined in Data.PartialSemigroup

Methods

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

show :: AppendLeft a b -> String #

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

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

Defined in Data.PartialSemigroup

Methods

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

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

(Ord a, Ord b) => Ord (AppendLeft a b) Source # 
Instance details

Defined in Data.PartialSemigroup

Methods

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

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

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

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

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

max :: AppendLeft a b -> AppendLeft a b -> AppendLeft a b #

min :: AppendLeft a b -> AppendLeft a b -> AppendLeft a b #

PartialSemigroup a => PartialSemigroup (AppendLeft a b) Source # 
Instance details

Defined in Data.PartialSemigroup

Methods

(<>?) :: AppendLeft a b -> AppendLeft a b -> Maybe (AppendLeft a b) Source #

newtype AppendRight a b Source #

A wrapper for Either where the PartialSemigroup operator is defined only over Right values.

Examples

Two Rights make a Just.

>>> AppendRight (Right "ab") <>? AppendRight (Right "cd")
Just (AppendRight {unAppendRight = Right "abcd"})

Anything else produces Nothing

>>> AppendRight (Left "ab") <>? AppendRight (Left "cd")
Nothing

groupAndConcat combines consecutive Right values, leaving the Left values unmodified.

>>> xs = [Left "a", Left "b", Right "c", Right "d", Left "e", Left "f"]
>>> fmap unAppendRight . groupAndConcat . fmap AppendRight $ xs
[Left "a",Left "b",Right "cd",Left "e",Left "f"]

Constructors

AppendRight 

Fields

Instances

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

Defined in Data.PartialSemigroup

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

Defined in Data.PartialSemigroup

Methods

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

show :: AppendRight a b -> String #

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

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

Defined in Data.PartialSemigroup

Methods

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

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

(Ord a, Ord b) => Ord (AppendRight a b) Source # 
Instance details

Defined in Data.PartialSemigroup

Methods

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

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

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

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

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

max :: AppendRight a b -> AppendRight a b -> AppendRight a b #

min :: AppendRight a b -> AppendRight a b -> AppendRight a b #

PartialSemigroup b => PartialSemigroup (AppendRight a b) Source # 
Instance details

Defined in Data.PartialSemigroup

Methods

(<>?) :: AppendRight a b -> AppendRight a b -> Maybe (AppendRight a b) Source #

Tuples

A tuple forms a partial semigroups when all of its constituent parts have partial semigroups. The append operator returns a Just value when all of the fields' append operators must return Just values.

>>> x = (Left "ab", Right "hi")
>>> y = (Left "cd", Right "jk")
>>> x <>? y
Just (Left "abcd",Right "hijk")
>>> x = (Left "ab", Right "hi")
>>> y = (Left "cd", Left "jk")
>>> x <>? y
Nothing

Concatenation

groupAndConcat :: PartialSemigroup a => [a] -> [a] Source #

Apply a semigroup operation to any pairs of consecutive list elements where the semigroup operation is defined over them.

Examples

For Either, groupAndConcat combines contiguous sublists of Left and contiguous sublists of Right.

>>> xs = [Left "a", Right "b", Right "c", Left "d", Left "e", Left "f"]
>>> groupAndConcat xs
[Left "a",Right "bc",Left "def"]

partialConcat :: PartialSemigroup a => [a] -> Maybe a Source #

If xs is nonempty and the partial semigroup operator is defined for all pairs of values in xs, then partialConcat xs produces a Just result with the combination of all the values. Otherwise, returns Nothing.

Examples

When all values can combine, we get a Just of their combination.

>>> partialConcat [Left "a", Left "b", Left "c"]
Just (Left "abc")

When some values cannot be combined, we get Nothing.

>>> partialConcat [Left "a", Left "b", Right "c"]
Nothing

When the list is empty, we get Nothing.

>>> partialConcat []
Nothing

partialConcat1 :: PartialSemigroup a => NonEmpty a -> Maybe a Source #

Like partialConcat, but for non-empty lists.

Examples

When all values can combine, we get a Just of their combination.

>>> partialConcat1 (Left "a" :| [Left "b", Left "c"])
Just (Left "abc")

When some values cannot be combined, we get Nothing.

>>> partialConcat1 (Left "a" :| [Left "b", Right "c"])
Nothing

Zipping

partialZip :: PartialSemigroup a => [a] -> [a] -> Maybe [a] Source #

Examples

If lists are the same length and each pair of elements successfully, then we get a Just result.

>>> xs = [Left "a", Left "b", Right "c"]
>>> ys = [Left "1", Left "2", Right "3"]
>>> partialZip xs ys
Just [Left "a1",Left "b2",Right "c3"]

If the pairs do not all combine, then we get Nothing.

>>> xs = [Left "a", Left "b", Right "c"]
>>> ys = [Left "1", Right "2", Right "3"]
>>> partialZip xs ys
Nothing

If the lists have different lengths, then we get Nothing.

>>> xs = [Left "a", Left "b", Right "c"]
>>> ys = [Left "1", Left "2"]
>>> partialZip xs ys
Nothing

partialZip1 :: PartialSemigroup a => NonEmpty a -> NonEmpty a -> Maybe (NonEmpty a) Source #

Like partialZip, but for non-empty lists.

Examples

If lists are the same length and each pair of elements successfully, then we get a Just result.

>>> xs = Left "a" :| [Left "b", Right "c"]
>>> ys = Left "1" :| [Left "2", Right "3"]
>>> partialZip1 xs ys
Just (Left "a1" :| [Left "b2",Right "c3"])

If the pairs do not all combine, then we get Nothing.

>>> xs = Left "a" :| [Left "b", Right "c"]
>>> ys = Left "1" :| [Right "2", Right "3"]
>>> partialZip1 xs ys
Nothing

If the lists have different lengths, then we get Nothing.

>>> xs = Left "a" :| [Left "b", Right "c"]
>>> ys = Left "1" :| [Left "2"]
>>> partialZip1 xs ys
Nothing

Total to partial

For every type with a Semigroup, we can trivially construct a PartialSemigroup as:

x <>? y = Just (x <> y)

Additionally, any type with a Semigroup can be treated as a PartialSemigroup by lifting it into Total.

newtype Total a Source #

A wrapper to turn any value with a Semigroup instance into a value with a PartialSemigroup instance whose <>? operator always returns Just.

Examples

>>> Total "ab" <>? Total "cd"
Just (Total {unTotal = "abcd"})
>>> f = getProduct . unTotal
>>> g = Total . Product
>>> fmap f . partialConcat . fmap g $ [1..4]
Just 24

Constructors

Total 

Fields

Instances

Instances details
Read a => Read (Total a) Source # 
Instance details

Defined in Data.PartialSemigroup

Show a => Show (Total a) Source # 
Instance details

Defined in Data.PartialSemigroup

Methods

showsPrec :: Int -> Total a -> ShowS #

show :: Total a -> String #

showList :: [Total a] -> ShowS #

Eq a => Eq (Total a) Source # 
Instance details

Defined in Data.PartialSemigroup

Methods

(==) :: Total a -> Total a -> Bool #

(/=) :: Total a -> Total a -> Bool #

Ord a => Ord (Total a) Source # 
Instance details

Defined in Data.PartialSemigroup

Methods

compare :: Total a -> Total a -> Ordering #

(<) :: Total a -> Total a -> Bool #

(<=) :: Total a -> Total a -> Bool #

(>) :: Total a -> Total a -> Bool #

(>=) :: Total a -> Total a -> Bool #

max :: Total a -> Total a -> Total a #

min :: Total a -> Total a -> Total a #

Semigroup a => PartialSemigroup (Total a) Source # 
Instance details

Defined in Data.PartialSemigroup

Methods

(<>?) :: Total a -> Total a -> Maybe (Total a) Source #

Partial to total

For every type a with a PartialSemigroup, we can construct a total Semigroup for Maybe a as:

Just x <> Just y = x <>? y
_ <> _ = Nothing

We don't actually define this instance for Maybe because it already has a different Semigroup defined over it, but we do provide the Partial wrapper which has this instance.

newtype Partial a Source #

A wrapper for Maybe with an error-propagating Semigroup.

Constructors

Partial 

Fields

Instances

Instances details
PartialSemigroup a => Semigroup (Partial a) Source # 
Instance details

Defined in Data.PartialSemigroup

Methods

(<>) :: Partial a -> Partial a -> Partial a #

sconcat :: NonEmpty (Partial a) -> Partial a #

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

Read a => Read (Partial a) Source # 
Instance details

Defined in Data.PartialSemigroup

Show a => Show (Partial a) Source # 
Instance details

Defined in Data.PartialSemigroup

Methods

showsPrec :: Int -> Partial a -> ShowS #

show :: Partial a -> String #

showList :: [Partial a] -> ShowS #

Eq a => Eq (Partial a) Source # 
Instance details

Defined in Data.PartialSemigroup

Methods

(==) :: Partial a -> Partial a -> Bool #

(/=) :: Partial a -> Partial a -> Bool #

Ord a => Ord (Partial a) Source # 
Instance details

Defined in Data.PartialSemigroup

Methods

compare :: Partial a -> Partial a -> Ordering #

(<) :: Partial a -> Partial a -> Bool #

(<=) :: Partial a -> Partial a -> Bool #

(>) :: Partial a -> Partial a -> Bool #

(>=) :: Partial a -> Partial a -> Bool #

max :: Partial a -> Partial a -> Partial a #

min :: Partial a -> Partial a -> Partial a #

Refusing to combine

These are PartialSemigroup instances that don't really combine their values at all; whenever more than one thing is present, <>? fails.

newtype One a Source #

A partial semigroup operation which always fails.

Constructors

One 

Fields

Instances

Instances details
Read a => Read (One a) Source # 
Instance details

Defined in Data.PartialSemigroup

Show a => Show (One a) Source # 
Instance details

Defined in Data.PartialSemigroup

Methods

showsPrec :: Int -> One a -> ShowS #

show :: One a -> String #

showList :: [One a] -> ShowS #

Eq a => Eq (One a) Source # 
Instance details

Defined in Data.PartialSemigroup

Methods

(==) :: One a -> One a -> Bool #

(/=) :: One a -> One a -> Bool #

Ord a => Ord (One a) Source # 
Instance details

Defined in Data.PartialSemigroup

Methods

compare :: One a -> One a -> Ordering #

(<) :: One a -> One a -> Bool #

(<=) :: One a -> One a -> Bool #

(>) :: One a -> One a -> Bool #

(>=) :: One a -> One a -> Bool #

max :: One a -> One a -> One a #

min :: One a -> One a -> One a #

PartialSemigroup (One a) Source # 
Instance details

Defined in Data.PartialSemigroup

Methods

(<>?) :: One a -> One a -> Maybe (One a) Source #

newtype AtMostOne a Source #

A wrapper for Maybe whose partial semigroup operation fails when two Justs are combined.

Constructors

AtMostOne 

Fields

Instances

Instances details
Read a => Read (AtMostOne a) Source # 
Instance details

Defined in Data.PartialSemigroup

Show a => Show (AtMostOne a) Source # 
Instance details

Defined in Data.PartialSemigroup

Eq a => Eq (AtMostOne a) Source # 
Instance details

Defined in Data.PartialSemigroup

Methods

(==) :: AtMostOne a -> AtMostOne a -> Bool #

(/=) :: AtMostOne a -> AtMostOne a -> Bool #

Ord a => Ord (AtMostOne a) Source # 
Instance details

Defined in Data.PartialSemigroup

PartialSemigroup (AtMostOne a) Source # 
Instance details

Defined in Data.PartialSemigroup

Methods

(<>?) :: AtMostOne a -> AtMostOne a -> Maybe (AtMostOne a) Source #