| Safe Haskell | None |
|---|---|
| Language | Haskell2010 |
Data.Separated
- newtype Separated a b = Separated [(a, b)]
- data Separated1 b a = Separated1 b (Separated a b)
- newtype Pesarated b a = Pesarated (Separated a b)
- newtype Pesarated1 a b = Pesarated1 (Separated1 b a)
- separated :: Iso [(a, b)] [(c, d)] (Separated a b) (Separated c d)
- separated1 :: Iso (a, Separated s a) (b, Separated t b) (Separated1 a s) (Separated1 b t)
- pesarated :: Iso [(a, b)] [(c, d)] (Pesarated b a) (Pesarated d c)
- pesarated1 :: Iso (a, Pesarated a s) (b, Pesarated b t) (Pesarated1 s a) (Pesarated1 t b)
- class HasHead s t a b | s -> a, t -> b, s b -> t, t a -> s where
- class HasTail s t a b | s -> a, t -> b, s b -> t, t a -> s where
- class Separated1Single f where
- class Pesarated1Single f where
- class Construct f where
- class Sprinkle f where
- skrinple :: s -> NonEmpty a -> Pesarated1 s a
- skrinpleMay :: s -> [a] -> Maybe (Pesarated1 s a)
- class (f ~ SeparatedConsF g, g ~ SeparatedConsG f) => SeparatedCons f g where
- type SeparatedConsF g :: * -> * -> *
- type SeparatedConsG f :: * -> * -> *
- class (f ~ PesaratedConsF g, g ~ PesaratedConsG f) => PesaratedCons f g where
- type PesaratedConsF g :: * -> * -> *
- type PesaratedConsG f :: * -> * -> *
- class Appends a b c | a b -> c where
- separatedBy :: Alternative f => f a -> f b -> f (Separated a b)
- separatedBy1 :: Alternative f => f b -> f a -> f (Separated1 b a)
- pesaratedBy :: Alternative f => f a -> f b -> f (Pesarated b a)
- pesaratedBy1 :: Alternative f => f b -> f a -> f (Pesarated1 a b)
Data types
newtype Separated a b Source #
A list of pairs of separator and value. Separated by a in values b.
There are an even number of separators as there are values.
Constructors
| Separated [(a, b)] |
Instances
| Bifunctor Separated Source # | |
| Bitraversable Separated Source # | |
| Bifoldable Separated Source # | |
| Swapped Separated Source # | The isomorphism that swaps elements with their separators.
|
| Sprinkle Separated Source # | |
| Construct Separated Source # | One element and one separator.
|
| SeparatedCons Separated1 Separated Source # | |
| SeparatedCons Separated Separated1 Source # | |
| Functor (Separated a) Source # | Map across a fmap id (x :: Separated Int String) == x \a b -> fmap (+1) (a +: b +: emptySeparated) == a +: (1+b) +: emptySeparated |
| Monoid a => Applicative (Separated a) Source # | Applies functions with element values, using a zipping operation, appending separators. The identity operation is an infinite list of the emptySeparated separator and the given element value.
|
| Foldable (Separated a) Source # | |
| Traversable (Separated a) Source # | |
| Semigroup a => Apply (Separated a) Source # | Applies functions with element values, using a zipping operation, appending separators.
|
| (Eq b, Eq a) => Eq (Separated a b) Source # | |
| (Ord b, Ord a) => Ord (Separated a b) Source # | |
| (Show a, Show b) => Show (Separated a b) Source # |
|
| Semigroup (Separated a b) Source # |
|
| Monoid (Separated a b) Source # |
|
| Wrapped (Separated a0 b0) Source # | |
| (~) * (Separated a0 b0) t0 => Rewrapped (Separated a1 b1) t0 Source # | |
| Appends (Separated1 a s) (Separated s a) (Separated1 a s) Source # | Append a list of pairs of separator and element values to element values interspersed with a separator.
|
| Appends (Separated1 s a) (Separated1 a s) (Separated s a) Source # | Append two lists of separated values to produce a list of pairs of separator and element values.
a +: (b :: Separated Int Int) == a +: b -- (a +: (b <++> c)) == ((a +: b) <++> c) |
| Appends (Separated s a) (Separated1 s a) (Separated1 s a) Source # | Append element values interspersed with a separator to a list of pairs of separator and element values.
|
| HasTail (Separated1 a s) (Separated1 a t) (Separated s a) (Separated t a) Source # | A lens on the tail. (d +: e +: (singleSeparated x :: Separated1 Int Char)) ^. tailL == e +: x +: emptySeparated |
| type SeparatedConsF Separated Source # | |
| type SeparatedConsG Separated Source # | |
| type Unwrapped (Separated a0 b0) Source # | |
data Separated1 b a Source #
A list of pairs of separator and value. Separated by a in values b.
There is one more value than there are separators.
Constructors
| Separated1 b (Separated a b) |
Instances
| Bifunctor Separated1 Source # | |
| Bitraversable Separated1 Source # | |
| Bifoldable Separated1 Source # | |
| Sprinkle Separated1 Source # | |
| Separated1Single Separated1 Source # | Zero element values interspersed with one element.
(singleSeparated x :: Separated1 Int Char) ^. tailL == emptySeparated |
| SeparatedCons Separated1 Separated Source # | |
| SeparatedCons Separated Separated1 Source # | |
| Functor (Separated1 b) Source # | Map across a
fmap id (x :: Separated1 Int String) == x fmap (+1) (singleSeparated x :: Separated1 Char Int) == singleSeparated x |
| Monoid b => Applicative (Separated1 b) Source # | Applies functions with separator values, using a zipping operation, appending elements. The identity operation is an infinite list of the emptySeparated element and the given separator value.
|
| Foldable (Separated1 b) Source # | |
| Traversable (Separated1 b) Source # | |
| Semigroup b => Apply (Separated1 b) Source # | Applies functions with separator values, using a zipping operation, appending elements.
|
| (Eq a, Eq b) => Eq (Separated1 b a) Source # | |
| (Ord a, Ord b) => Ord (Separated1 b a) Source # | |
| (Show b, Show a) => Show (Separated1 b a) Source # | |
| HasHead (Separated1 a t) (Separated1 a t) a a Source # | A lens on the first element value.
(singleSeparated x :: Separated1 Int Char) ^. headL == (x :: Int) |
| Appends (Separated1 a s) (Separated s a) (Separated1 a s) Source # | Append a list of pairs of separator and element values to element values interspersed with a separator.
|
| Appends (Separated1 s a) (Separated1 a s) (Separated s a) Source # | Append two lists of separated values to produce a list of pairs of separator and element values.
a +: (b :: Separated Int Int) == a +: b -- (a +: (b <++> c)) == ((a +: b) <++> c) |
| Appends (Separated s a) (Separated1 s a) (Separated1 s a) Source # | Append element values interspersed with a separator to a list of pairs of separator and element values.
|
| HasTail (Separated1 a s) (Separated1 a t) (Separated s a) (Separated t a) Source # | A lens on the tail. (d +: e +: (singleSeparated x :: Separated1 Int Char)) ^. tailL == e +: x +: emptySeparated |
| type SeparatedConsF Separated1 Source # | |
| type SeparatedConsG Separated1 Source # | |
newtype Pesarated b a Source #
The Separated type constructor, flipped.
Instances
| Bifunctor Pesarated Source # | |
| Bitraversable Pesarated Source # | |
| Bifoldable Pesarated Source # | |
| Swapped Pesarated Source # | The isomorphism that swaps elements with their separators.
|
| Sprinkle Pesarated Source # | |
| Construct Pesarated Source # | One element and one separator.
|
| PesaratedCons Pesarated1 Pesarated Source # | |
| PesaratedCons Pesarated Pesarated1 Source # | |
| Functor (Pesarated a) Source # | Map across a fmap id (x :: Pesarated Int String) == x \a b -> fmap (+1) (a -: b -: emptyPesarated) == (1+a) -: b -: emptyPesarated |
| Monoid a => Applicative (Pesarated a) Source # | Applies functions with element values, using a zipping operation, appending separators. The identity operation is an infinite list of the emptySeparated separator and the given element value.
|
| Foldable (Pesarated b) Source # | |
| Traversable (Pesarated b) Source # | |
| Semigroup a => Apply (Pesarated a) Source # | Applies functions with element values, using a zipping operation, appending separators.
|
| (Eq a, Eq b) => Eq (Pesarated b a) Source # | |
| (Ord a, Ord b) => Ord (Pesarated b a) Source # | |
| (Show a, Show b) => Show (Pesarated b a) Source # |
|
| Semigroup (Pesarated b a) Source # |
|
| Monoid (Pesarated b a) Source # |
|
| Wrapped (Pesarated b0 a0) Source # | |
| (~) * (Pesarated b0 a0) t0 => Rewrapped (Pesarated b1 a1) t0 Source # | |
| HasTail (Pesarated1 a s) (Pesarated1 b s) (Pesarated s a) (Pesarated s b) Source # | A lens on the tail. (d -: e -: (singlePesarated x :: Pesarated1 Char Int)) ^. tailL == e -: x -: emptyPesarated |
| type PesaratedConsF Pesarated Source # | |
| type PesaratedConsG Pesarated Source # | |
| type Unwrapped (Pesarated b0 a0) Source # | |
newtype Pesarated1 a b Source #
The Separated1 type constructor, flipped.
Constructors
| Pesarated1 (Separated1 b a) |
Instances
| Bifunctor Pesarated1 Source # | |
| Bitraversable Pesarated1 Source # | |
| Bifoldable Pesarated1 Source # | |
| Pesarated1Single Pesarated1 Source # | Zero element values interspersed with one element.
(singlePesarated x :: Pesarated1 Int Char) ^. tailL == emptyPesarated |
| PesaratedCons Pesarated1 Pesarated Source # | |
| PesaratedCons Pesarated Pesarated1 Source # | |
| Functor (Pesarated1 a) Source # | Map across a
fmap id (x :: Pesarated1 Int String) == x fmap (+1) (singlePesarated x :: Pesarated1 Char Int) == singlePesarated (x + 1) |
| Monoid a => Applicative (Pesarated1 a) Source # | Applies functions with separator values, using a zipping operation, appending elements. The identity operation is an infinite list of the emptySeparated element and the given separator value.
|
| Foldable (Pesarated1 a) Source # | |
| Traversable (Pesarated1 a) Source # | |
| Traversable1 (Pesarated1 a) Source # | |
| Semigroup a => Apply (Pesarated1 a) Source # | Applies functions with separator values, using a zipping operation, appending elements.
|
| Foldable1 (Pesarated1 a) Source # | |
| (Eq b, Eq a) => Eq (Pesarated1 a b) Source # | |
| (Ord b, Ord a) => Ord (Pesarated1 a b) Source # | |
| (Show a, Show b) => Show (Pesarated1 a b) Source # | |
| Wrapped (Pesarated1 a0 b0) Source # | |
| (~) * (Pesarated1 a0 b0) t0 => Rewrapped (Pesarated1 a1 b1) t0 Source # | |
| HasHead (Pesarated1 a t) (Pesarated1 a t) t t Source # | A lens on the first element value.
(singlePesarated x :: Pesarated1 Char Int) ^. headL == (x :: Int) |
| HasTail (Pesarated1 a s) (Pesarated1 b s) (Pesarated s a) (Pesarated s b) Source # | A lens on the tail. (d -: e -: (singlePesarated x :: Pesarated1 Char Int)) ^. tailL == e -: x -: emptyPesarated |
| type PesaratedConsF Pesarated1 Source # | |
| type PesaratedConsG Pesarated1 Source # | |
| type Unwrapped (Pesarated1 a0 b0) Source # | |
Iso
separated :: Iso [(a, b)] [(c, d)] (Separated a b) (Separated c d) Source #
The isomorphism to a list of pairs of element and separator values.
>>>separated # emptySeparated[]
>>>separated # ('x' +: 6 +: emptySeparated)[('x',6)]
>>>[] ^. separated[]
>>>[(6, [])] ^. separated[6,[]]
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 # (singleSeparated 6)(6,[])
>>>separated1 # (5 +: 'x' +: singleSeparated 6)(5,['x',6])
>>>(6, emptySeparated) ^. separated1[6]
>>>(5, 'x' +- 6) ^. separated1[5,'x',6]
pesarated :: Iso [(a, b)] [(c, d)] (Pesarated b a) (Pesarated d c) Source #
The isomorphism to element values interspersed with a separator.
>>>pesarated # emptyPesarated[]
>>>('a', 'x' +- 6) ^. pesarated1['a',6,'x']
>>>('x' -: 6 -: emptyPesarated)['x',6]
pesarated1 :: Iso (a, Pesarated a s) (b, Pesarated b t) (Pesarated1 s a) (Pesarated1 t b) Source #
The isomorphism to element values interspersed with a separator.
>>>pesarated1 # singlePesarated 6(6,[])
>>>pesarated1 # (8 -: 'x' -: singlePesarated 6)(8,['x',6])
>>>(6, empty) ^. pesarated1[6]
>>>(5, 'x' -+ 6) ^. pesarated1[5,'x',6]
Viewing
class HasHead s t a b | s -> a, t -> b, s b -> t, t a -> s where Source #
Structures that have a head element.
Minimal complete definition
Instances
| HasHead (Pesarated1 a t) (Pesarated1 a t) t t Source # | A lens on the first element value.
(singlePesarated x :: Pesarated1 Char Int) ^. headL == (x :: Int) |
| HasHead (Separated1 a t) (Separated1 a t) a a Source # | A lens on the first element value.
(singleSeparated x :: Separated1 Int Char) ^. headL == (x :: Int) |
class HasTail s t a b | s -> a, t -> b, s b -> t, t a -> s where Source #
Structures that have a tail.
Minimal complete definition
Instances
| HasTail (Pesarated1 a s) (Pesarated1 b s) (Pesarated s a) (Pesarated s b) Source # | A lens on the tail. (d -: e -: (singlePesarated x :: Pesarated1 Char Int)) ^. tailL == e -: x -: emptyPesarated |
| HasTail (Separated1 a s) (Separated1 a t) (Separated s a) (Separated t a) Source # | A lens on the tail. (d +: e +: (singleSeparated x :: Separated1 Int Char)) ^. tailL == e +: x +: emptySeparated |
Constructing
class Separated1Single f where Source #
Construct a single separated value.
Minimal complete definition
Methods
singleSeparated :: a -> f a s Source #
Instances
| Separated1Single Separated1 Source # | Zero element values interspersed with one element.
(singleSeparated x :: Separated1 Int Char) ^. tailL == emptySeparated |
class Pesarated1Single f where Source #
Minimal complete definition
Methods
singlePesarated :: a -> f s a Source #
Instances
| Pesarated1Single Pesarated1 Source # | Zero element values interspersed with one element.
(singlePesarated x :: Pesarated1 Int Char) ^. tailL == emptyPesarated |
class Construct f where Source #
Construction of separated values.
Instances
| Construct Pesarated Source # | One element and one separator.
|
| Construct Separated Source # | One element and one separator.
|
skrinple :: s -> NonEmpty a -> Pesarated1 s a Source #
skrinpleMay :: s -> [a] -> Maybe (Pesarated1 s a) Source #
class (f ~ SeparatedConsF g, g ~ SeparatedConsG f) => SeparatedCons f g where Source #
Prepend a value to a separated-like structure.
Minimal complete definition
class (f ~ PesaratedConsF g, g ~ PesaratedConsG f) => PesaratedCons f g where Source #
Prepend a value to a separated-like structure.
Minimal complete definition
Appending
class Appends a b c | a b -> c where Source #
Append two to make one.
Minimal complete definition
Instances
| Appends (Separated1 a s) (Separated s a) (Separated1 a s) Source # | Append a list of pairs of separator and element values to element values interspersed with a separator.
|
| Appends (Separated1 s a) (Separated1 a s) (Separated s a) Source # | Append two lists of separated values to produce a list of pairs of separator and element values.
a +: (b :: Separated Int Int) == a +: b -- (a +: (b <++> c)) == ((a +: b) <++> c) |
| Appends (Separated s a) (Separated1 s a) (Separated1 s a) Source # | Append element values interspersed with a separator to a list of pairs of separator and element values.
|
Alternating
separatedBy :: Alternative f => f a -> f b -> f (Separated a b) Source #
Alternate separated values e.g. `f ~ Parser`.
>>>parse (separatedBy (char ',') digit) "test" ""Right []
>>>isLeft (parse (separatedBy (char ',') digit) "test" ",")True
>>>parse (separatedBy (char ',') digit) "test" ",1"Right [',','1']
>>>isLeft (parse (separatedBy (char ',') digit) "test" ",1,")True
>>>parse (separatedBy (char ',') digit) "test" ",1,2,3,4,5"Right [',','1',',','2',',','3',',','4',',','5']
separatedBy1 :: Alternative f => f b -> f a -> f (Separated1 b a) Source #
Alternate separated values e.g. `f ~ Parser`.
>>>isLeft (parse (separatedBy1 (char ',') digit) "test" "")True
>>>parse (separatedBy1 (char ',') digit) "test" ","Right [',']
>>>isLeft (parse (separatedBy1 (char ',') digit) "test" ",1")True
>>>parse (separatedBy1 (char ',') digit) "test" ",1,"Right [',','1',',']
>>>parse (separatedBy1 (char ',') digit) "test" ",1,2,3,4,5,"Right [',','1',',','2',',','3',',','4',',','5',',']
pesaratedBy :: Alternative f => f a -> f b -> f (Pesarated b a) Source #
Alternate separated values e.g. `f ~ Parser`.
>>>parse (pesaratedBy (char ',') digit) "test" ""Right []
>>>isLeft (parse (pesaratedBy (char ',') digit) "test" ",")True
>>>parse (separatedBy (char ',') digit) "test" ",1"Right [',','1']
>>>isLeft (parse (pesaratedBy (char ',') digit) "test" ",1,")True
>>>parse (pesaratedBy (char ',') digit) "test" ",1,2,3,4,5"Right [',','1',',','2',',','3',',','4',',','5']
pesaratedBy1 :: Alternative f => f b -> f a -> f (Pesarated1 a b) Source #
Alternate separated values e.g. `f ~ Parser`.
>>>isLeft (parse (pesaratedBy1 (char ',') digit) "test" "")True
>>>parse (pesaratedBy1 (char ',') digit) "test" ","Right [',']
>>>isLeft (parse (pesaratedBy1 (char ',') digit) "test" ",1")True
>>>parse (pesaratedBy1 (char ',') digit) "test" ",1,"Right [',','1',',']
>>>parse (pesaratedBy1 (char ',') digit) "test" ",1,2,3,4,5,"Right [',','1',',','2',',','3',',','4',',','5',',']