aeson-filthy-0.1.2: Several newtypes and combinators for dealing with less-than-cleanly JSON input.

Safe HaskellNone
LanguageHaskell2010

Data.Aeson.Filthy

Contents

Description

Several newtypes and combinators for dealing with less-than-cleanly JSON input.

Synopsis

Double-Encodings

newtype JSONString a Source #

A double-encoded JSON value.

>>> encode (JSONString True)
"\"true\""
>>> decode "\"true\"" :: Maybe (JSONString Bool)
Just (JSONString {jsonString = True})

Constructors

JSONString 

Fields

Instances

Bounded a => Bounded (JSONString a) Source # 
Enum a => Enum (JSONString a) Source # 
Eq a => Eq (JSONString a) Source # 

Methods

(==) :: JSONString a -> JSONString a -> Bool #

(/=) :: JSONString a -> JSONString a -> Bool #

Floating a => Floating (JSONString a) Source # 
Fractional a => Fractional (JSONString a) Source # 
Integral a => Integral (JSONString a) Source # 
Num a => Num (JSONString a) Source # 
Ord a => Ord (JSONString a) Source # 
Read a => Read (JSONString a) Source # 
Real a => Real (JSONString a) Source # 
RealFloat a => RealFloat (JSONString a) Source # 
RealFrac a => RealFrac (JSONString a) Source # 

Methods

properFraction :: Integral b => JSONString a -> (b, JSONString a) #

truncate :: Integral b => JSONString a -> b #

round :: Integral b => JSONString a -> b #

ceiling :: Integral b => JSONString a -> b #

floor :: Integral b => JSONString a -> b #

Show a => Show (JSONString a) Source # 
Ix a => Ix (JSONString a) Source # 
IsString a => IsString (JSONString a) Source # 

Methods

fromString :: String -> JSONString a #

Generic (JSONString a) Source # 

Associated Types

type Rep (JSONString a) :: * -> * #

Methods

from :: JSONString a -> Rep (JSONString a) x #

to :: Rep (JSONString a) x -> JSONString a #

ToJSON a => ToJSON (JSONString a) Source # 
FromJSON a => FromJSON (JSONString a) Source # 
Storable a => Storable (JSONString a) Source # 

Methods

sizeOf :: JSONString a -> Int #

alignment :: JSONString a -> Int #

peekElemOff :: Ptr (JSONString a) -> Int -> IO (JSONString a) #

pokeElemOff :: Ptr (JSONString a) -> Int -> JSONString a -> IO () #

peekByteOff :: Ptr b -> Int -> IO (JSONString a) #

pokeByteOff :: Ptr b -> Int -> JSONString a -> IO () #

peek :: Ptr (JSONString a) -> IO (JSONString a) #

poke :: Ptr (JSONString a) -> JSONString a -> IO () #

Bits a => Bits (JSONString a) Source # 
FiniteBits a => FiniteBits (JSONString a) Source # 
type Rep (JSONString a) Source # 
type Rep (JSONString a) = D1 * (MetaData "JSONString" "Data.Aeson.Filthy" "aeson-filthy-0.1.2-3m7QfYgBex14ugsSEuaPoe" True) (C1 * (MetaCons "JSONString" PrefixI True) (S1 * (MetaSel (Just Symbol "jsonString") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * a)))

(.:$) :: FromJSON a => Object -> Text -> Parser a Source #

Works like aeson's (.:), but assumes the value being parsed is double-encoded. Mnemonic: $ sorta looks like an S (for String).

(.=$) :: ToJSON a => Text -> a -> Pair Source #

Works like aeson's (.=), but double-encodes the value being serialized.

Booleans

There's a surprising number of ways people like to encode Booleans. At present, the docs below lie a bit in that values which don't parse to a True value are considered false. For instance,

>>> oneOrZero <$> decode "0"
Just False
>>> oneOrZero <$> decode "1"
Just True
>>> oneOrZero <$> decode "2"
Just False

newtype OneOrZero Source #

Bools rendered 0 or 1

>>> oneOrZero <$> decode "1"
Just True
>>> oneOrZero <$> decode "0"
Just False

Constructors

OneOrZero 

Fields

Instances

Bounded OneOrZero Source # 
Enum OneOrZero Source # 
Eq OneOrZero Source # 
Ord OneOrZero Source # 
Read OneOrZero Source # 
Show OneOrZero Source # 
Ix OneOrZero Source # 
Generic OneOrZero Source # 

Associated Types

type Rep OneOrZero :: * -> * #

