waargonaut-0.5.2.1: JSON wrangling

Safe HaskellNone
LanguageHaskell2010

Waargonaut.Types.CommaSep

Contents

Description

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

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.

Constructors

CommaSeparated ws (Maybe (Elems ws a)) 
Instances
Bitraversable CommaSeparated Source # 
Instance details

Defined in Waargonaut.Types.CommaSep

Methods

bitraverse :: Applicative f => (a -> f c) -> (b -> f d) -> CommaSeparated a b -> f (CommaSeparated c d) #

Bifoldable CommaSeparated Source # 
Instance details

Defined in Waargonaut.Types.CommaSep

Methods

bifold :: Monoid m => CommaSeparated m m -> m #

bifoldMap :: Monoid m => (a -> m) -> (b -> m) -> CommaSeparated a b -> m #

bifoldr :: (a -> c -> c) -> (b -> c -> c) -> c -> CommaSeparated a b -> c #

bifoldl :: (c -> a -> c) -> (c -> b -> c) -> c -> CommaSeparated a b -> c #

Bifunctor CommaSeparated Source # 
Instance details

Defined in Waargonaut.Types.CommaSep

Methods

bimap :: (a -> b) -> (c -> d) -> CommaSeparated a c -> CommaSeparated b d #

first :: (a -> b) -> CommaSeparated a c -> CommaSeparated b c #

second :: (b -> c) -> CommaSeparated a b -> CommaSeparated a c #

Functor (CommaSeparated ws) Source # 
Instance details

Defined in Waargonaut.Types.CommaSep

Methods

fmap :: (a -> b) -> CommaSeparated ws a -> CommaSeparated ws b #

(<$) :: a -> CommaSeparated ws b -> CommaSeparated ws a #

Foldable (CommaSeparated ws) Source # 
Instance details

Defined in Waargonaut.Types.CommaSep

Methods

fold :: Monoid m => CommaSeparated ws m -> m #

foldMap :: Monoid m => (a -> m) -> CommaSeparated ws a -> m #

foldr :: (a -> b -> b) -> b -> CommaSeparated ws a -> b #

foldr' :: (a -> b -> b) -> b -> CommaSeparated ws a -> b #

foldl :: (b -> a -> b) -> b -> CommaSeparated ws a -> b #

foldl' :: (b -> a -> b) -> b -> CommaSeparated ws a -> b #

foldr1 :: (a -> a -> a) -> CommaSeparated ws a -> a #

foldl1 :: (a -> a -> a) -> CommaSeparated ws a -> a #

toList :: CommaSeparated ws a -> [a] #

null :: CommaSeparated ws a -> Bool #

length :: CommaSeparated ws a -> Int #

elem :: Eq a => a -> CommaSeparated ws a -> Bool #

maximum :: Ord a => CommaSeparated ws a -> a #

minimum :: Ord a => CommaSeparated ws a -> a #

sum :: Num a => CommaSeparated ws a -> a #

product :: Num a => CommaSeparated ws a -> a #

Traversable (CommaSeparated ws) Source # 
Instance details

Defined in Waargonaut.Types.CommaSep

Methods

traverse :: Applicative f => (a -> f b) -> CommaSeparated ws a -> f (CommaSeparated ws b) #

sequenceA :: Applicative f => CommaSeparated ws (f a) -> f (CommaSeparated ws a) #

mapM :: Monad m => (a -> m b) -> CommaSeparated ws a -> m (CommaSeparated ws b) #

sequence :: Monad m => CommaSeparated ws (m a) -> m (CommaSeparated ws a) #

Monoid ws => Filterable (CommaSeparated ws) Source # 
Instance details

Defined in Waargonaut.Types.CommaSep

Methods

mapMaybe :: (a -> Maybe b) -> CommaSeparated ws a -> CommaSeparated ws b #

catMaybes :: CommaSeparated ws (Maybe a) -> CommaSeparated ws a #

filter :: (a -> Bool) -> CommaSeparated ws a -> CommaSeparated ws a #

Monoid ws => Witherable (CommaSeparated ws) Source # 
Instance details

Defined in Waargonaut.Types.CommaSep

Methods

wither :: Applicative f => (a -> f (Maybe b)) -> CommaSeparated ws a -> f (CommaSeparated ws b) #

