separated-0.1.0: A data type with elements separated by values

Safe HaskellSafe-Inferred
LanguageHaskell2010

Data.Separated.Separated

Synopsis

Documentation

data Separated s a Source

Instances

Bifunctor Separated 
SeparatedCons Separated1 Separated 
SeparatedCons Separated Separated1 
Functor (Separated s)

Map across a Separated on the element values.

fmap id (x :: Separated Int String) == x
fmap (+1) (a +: b +: empty) == a +: (1+b) +: empty
Monoid s => Applicative (Separated s)

Applies functions with element values, using a zipping operation, appending separators. The identity operation is an infinite list of the empty separator and the given element value.

>>> (empty :: Separated [Int] (String -> [String])) <*> empty
[]
>>> [1,2] +: (\s -> [s, reverse s, drop 1 s]) +: empty <*> [3,4,5] +: "abc" +: empty
[[1,2,3,4,5],["abc","cba","bc"]]
Semigroup s => Apply (Separated s)

Applies functions with element values, using a zipping operation, appending separators.

>>> (empty :: Separated [Int] (String -> [String])) <.> empty
[]
>>> [1,2] +: (\s -> [s, reverse s, drop 1 s]) +: empty <.> [3,4,5] +: "abc" +: empty
[[1,2,3,4,5],["abc","cba","bc"]]
(Eq s, Eq a) => Eq (Separated s a) 
(Ord s, Ord a) => Ord (Separated s a) 
(Show s, Show a) => Show (Separated s a) 
Monoid (Separated s a) 
Semigroup (Separated s a) 
type SeparatedConsF Separated = Separated1 
type SeparatedConsG Separated = Separated1 

separated :: Iso [(s, a)] [(t, b)] (Separated s a) (Separated t b) Source

The isomorphism to a list of pairs of element and separator values.

>>> separated # empty
[]
>>> separated # ('x' +: 6 +: empty)
[('x',6)]
>>> [] ^. separated
[]
>>> [(6, [])] ^. separated
[6,[]]

data Separated1 a s Source

Instances

Bifunctor Separated1 
SeparatedCons Separated1 Separated 
SeparatedCons Separated Separated1 
Functor (Separated1 s)

Map across a Separated1 on the separator values.

>>> fmap (+1) (set separated1Tail (1 +: 'b' +: 2 +: 'c' +: empty) (single 'a'))
['a',2,'b',3,'c']
fmap id (x :: Separated1 Int String) == x
fmap (+1) (single x) == single x
Monoid s => Applicative (Separated1 s)

Applies functions with separator values, using a zipping operation, appending elements. The identity operation is an infinite list of the empty element and the given separator value.

>>> [1,2] +: reverse +: [3,4] +: empty <*> [5,6,7] +: "abc" +: [8] +: empty
[[1,2,5,6,7],"cba",[3,4,8]]
Semigroup s => Apply (Separated1 s)

Applies functions with separator values, using a zipping operation, appending elements.

>>> [1,2] +: reverse +: [3,4] +: empty <.> [5,6,7] +: "abc" +: [8] +: empty
[[1,2,5,6,7],"cba",[3,4,8]]
(Eq a, Eq s) => Eq (Separated1 a s) 
(Ord a, Ord s) => Ord (Separated1 a s) 
(Show a, Show s) => Show (Separated1 a s) 
type SeparatedConsF Separated1 = Separated 
type SeparatedConsG Separated1 = Separated 

separated1 :: Iso (a, Separated s a) (b, Separated t b) (Separated1 a s) (Separated1 b t) Source

The isomorphism to element values interspersed with a separator.

>>> separated1 # (single 6)
(6,[])
>>> separated1 # (5 +: 'x' +: single 6)
(5,['x',6])
>>> (6, empty) ^. separated1
[6]
>>> (5, 'x' +- 6) ^. separated1
[5,'x',6]

separated1Head :: Lens (Separated1 a t) (Separated1 a t) a a Source

A lens on the first element value.

>>> single 7 ^. separated1Head
7
single x ^. separated1Head == (x :: Int)

separated1Tail :: Lens (Separated1 a s) (Separated1 a t) (Separated s a) (Separated t a) Source

A lens on the tail.

(d +: e +: single x) ^. separated1Tail == e +: x +: empty

(+-) :: s -> a -> Separated s a Source

One element and one separator.

>>> 7 +- "abc"
[7,"abc"]
>>> 7 +: "abc" +: 8 +- "def"
[7,"abc",8,"def"]

single :: a -> Separated1 a s Source

Zero element values interspersed with one element.

>>> single 4
[4]
single x ^. separated1Tail == empty

shift :: Iso (Separated1 a s) (Separated1 b t) ([(a, s)], a) ([(b, t)], b) Source

The isomorphism that shuffles the elements and separators one position.

>>> shift # ([], 6)
[6]
>>> shift # ([(5, 'x')], 6)
[5,'x',6]
>>> single 6 ^. shift
([],6)
>>> (5 +: 'x' +: single 6) ^. shift
([(5,'x')],6)

separatedSwap :: Iso (Separated s a) (Separated t b) (Separated a s) (Separated b t) Source

The isomorphism that swaps elements with their separators.

>>> separatedSwap # empty
[]
>>> separatedSwap # ('x' +: 6 +: empty)
[6,'x']
>>> empty ^. separatedSwap
[]
>>> ('x' +: 6 +: empty) ^. separatedSwap
[6,'x']

(.++.) :: Separated1 s a -> Separated1 a s -> Separated s a infixr 5 Source

Append two lists of separated values to produce a list of pairs of separator and element values.

>>> single 7 .++. single 'a'
[7,'a']

a +: single 7 .++. single b [a,7,b]

a +: (b .++. c) == (a +: b) *+: c

(++.) :: Separated s a -> Separated1 s a -> Separated1 s a infixr 5 Source

Append element values interspersed with a separator to a list of pairs of separator and element values.

>>> empty ++. single 7
[7]
>>> empty ++. 6 +: 'x' +: single 7
[6,'x',7]
>>> 'w' +: empty ++. 6 +: 'x' +: single 7
['w',6,'x',7]

(.++) :: Separated1 a s -> Separated s a -> Separated1 a s infixr 5 Source

Append a list of pairs of separator and element values to element values interspersed with a separator.

>>> single 7 .++ empty
[7]
>>> single 6 .++ 'x' +: 7 +: empty
[6,'x',7]
>>> 'w' +: single 6 .++ 'x' +: 7 +: empty
['w',6,'x',7]