ToJSON OneOrZero Source # 
FromJSON OneOrZero Source # 
Storable OneOrZero Source # 
Bits OneOrZero Source # 
FiniteBits OneOrZero Source # 
type Rep OneOrZero Source # 
type Rep OneOrZero = D1 * (MetaData "OneOrZero" "Data.Aeson.Filthy" "aeson-filthy-0.1.2-3m7QfYgBex14ugsSEuaPoe" True) (C1 * (MetaCons "OneOrZero" PrefixI True) (S1 * (MetaSel (Just Symbol "oneOrZero") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Bool)))

newtype YesOrNo Source #

Bools rendered "yes" or "no"

>>> yesOrNo <$> decode "\"yes\""
Just True
>>> yesOrNo <$> decode "\"no\""
Just False

Constructors

YesOrNo 

Fields

Instances

Bounded YesOrNo Source # 
Enum YesOrNo Source # 
Eq YesOrNo Source # 

Methods

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

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

Ord YesOrNo Source # 
Read YesOrNo Source # 
Show YesOrNo Source # 
Ix YesOrNo Source # 
Generic YesOrNo Source # 

Associated Types

type Rep YesOrNo :: * -> * #

Methods

from :: YesOrNo -> Rep YesOrNo x #

to :: Rep YesOrNo x -> YesOrNo #

ToJSON YesOrNo Source # 
FromJSON YesOrNo Source # 
Storable YesOrNo Source # 
Bits YesOrNo Source # 
FiniteBits YesOrNo Source # 
type Rep YesOrNo Source # 
type Rep YesOrNo = D1 * (MetaData "YesOrNo" "Data.Aeson.Filthy" "aeson-filthy-0.1.2-3m7QfYgBex14ugsSEuaPoe" True) (C1 * (MetaCons "YesOrNo" PrefixI True) (S1 * (MetaSel (Just Symbol "yesOrNo") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Bool)))

newtype OnOrOff Source #

Bools rendered "on" or "off"

>>> onOrOff <$> decode "\"on\""
Just True
>>> onOrOff <$> decode "\"off\""
Just False

Constructors

OnOrOff 

Fields

Instances

Bounded OnOrOff Source # 
Enum OnOrOff Source # 
Eq OnOrOff Source # 

Methods

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

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

Ord OnOrOff Source # 
Read OnOrOff Source # 
Show OnOrOff Source # 
Ix OnOrOff Source # 
Generic OnOrOff Source # 

Associated Types

type Rep OnOrOff :: * -> * #

Methods

from :: OnOrOff -> Rep OnOrOff x #

to :: Rep OnOrOff x -> OnOrOff #

ToJSON OnOrOff Source # 
FromJSON OnOrOff Source # 
Storable OnOrOff Source # 
Bits OnOrOff Source # 
FiniteBits OnOrOff Source # 
type Rep OnOrOff Source # 
type Rep OnOrOff = D1 * (MetaData "OnOrOff" "Data.Aeson.Filthy" "aeson-filthy-0.1.2-3m7QfYgBex14ugsSEuaPoe" True) (C1 * (MetaCons "OnOrOff" PrefixI True) (S1 * (MetaSel (Just Symbol "onOrOff") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Bool)))

newtype AnyBool Source #

Bools rendered as more-or-less anything.

>>> let Just bs = decode "[1, \"1\", \"true\", \"yes\", \"on\", true]"
>>> and $ map anyBool bs
True

Constructors

AnyBool 

Fields

Instances

Bounded AnyBool Source # 
Enum AnyBool Source # 
Eq AnyBool Source # 

Methods

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

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

Ord AnyBool Source # 
Read AnyBool Source # 
Show AnyBool Source # 
Ix AnyBool Source # 
Generic AnyBool Source # 

Associated Types

type Rep AnyBool :: * -> * #

Methods

from :: AnyBool -> Rep AnyBool x #

to :: Rep AnyBool x -> AnyBool #

FromJSON AnyBool Source # 
Storable AnyBool Source # 
Bits AnyBool Source # 
FiniteBits AnyBool Source # 
type Rep AnyBool Source # 
type Rep AnyBool = D1 * (MetaData "AnyBool" "Data.Aeson.Filthy" "aeson-filthy-0.1.2-3m7QfYgBex14ugsSEuaPoe" True) (C1 * (MetaCons "AnyBool" PrefixI True) (S1 * (MetaSel (Just Symbol "anyBool") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Bool)))

Maybe

newtype EmptyAsNothing a Source #

Sometimes an empty string in a JSON object actually means Nothing

>>> emptyAsNothing <$> decode "\"\"" :: Maybe (Maybe Text)
Just Nothing
>>> emptyAsNothing <$> decode "\"something\"" :: Maybe (Maybe Text)
Just (Just "something")

Constructors

EmptyAsNothing 

Fields

Instances

Monad EmptyAsNothing Source # 
Functor EmptyAsNothing Source # 