filterA :: Applicative f => (a -> f Bool) -> CommaSeparated ws a -> f (CommaSeparated ws a) #

(Eq ws, Eq a) => Eq (CommaSeparated ws a) Source # 
Instance details

Defined in Waargonaut.Types.CommaSep

Methods

(==) :: CommaSeparated ws a -> CommaSeparated ws a -> Bool #

(/=) :: CommaSeparated ws a -> CommaSeparated ws a -> Bool #

(Show ws, Show a) => Show (CommaSeparated ws a) Source # 
Instance details

Defined in Waargonaut.Types.CommaSep

(Monoid ws, Semigroup ws) => Semigroup (CommaSeparated ws a) Source # 
Instance details

Defined in Waargonaut.Types.CommaSep

(Monoid ws, Semigroup ws) => Monoid (CommaSeparated ws a) Source # 
Instance details

Defined in Waargonaut.Types.CommaSep

Ixed (CommaSeparated ws a) Source #

Without a notion of "keys", this list can only be indexed by Int

Instance details

Defined in Waargonaut.Types.CommaSep

(Semigroup ws, Monoid ws) => AsEmpty (CommaSeparated ws a) Source # 
Instance details

Defined in Waargonaut.Types.CommaSep

Methods

_Empty :: Prism' (CommaSeparated ws a) () #

Monoid ws => Cons (CommaSeparated ws a) (CommaSeparated ws a) a a Source #

By ignoring whitespace we're able to write a Cons instance.

Instance details

Defined in Waargonaut.Types.CommaSep

Methods

_Cons :: Prism (CommaSeparated ws a) (CommaSeparated ws a) (a, CommaSeparated ws a) (a, CommaSeparated ws a) #

Monoid ws => Snoc (CommaSeparated ws a) (CommaSeparated ws a) a a Source # 
Instance details

Defined in Waargonaut.Types.CommaSep

Methods

_Snoc :: Prism (CommaSeparated ws a) (CommaSeparated ws a) (CommaSeparated ws a, a) (CommaSeparated ws a, a) #

type Index (CommaSeparated ws a) Source # 
Instance details

Defined in Waargonaut.Types.CommaSep

type Index (CommaSeparated ws a) = Int
type IxValue (CommaSeparated ws a) Source # 
Instance details

Defined in Waargonaut.Types.CommaSep

type IxValue (CommaSeparated ws a) = a

data Elems ws a Source #

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.

Constructors

Elems 

Fields

Instances
Bitraversable Elems Source # 
Instance details

Defined in Waargonaut.Types.CommaSep

Methods

bitraverse :: Applicative f => (a -> f c) -> (b -> f d) -> Elems a b -> f (Elems c d) #

Bifoldable Elems Source # 
Instance details

Defined in Waargonaut.Types.CommaSep

Methods

bifold :: Monoid m => Elems m m -> m #

bifoldMap :: Monoid m => (a -> m) -> (b -> m) -> Elems a b -> m #

bifoldr :: (a -> c -> c) -> (b -> c -> c) -> c -> Elems a b -> c #

bifoldl :: (c -> a -> c) -> (c -> b -> c) -> c -> Elems a b -> c #

Bifunctor Elems Source # 
Instance details

Defined in Waargonaut.Types.CommaSep

Methods

bimap :: (a -> b) -> (c -> d) -> Elems a c -> Elems b d #

first :: (a -> b) -> Elems a c -> Elems b c #

second :: (b -> c) -> Elems a b -> Elems a c #

Functor (Elems ws) Source # 
Instance details

Defined in Waargonaut.Types.CommaSep

Methods

fmap :: (a -> b) -> Elems ws a -> Elems ws b #

(<$) :: a -> Elems ws b -> Elems ws a #

Monoid ws => Applicative (Elems ws) Source # 
Instance details

Defined in Waargonaut.Types.CommaSep

Methods

pure :: a -> Elems ws a #

(<*>) :: Elems ws (a -> b) -> Elems ws a -> Elems ws b #

liftA2 :: (a -> b -> c) -> Elems ws a -> Elems ws b -> Elems ws c #

(*>) :: Elems ws a -> Elems ws b -> Elems ws b #

(<*) :: Elems ws a -> Elems ws b -> Elems ws a #

