| Safe Haskell | None |
|---|---|
| Language | Haskell2010 |
Data.Separated.Separated
- data Separated a b
- separated :: Iso [(a, b)] [(c, d)] (Separated a b) (Separated c d)
- data Separated1 b a
- separated1 :: Iso (a, Separated s a) (b, Separated t b) (Separated1 a s) (Separated1 b t)
- separated1Head :: Lens (Separated1 a t) (Separated1 a t) a a
- separated1Tail :: Lens (Separated1 a s) (Separated1 a t) (Separated s a) (Separated t a)
- empty :: Separated s a
- (+-) :: s -> a -> Separated s a
- single :: a -> Separated1 a s
- shift :: Iso (Separated1 a s) (Separated1 b t) ([(a, s)], a) ([(b, t)], b)
- separatedSwap :: Iso (Separated s a) (Separated t b) (Separated a s) (Separated b t)
- (.++.) :: Separated1 s a -> Separated1 a s -> Separated s a
- (++.) :: Separated s a -> Separated1 s a -> Separated1 s a
- (.++) :: Separated1 a s -> Separated s a -> Separated1 a s
- separatedBy :: Alternative f => f a -> f b -> f (Separated a b)
- separatedBy1 :: Alternative f => f b -> f a -> f (Separated1 b a)
Documentation
Instances
| Bifunctor Separated Source # | |
| Bitraversable Separated Source # | |
| Bifoldable Separated Source # | |
| 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 +: empty) == a +: (1+b) +: empty |
| (Semigroup a, 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 empty separator and the given element value.
|
| 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 # | |
| type SeparatedConsF Separated Source # | |
| type SeparatedConsG Separated Source # | |
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 # empty[]
>>>separated # ('x' +: 6 +: empty)[('x',6)]
>>>[] ^. separated[]
>>>[(6, [])] ^. separated[6,[]]
data Separated1 b a Source #
Instances
| Bifunctor Separated1 Source # | |
| SeparatedCons Separated1 Separated Source # | |
| SeparatedCons Separated Separated1 Source # | |
| Functor (Separated1 b) Source # | Map across a
fmap id (x :: Separated1 Int String) == x fmap (+1) (single x) == single x |
| (Semigroup b, 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 empty element and the given separator value.
|
| 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 # | |
| type SeparatedConsF Separated1 Source # | |
| type SeparatedConsG Separated1 Source # | |
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 ^. separated1Head7
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 infixl 9 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 :: Separated Int Int) == a +: 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]
separatedBy :: Alternative f => f a -> f b -> f (Separated a b) Source #
>>>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 #
>>>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',',']