Methods

fmap :: (a -> b) -> EmptyAsNothing a -> EmptyAsNothing b #

(<$) :: a -> EmptyAsNothing b -> EmptyAsNothing a #

MonadFix EmptyAsNothing Source # 

Methods

mfix :: (a -> EmptyAsNothing a) -> EmptyAsNothing a #

Applicative EmptyAsNothing Source # 
Foldable EmptyAsNothing Source # 

Methods

fold :: Monoid m => EmptyAsNothing m -> m #

foldMap :: Monoid m => (a -> m) -> EmptyAsNothing a -> m #

foldr :: (a -> b -> b) -> b -> EmptyAsNothing a -> b #

foldr' :: (a -> b -> b) -> b -> EmptyAsNothing a -> b #

foldl :: (b -> a -> b) -> b -> EmptyAsNothing a -> b #

foldl' :: (b -> a -> b) -> b -> EmptyAsNothing a -> b #

foldr1 :: (a -> a -> a) -> EmptyAsNothing a -> a #

foldl1 :: (a -> a -> a) -> EmptyAsNothing a -> a #

toList :: EmptyAsNothing a -> [a] #

null :: EmptyAsNothing a -> Bool #

length :: EmptyAsNothing a -> Int #

elem :: Eq a => a -> EmptyAsNothing a -> Bool #

maximum :: Ord a => EmptyAsNothing a -> a #

minimum :: Ord a => EmptyAsNothing a -> a #

sum :: Num a => EmptyAsNothing a -> a #

product :: Num a => EmptyAsNothing a -> a #

Traversable EmptyAsNothing Source # 

Methods

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

sequenceA :: Applicative f => EmptyAsNothing (f a) -> f (EmptyAsNothing a) #

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

sequence :: Monad m => EmptyAsNothing (m a) -> m (EmptyAsNothing a) #

Alternative EmptyAsNothing Source # 
MonadPlus EmptyAsNothing Source # 
Eq a => Eq (EmptyAsNothing a) Source # 
Ord a => Ord (EmptyAsNothing a) Source # 
Read a => Read (EmptyAsNothing a) Source # 
Show a => Show (EmptyAsNothing a) Source # 
Generic (EmptyAsNothing a) Source # 

Associated Types

type Rep (EmptyAsNothing a) :: * -> * #

Semigroup a => Semigroup (EmptyAsNothing a) Source # 
Monoid a => Monoid (EmptyAsNothing a) Source # 
ToJSON a => ToJSON (EmptyAsNothing a) Source # 
FromJSON a => FromJSON (EmptyAsNothing a) Source # 
Generic1 * EmptyAsNothing Source # 

Associated Types

type Rep1 EmptyAsNothing (f :: EmptyAsNothing -> *) :: k -> * #

Methods

from1 :: f a -> Rep1 EmptyAsNothing f a #

to1 :: Rep1 EmptyAsNothing f a -> f a #

type Rep (EmptyAsNothing a) Source # 
type Rep (EmptyAsNothing a) = D1 * (MetaData "EmptyAsNothing" "Data.Aeson.Filthy" "aeson-filthy-0.1.2-3m7QfYgBex14ugsSEuaPoe" True) (C1 * (MetaCons "EmptyAsNothing" PrefixI True) (S1 * (MetaSel (Just Symbol "emptyAsNothing") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe a))))
type Rep1 * EmptyAsNothing Source # 
type Rep1 * EmptyAsNothing = D1 * (MetaData "EmptyAsNothing" "Data.Aeson.Filthy" "aeson-filthy-0.1.2-3m7QfYgBex14ugsSEuaPoe" True) (C1 * (MetaCons "EmptyAsNothing" PrefixI True) (S1 * (MetaSel (Just Symbol "emptyAsNothing") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec1 * Maybe)))

Case Insensitive Keys

(.:~) :: FromJSON a => Object -> Text -> Parser a Source #

Some systems attempt to treat keys in JSON objects case-insensitively(ish). Golang's JSON marshalling is a prominent example: https://golang.org/pkg/encoding/json/#Marshal. The (.:~) combinator works like (.:), but if it fails to match, attempts to find a case-insensitive variant of the key being sought. If there is an exact match, (.:~) will take that; if there are multiple non-exact matches, the choice of selected value is unspecified. Mnemonic: ~ swaps case in vi.

>>> data Foo = Foo Int deriving (Read, Show)
>>> instance FromJSON Foo where parseJSON (Object o) = Foo <$> o .:~ "foo"
>>> decode "{\"FOO\": 12}" :: Maybe Foo
Just (Foo 12)
>>> decode "{\"foo\": 17, \"FOO\": 12}" :: Maybe Foo
Just (Foo 17)