Foldable (Elems ws) Source # 
Instance details

Defined in Waargonaut.Types.CommaSep

Methods

fold :: Monoid m => Elems ws m -> 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 #

toList :: Elems ws a -> [a] #

null :: Elems ws a -> Bool #

length :: Elems ws a -> Int #

elem :: Eq a => a -> Elems ws a -> Bool #

maximum :: Ord a => Elems ws a -> a #

minimum :: Ord a => Elems ws a -> a #

sum :: Num a => Elems ws a -> a #

product :: Num a => Elems ws a -> a #

Traversable (Elems ws) Source # 
Instance details

Defined in Waargonaut.Types.CommaSep

Methods

traverse :: Applicative f => (a -> f b) -> Elems ws a -> f (Elems ws b) #

sequenceA :: Applicative f => Elems ws (f a) -> f (Elems ws a) #

mapM :: Monad m => (a -> m b) -> Elems ws a -> m (Elems ws b) #

sequence :: Monad m => Elems ws (m a) -> m (Elems ws a) #

(Eq ws, Eq a) => Eq (Elems ws a) Source # 
Instance details

Defined in Waargonaut.Types.CommaSep

Methods

(==) :: Elems ws a -> Elems ws a -> Bool #

(/=) :: Elems ws a -> Elems ws a -> Bool #

(Show ws, Show a) => Show (Elems ws a) Source # 
Instance details

Defined in Waargonaut.Types.CommaSep

Methods

showsPrec :: Int -> Elems ws a -> ShowS #

show :: Elems ws a -> String #

showList :: [Elems ws a] -> ShowS #

Monoid ws => Semigroup (Elems ws a) Source # 
Instance details

Defined in Waargonaut.Types.CommaSep

Methods

(<>) :: Elems ws a -> Elems ws a -> Elems ws a #

sconcat :: NonEmpty (Elems ws a) -> Elems ws a #

stimes :: Integral b => b -> Elems ws a -> Elems ws a #

HasElems (Elems ws a) ws a Source # 
Instance details

Defined in Waargonaut.Types.CommaSep

Methods

elems :: Lens' (Elems ws a) (Elems ws a) Source #

elemsElems :: Lens' (Elems ws a) (Vector (Elem Identity ws a)) Source #

elemsLast :: Lens' (Elems ws a) (Elem Maybe ws a) Source #

class HasElems c ws a | c -> ws a where Source #

Typeclass for things that contain an Elems structure.

Minimal complete definition

elems

Instances
HasElems (Elems ws a) ws a Source # 
Instance details

Defined in Waargonaut.Types.CommaSep

Methods

elems :: Lens' (Elems ws a) (Elems ws a) Source #

elemsElems :: Lens' (Elems ws a) (Vector (Elem Identity ws a)) Source #

elemsLast :: Lens' (Elems ws a) (Elem Maybe ws a) Source #

data Elem f ws a Source #

Data type to represent a single element in a CommaSeparated list. Carries information about it's own trailing whitespace. Denoted by the f.

Constructors

Elem 

Fields

Instances
Traversable f => Bitraversable (Elem f) Source # 
Instance details

Defined in Waargonaut.Types.CommaSep

Methods

bitraverse :: Applicative f0 => (a -> f0 c) -> (b -> f0 d) -> Elem f a b -> f0 (Elem f c d) #

Foldable f => Bifoldable (Elem f) Source # 
Instance details

Defined in Waargonaut.Types.CommaSep

Methods

bifold :: Monoid m => Elem f m m -> m #

bifoldMap :: Monoid m => (a -> m) -> (b -> m) -> Elem f a b -> m #

bifoldr :: (a -> c -> c) -> (b -> c -> c) -> c -> Elem f a b -> c #

bifoldl :: (c -> a -> c) -> (c -> b -> c) -> c -> Elem f a b -> c #

Functor f => Bifunctor (Elem f) Source # 
Instance details

Defined in Waargonaut.Types.CommaSep

Methods

bimap :: (a -> b) -> (c -> d) -> Elem f a c -> Elem f b d #

first :: (a -> b) -> Elem f a c -> Elem f b c #

second :: (b -> c) -> Elem f a b -> Elem f a c #

Functor (Elem f ws) Source # 
Instance details

