waargonaut-0.8.0.2: JSON wrangling
Safe HaskellNone
LanguageHaskell2010

Waargonaut.Types.Whitespace

Description

Parsers and builders for whitespace characters in our JSON.

Synopsis

Documentation

data Whitespace Source #

Represent the different types of whitespace.

newtype WS Source #

This is a wrapper for a sequence of consecutive whitespace.

Constructors

WS (Vector Whitespace) 

Instances

Instances details
Eq WS Source # 
Instance details

Defined in Waargonaut.Types.Whitespace

Methods

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

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

Show WS Source # 
Instance details

Defined in Waargonaut.Types.Whitespace

Methods

showsPrec :: Int -> WS -> ShowS #

show :: WS -> String #

showList :: [WS] -> ShowS #

Semigroup WS Source # 
Instance details

Defined in Waargonaut.Types.Whitespace

Methods

(<>) :: WS -> WS -> WS #

sconcat :: NonEmpty WS -> WS #

stimes :: Integral b => b -> WS -> WS #

Monoid WS Source # 
Instance details

Defined in Waargonaut.Types.Whitespace

Methods

mempty :: WS #

mappend :: WS -> WS -> WS #

mconcat :: [WS] -> WS #

AsEmpty WS Source # 
Instance details

Defined in Waargonaut.Types.Whitespace

Methods

_Empty :: Prism' WS ()

Wrapped WS Source # 
Instance details

Defined in Waargonaut.Types.Whitespace

Associated Types

type Unwrapped WS

Methods

_Wrapped' :: Iso' WS (Unwrapped WS)

WS ~ t => Rewrapped WS t Source # 
Instance details

Defined in Waargonaut.Types.Whitespace

AsJType Json WS Json Source #

Json is comprised of the different JType types.

Instance details

Defined in Waargonaut.Types.Json

Methods

_JType :: Prism' Json (JType WS Json) Source #

_JNull :: Prism' Json WS Source #

_JBool :: Prism' Json (Bool, WS) Source #

_JNum :: Prism' Json (JNumber, WS) Source #

_JStr :: Prism' Json (JString, WS) Source #

_JArr :: Prism' Json (JArray WS Json, WS) Source #

_JObj :: Prism' Json (JObject WS Json, WS) Source #

Cons WS WS Whitespace Whitespace Source # 
Instance details

Defined in Waargonaut.Types.Whitespace

Methods

_Cons :: Prism WS WS (Whitespace, WS) (Whitespace, WS)

Applicative f => Decidable (EncoderFns (JObject WS Json) f) 
Instance details

Defined in Waargonaut.Encode.Types

Methods

lose :: (a -> Void) -> EncoderFns (JObject WS Json) f a

choose :: (a -> Either b c) -> EncoderFns (JObject WS Json) f b -> EncoderFns (JObject WS Json) f c -> EncoderFns (JObject WS Json) f a

Applicative f => Divisible (EncoderFns (JObject WS Json) f) 
Instance details

Defined in Waargonaut.Encode.Types

Methods

divide :: (a -> (b, c)) -> EncoderFns (JObject WS Json) f b -> EncoderFns (JObject WS Json) f c -> EncoderFns (JObject WS Json) f a

conquer :: EncoderFns (JObject WS Json) f a

type Unwrapped WS Source # 
Instance details

Defined in Waargonaut.Types.Whitespace

type Unwrapped WS = Vector Whitespace

_WhitespaceChar :: Prism' Char Whitespace Source #

Handy Prism' between a Char its possible Whitespace representation.

escapedWhitespaceChar :: Whitespace -> Char Source #

Change a Whitespace into its escaped Char form.

unescapedWhitespaceChar :: Whitespace -> Char Source #

Change a Whitespace into a single unescaped Char. Useful if you're already handling escaping with some other mechanism.

oneWhitespace :: CharParsing f => f Whitespace Source #

Parse a single Whitespace character.

parseWhitespace :: CharParsing f => f WS Source #

>>> testparse parseWhitespace " "
Right (WS [Space])
>>> testparse parseWhitespace "\n    "
Right (WS [NewLine,Space,Space,Space,Space])
>>> testparse parseWhitespace " \t"
Right (WS [Space,HorizontalTab])
>>> testparse parseWhitespace "\f\f"
Right (WS [LineFeed,LineFeed])
>>> testparse parseWhitespace "\r\r\r"
Right (WS [CarriageReturn,CarriageReturn,CarriageReturn])
>>> testparse parseWhitespace "\n\r\r\n"
Right (WS [NewLine,CarriageReturn,CarriageReturn,NewLine])
>>> testparse parseWhitespace ""
Right (WS [])
>>> testparse parseWhitespace "\n   ]"
Right (WS [NewLine,Space,Space,Space])

parseSomeWhitespace :: CharParsing f => f (NonEmpty Whitespace) Source #

Parse a NonEmpty sequence of consecutive whitespace.