Safe Haskell | None |
---|---|
Language | Haskell2010 |
Both arrays and objects in JSON allow for an optional trailing comma on the final element. This module houses the shared types and functions that let us handle this.
Synopsis
- data CommaSeparated ws a = CommaSeparated ws (Maybe (Elems ws a))
- data Elems ws a = Elems {
- _elemsElems :: Vector (Elem Identity ws a)
- _elemsLast :: Elem Maybe ws a
- class HasElems c ws a | c -> ws a where
- data Elem f ws a = Elem {
- _elemVal :: a
- _elemTrailing :: f (Comma, ws)
- class HasElem c f ws a | c -> f ws a where
- elem :: Lens' c (Elem f ws a)
- elemTrailing :: Lens' c (f (Comma, ws))
- elemVal :: Lens' c a
- data Comma = Comma
- parseComma :: CharParsing f => f Comma
- parseCommaSeparated :: (Monad f, CharParsing f) => f open -> f close -> f ws -> f a -> f (CommaSeparated ws a)
- _CommaSeparated :: Iso (CommaSeparated ws a) (CommaSeparated ws' b) (ws, Maybe (Elems ws a)) (ws', Maybe (Elems ws' b))
- toList :: CommaSeparated ws a -> [a]
- fromList :: (Monoid ws, Semigroup ws) => [a] -> CommaSeparated ws a
- fromCommaSep :: Traversal' j (CommaSeparated ws x) -> v -> (Elems ws a -> v) -> (x -> Maybe a) -> j -> Either j v
- consCommaSep :: Monoid ws => ((Comma, ws), a) -> CommaSeparated ws a -> CommaSeparated ws a
- unconsCommaSep :: Monoid ws => CommaSeparated ws a -> Maybe ((Maybe (Comma, ws), a), CommaSeparated ws a)
Types
data CommaSeparated ws a Source #
This type is our possibly empty comma-separated list of values. It carries
information about any leading whitespace before the first element, as well as a
the rest of the elements in an Elems
type.
CommaSeparated ws (Maybe (Elems ws a)) |
Instances
This type represents a non-empty list of elements, enforcing that the any element but the last must be followed by a trailing comma and supporting option of a final trailing comma.
Elems | |
|
Instances
Bitraversable Elems Source # | |
Defined in Waargonaut.Types.CommaSep.Elems bitraverse :: Applicative f => (a -> f c) -> (b -> f d) -> Elems a b -> f (Elems c d) # | |
Bifoldable Elems Source # | |
Bifunctor Elems Source # | |
Functor (Elems ws) Source # | |
Monoid ws => Applicative (Elems ws) Source # | |
Foldable (Elems ws) Source # | |
Defined in Waargonaut.Types.CommaSep.Elems fold :: Monoid m => Elems ws m -> m # foldMap :: Monoid m => (a -> m) -> Elems ws a -> m # foldMap' :: Monoid m => (a -> m) -> Elems ws a -> m # foldr :: (a -> b -> b) -> b -> Elems ws a -> b # foldr' :: (a -> b -> b) -> b -> Elems ws a -> b # foldl :: (b -> a -> b) -> b -> Elems ws a -> b # foldl' :: (b -> a -> b) -> b -> Elems ws a -> b # foldr1 :: (a -> a -> a) -> Elems ws a -> a # foldl1 :: (a -> a -> a) -> Elems ws a -> a # elem :: Eq a => a -> Elems ws a -> Bool # maximum :: Ord a => Elems ws a -> a # minimum :: Ord a => Elems ws a -> a # | |
Traversable (Elems ws) Source # | |
Defined in Waargonaut.Types.CommaSep.Elems | |
(Eq ws, Eq a) => Eq (Elems ws a) Source # | |
(Show ws, Show a) => Show (Elems ws a) Source # | |
Monoid ws => Semigroup (Elems ws a) Source # | |
HasElems (Elems ws a) ws a Source # | |
class HasElems c ws a | c -> ws a where Source #
Typeclass for things that contain an Elems
structure.
Data type to represent a single element in a CommaSeparated
list. Carries
information about it's own trailing whitespace. Denoted by the f
.
Elem | |
|
Instances
Traversable f => Bitraversable (Elem f) Source # | |
Defined in Waargonaut.Types.CommaSep.Elem bitraverse :: Applicative f0 => (a -> f0 c) -> (b -> f0 d) -> Elem f a b -> f0 (Elem f c d) # | |
Foldable f => Bifoldable (Elem f) Source # | |
Functor f => Bifunctor (Elem f) Source # | |
Functor (Elem f ws) Source # | |
(Monoid ws, Applicative f) => Applicative (Elem f ws) Source # | |
Foldable (Elem f ws) Source # | |
Defined in Waargonaut.Types.CommaSep.Elem fold :: Monoid m => Elem f ws m -> m # foldMap :: Monoid m => (a -> m) -> Elem f ws a -> m # foldMap' :: Monoid m => (a -> m) -> Elem f ws a -> m # foldr :: (a -> b -> b) -> b -> Elem f ws a -> b # foldr' :: (a -> b -> b) -> b -> Elem f ws a -> b # foldl :: (b -> a -> b) -> b -> Elem f ws a -> b # foldl' :: (b -> a -> b) -> b -> Elem f ws a -> b # foldr1 :: (a -> a -> a) -> Elem f ws a -> a # foldl1 :: (a -> a -> a) -> Elem f ws a -> a # toList :: Elem f ws a -> [a] # length :: Elem f ws a -> Int # elem :: Eq a => a -> Elem f ws a -> Bool # maximum :: Ord a => Elem f ws a -> a # minimum :: Ord a => Elem f ws a -> a # | |
Traversable (Elem f ws) Source # | |
Defined in Waargonaut.Types.CommaSep.Elem | |
(Eq1 f, Eq ws, Eq a) => Eq (Elem f ws a) Source # | |
(Show1 f, Show ws, Show a) => Show (Elem f ws a) Source # | |
HasElem (Elem f ws a) f ws a Source # | |
class HasElem c f ws a | c -> f ws a where Source #
Typeclass for things that contain a single Elem
structure.
Unary type to represent a comma.
Parse
parseComma :: CharParsing f => f Comma Source #
Parse a single comma (,)
parseCommaSeparated :: (Monad f, CharParsing f) => f open -> f close -> f ws -> f a -> f (CommaSeparated ws a) Source #
Parse a CommaSeparated
data structure.
>>>
testparse (parseCommaSeparated (char '[') (char ']') parseWhitespace charWS) "[]"
Right (CommaSeparated (WS []) Nothing)
>>>
testparse (parseCommaSeparated (char '[') (char ']') parseWhitespace charWS) "[ ]"
Right (CommaSeparated (WS [Space]) Nothing)
>>>
isLeft $ testparse (parseCommaSeparated (char '[') (char ']') parseWhitespace charWS) "[ , ]"
True
>>>
isLeft $ testparse (parseCommaSeparated (char '[') (char ']') parseWhitespace charWS) "[ , a]"
True
>>>
isLeft $ testparse (parseCommaSeparated (char '[') (char ']') parseWhitespace charWS) "[d a]"
True
>>>
testparse (parseCommaSeparated (char '[') (char ']') parseWhitespace charWS) "[d , ]"
Right (CommaSeparated (WS []) (Just (Elems {_elemsElems = [], _elemsLast = Elem {_elemVal = ('d',WS [Space]), _elemTrailing = Just (Comma,WS [Space])}})))
>>>
testparse (parseCommaSeparated (char '[') (char ']') parseWhitespace charWS) "[\na\n , b]"
Right (CommaSeparated (WS [NewLine]) (Just (Elems {_elemsElems = [Elem {_elemVal = ('a',WS [NewLine,Space]), _elemTrailing = Identity (Comma,WS [Space])}], _elemsLast = Elem {_elemVal = ('b',WS []), _elemTrailing = Nothing}})))
>>>
testparse (parseCommaSeparated (char '[') (char ']') parseWhitespace charWS) "[\na\n , b, \n]"
Right (CommaSeparated (WS [NewLine]) (Just (Elems {_elemsElems = [Elem {_elemVal = ('a',WS [NewLine,Space]), _elemTrailing = Identity (Comma,WS [Space])}], _elemsLast = Elem {_elemVal = ('b',WS []), _elemTrailing = Just (Comma,WS [Space,NewLine])}})))
Conversion
_CommaSeparated :: Iso (CommaSeparated ws a) (CommaSeparated ws' b) (ws, Maybe (Elems ws a)) (ws', Maybe (Elems ws' b)) Source #
Isomorphism between the internal pieces of a CommaSeparated
element.
toList :: CommaSeparated ws a -> [a] Source #
Convert a CommaSeparated
of a
to [a]
, discarding whitespace.
fromList :: (Monoid ws, Semigroup ws) => [a] -> CommaSeparated ws a Source #
Convert a list of a
to a CommaSeparated
list, with no whitespace.
fromCommaSep :: Traversal' j (CommaSeparated ws x) -> v -> (Elems ws a -> v) -> (x -> Maybe a) -> j -> Either j v Source #
Attempt convert a CommaSeparated
to some other value using the given functions.
Cons / Uncons
consCommaSep :: Monoid ws => ((Comma, ws), a) -> CommaSeparated ws a -> CommaSeparated ws a Source #
Cons elements onto a CommaSeparated
with provided whitespace information.
If you don't need explicit whitespace then the Cons
instance is more straightforward.
unconsCommaSep :: Monoid ws => CommaSeparated ws a -> Maybe ((Maybe (Comma, ws), a), CommaSeparated ws a) Source #
Attempt to "uncons" elements from the front of a CommaSeparated
without
discarding the elements' whitespace information. If you don't need explicit
whitespace then the Cons
instance is more straightforward.