Defined in Waargonaut.Types.CommaSep

Methods

fmap :: (a -> b) -> Elem f ws a -> Elem f ws b #

(<$) :: a -> Elem f ws b -> Elem f ws a #

(Monoid ws, Applicative f) => Applicative (Elem f ws) Source # 
Instance details

Defined in Waargonaut.Types.CommaSep

Methods

pure :: a -> Elem f ws a #

(<*>) :: Elem f ws (a -> b) -> Elem f ws a -> Elem f ws b #

liftA2 :: (a -> b -> c) -> Elem f ws a -> Elem f ws b -> Elem f ws c #

(*>) :: Elem f ws a -> Elem f ws b -> Elem f ws b #

(<*) :: Elem f ws a -> Elem f ws b -> Elem f ws a #

Foldable (Elem f ws) Source # 
Instance details

Defined in Waargonaut.Types.CommaSep

Methods

fold :: Monoid m => Elem f ws m -> 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] #

null :: Elem f ws a -> Bool #

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 #

sum :: Num a => Elem f ws a -> a #

product :: Num a => Elem f ws a -> a #

Traversable (Elem f ws) Source # 
Instance details

Defined in Waargonaut.Types.CommaSep

Methods

traverse :: Applicative f0 => (a -> f0 b) -> Elem f ws a -> f0 (Elem f ws b) #

sequenceA :: Applicative f0 => Elem f ws (f0 a) -> f0 (Elem f ws a) #

mapM :: Monad m => (a -> m b) -> Elem f ws a -> m (Elem f ws b) #

sequence :: Monad m => Elem f ws (m a) -> m (Elem f ws a) #

(Eq1 f, Eq ws, Eq a) => Eq (Elem f ws a) Source # 
Instance details

Defined in Waargonaut.Types.CommaSep

Methods

(==) :: Elem f ws a -> Elem f ws a -> Bool #

(/=) :: Elem f ws a -> Elem f ws a -> Bool #

(Show1 f, Show ws, Show a) => Show (Elem f ws a) Source # 
Instance details

Defined in Waargonaut.Types.CommaSep

Methods

showsPrec :: Int -> Elem f ws a -> ShowS #

show :: Elem f ws a -> String #

showList :: [Elem f ws a] -> ShowS #

HasElem (Elem f ws a) f ws a Source # 
Instance details

Defined in Waargonaut.Types.CommaSep

Methods

elem :: Lens' (Elem f ws a) (Elem f ws a) Source #

elemTrailing :: Lens' (Elem f ws a) (f (Comma, ws)) Source #

elemVal :: Lens' (Elem f ws a) a Source #

class HasElem c f ws a | c -> f ws a where Source #

Typeclass for things that contain a single Elem structure.

Minimal complete definition

elem

Methods

elem :: Lens' c (Elem f ws a) Source #

elemTrailing :: Lens' c (f (Comma, ws)) Source #

elemVal :: Lens' c a Source #

Instances
HasElem (Elem f ws a) f ws a Source # 
Instance details

Defined in Waargonaut.Types.CommaSep

Methods

elem :: Lens' (Elem f ws a) (Elem f ws a) Source #

elemTrailing :: Lens' (Elem f ws a) (f (Comma, ws)) Source #

elemVal :: Lens' (Elem f ws a) a Source #

data Comma Source #

Unary type to represent a comma.

Constructors

Comma 
Instances
Eq Comma Source # 
Instance details

Defined in Waargonaut.Types.CommaSep

Methods

(==) :: Comma -> Comma -> Bool #

(/=) :: Comma -> Comma -> Bool #

Show Comma Source # 
Instance details

Defined in Waargonaut.Types.CommaSep

Methods

showsPrec :: Int -> Comma -> ShowS #

show :: Comma -> String #

showList :: [Comma] -> ShowS #

Parse / Build

parseComma :: CharParsing f => f Comma Source #

Parse a single comma (,)

commaBuilder :: Builder Source #

Builder for UTF8 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])}})))

commaSeparatedBuilder :: forall ws a. Char -> Char -> (ws -> Builder) -> (a -> Builder) -> CommaSeparated ws a -> Builder Source #

Using the given builders for the whitespace and elements (a), create a builder for a CommaSeparated.

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.

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.