{-# LANGUAGE CPP #-}
{-# LANGUAGE LambdaCase #-}
module Data.Aeson.Combinators.Decode (
Decoder(..)
, auto
, fromDecoder
, nullable
, list, vector
, hashMapLazy, hashMapStrict, keyMap
, mapLazy, mapStrict
, jsonNull
, key
, maybeKey
, at
, index
, indexes
, element
, path
, maybe
, either
, oneOf
, void
, unit, bool
, int, integer, int8, int16, int32, int64
, word, word8, word16, word32, word64
#if (MIN_VERSION_base(4,8,0))
, natural
#endif
, float, double
, scientific
, char, text, string
, uuid, version
, zonedTime, localTime, timeOfDay
, utcTime
, day
#if (MIN_VERSION_time_compat(1,9,2))
, dayOfWeek
#endif
, decode, decode'
, eitherDecode, eitherDecode'
, decodeStrict, decodeStrict'
, eitherDecodeStrict, eitherDecodeStrict'
, decodeFileStrict, decodeFileStrict'
, eitherDecodeFileStrict, eitherDecodeFileStrict'
, parseMaybe
, parseEither
, module Data.Aeson.Combinators.Compat
) where
import Prelude hiding (either, fail, maybe)
import qualified Prelude (either, maybe)
import Control.Applicative
import Control.Monad hiding (void)
import Control.Monad.Fail (MonadFail (..))
import qualified Control.Monad.Fail as Fail
import Data.Aeson.Combinators.Compat
import Data.Aeson.Internal (JSONPath, JSONPathElement (..))
import qualified Data.Aeson.Internal as AI
import qualified Data.Aeson.Parser as Parser
import qualified Data.Aeson.Parser.Internal as ParserI
import Data.Aeson.Types hiding (parseEither, parseMaybe)
import qualified Data.Aeson.Types as ATypes
import qualified Data.ByteString as B
import qualified Data.ByteString.Lazy as LB
import Data.List.NonEmpty (NonEmpty (..))
import Data.Text (Text)
import qualified Data.Vector as Vector
import Data.Int (Int16, Int32, Int64, Int8)
import Data.Time.Calendar (Day)
#if (MIN_VERSION_time_compat(1,9,2))
import Data.Time.Calendar.Compat (DayOfWeek)
#endif
import Data.Time.Clock (UTCTime)
import Data.Time.LocalTime (LocalTime, TimeOfDay, ZonedTime)
import Data.UUID.Types (UUID)
import Data.Vector (Vector, (!?))
import Data.Version (Version)
import Data.Void (Void)
import Data.Word (Word, Word16, Word32, Word64,
Word8)
#if (MIN_VERSION_base(4,8,0))
import GHC.Natural (Natural)
#endif
import qualified Data.HashMap.Lazy as HL
import qualified Data.HashMap.Strict as HS
import qualified Data.Map.Lazy as ML
import qualified Data.Map.Strict as MS
import Data.Scientific (Scientific)
import Data.Traversable (traverse)
newtype Decoder a =
Decoder (Value -> Parser a)
instance Functor Decoder where
fmap :: forall a b. (a -> b) -> Decoder a -> Decoder b
fmap a -> b
f (Decoder Value -> Parser a
d) = forall a. (Value -> Parser a) -> Decoder a
Decoder forall a b. (a -> b) -> a -> b
$ forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap a -> b
f forall b c a. (b -> c) -> (a -> b) -> a -> c
. Value -> Parser a
d
{-# INLINE fmap #-}
instance Applicative Decoder where
pure :: forall a. a -> Decoder a
pure a
val = forall a. (Value -> Parser a) -> Decoder a
Decoder forall a b. (a -> b) -> a -> b
$ \Value
_ -> forall (f :: * -> *) a. Applicative f => a -> f a
pure a
val
{-# INLINE pure #-}
(Decoder Value -> Parser (a -> b)
f') <*> :: forall a b. Decoder (a -> b) -> Decoder a -> Decoder b
<*> (Decoder Value -> Parser a
d) = forall a. (Value -> Parser a) -> Decoder a
Decoder forall a b. (a -> b) -> a -> b
$
\Value
val ->
(\a -> b
f -> forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap a -> b
f (Value -> Parser a
d Value
val)) forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< Value -> Parser (a -> b)
f' Value
val
{-# INLINE (<*>) #-}
instance Monad Decoder where
return :: forall a. a -> Decoder a
return = forall (f :: * -> *) a. Applicative f => a -> f a
pure
(Decoder Value -> Parser a
a) >>= :: forall a b. Decoder a -> (a -> Decoder b) -> Decoder b
>>= a -> Decoder b
f = forall a. (Value -> Parser a) -> Decoder a
Decoder forall a b. (a -> b) -> a -> b
$
\Value
val -> case forall a b. (a -> Parser b) -> a -> Result b
parse Value -> Parser a
a Value
val of
Success a
v -> let (Decoder Value -> Parser b
res) = a -> Decoder b
f a
v
in Value -> Parser b
res Value
val
Result a
_ -> forall a. Value -> Parser a
unexpected Value
val
{-# INLINE (>>=) #-}
#if !(MIN_VERSION_base(4,13,0))
fail = Fail.fail
#endif
instance Alternative Decoder where
empty :: forall a. Decoder a
empty = forall a. (Value -> Parser a) -> Decoder a
Decoder forall a. Value -> Parser a
unexpected
{-# INLINE empty #-}
Decoder Value -> Parser a
a <|> :: forall a. Decoder a -> Decoder a -> Decoder a
<|> Decoder Value -> Parser a
b = forall a. (Value -> Parser a) -> Decoder a
Decoder forall a b. (a -> b) -> a -> b
$ \Value
v -> Value -> Parser a
a Value
v forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> Value -> Parser a
b Value
v
{-# INLINE (<|>) #-}
instance MonadFail Decoder where
fail :: forall a. String -> Decoder a
fail String
s = forall a. (Value -> Parser a) -> Decoder a
Decoder forall a b. (a -> b) -> a -> b
$ \Value
_ -> forall (m :: * -> *) a. MonadFail m => String -> m a
Fail.fail String
s
{-# INLINE fail #-}
fromDecoder :: Decoder a -> Value -> Parser a
fromDecoder :: forall a. Decoder a -> Value -> Parser a
fromDecoder (Decoder Value -> Parser a
f) = Value -> Parser a
f
{-# INLINE fromDecoder #-}
auto :: FromJSON a => Decoder a
auto :: forall a. FromJSON a => Decoder a
auto = forall a. (Value -> Parser a) -> Decoder a
Decoder forall a. FromJSON a => Value -> Parser a
parseJSON
{-# INLINE auto #-}
nullable :: Decoder a -> Decoder (Maybe a)
nullable :: forall a. Decoder a -> Decoder (Maybe a)
nullable (Decoder Value -> Parser a
d) = forall a. (Value -> Parser a) -> Decoder a
Decoder forall a b. (a -> b) -> a -> b
$ \case
Value
Null -> forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a. Maybe a
Nothing
Value
other -> forall a. a -> Maybe a
Just forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Value -> Parser a
d Value
other
{-# INLINE nullable #-}
list :: Decoder a -> Decoder [a]
list :: forall a. Decoder a -> Decoder [a]
list (Decoder Value -> Parser a
d) = forall a. (Value -> Parser a) -> Decoder a
Decoder forall a b. (a -> b) -> a -> b
$
forall a. (Value -> Parser a) -> Value -> Parser [a]
listParser Value -> Parser a
d
{-# INLINE list #-}
vector :: Decoder a -> Decoder (Vector a)
vector :: forall a. Decoder a -> Decoder (Vector a)
vector (Decoder Value -> Parser a
d) = forall a. (Value -> Parser a) -> Decoder a
Decoder forall a b. (a -> b) -> a -> b
$ \case
Array Array
v -> forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> Vector a -> m (Vector b)
Vector.mapM Value -> Parser a
d Array
v
Value
other -> forall a. String -> Value -> Parser a
typeMismatch String
"Array" Value
other
{-# INLINE vector #-}
hashMapLazy :: Decoder a -> Decoder (HL.HashMap Text a)
hashMapLazy :: forall a. Decoder a -> Decoder (HashMap Text a)
hashMapLazy (Decoder Value -> Parser a
d) = forall a. (Value -> Parser a) -> Decoder a
Decoder forall a b. (a -> b) -> a -> b
$ \case
Object Object
xs -> forall v. KeyMap v -> HashMap Text v
toHashMapText forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
(a -> f b) -> t a -> f (t b)
traverse Value -> Parser a
d Object
xs
Value
val -> forall a. String -> Value -> Parser a
typeMismatch String
"Array" Value
val
{-# INLINE hashMapLazy #-}
hashMapStrict :: Decoder a -> Decoder (HS.HashMap Text a)
hashMapStrict :: forall a. Decoder a -> Decoder (HashMap Text a)
hashMapStrict (Decoder Value -> Parser a
d) = forall a. (Value -> Parser a) -> Decoder a
Decoder forall a b. (a -> b) -> a -> b
$ \case
Object Object
xs -> forall v. KeyMap v -> HashMap Text v
toHashMapText forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
(a -> f b) -> t a -> f (t b)
traverse Value -> Parser a
d Object
xs
Value
val -> forall a. String -> Value -> Parser a
typeMismatch String
"Array" Value
val
{-# INLINE hashMapStrict #-}
keyMap :: Decoder a -> Decoder (KeyMap a)
keyMap :: forall a. Decoder a -> Decoder (KeyMap a)
keyMap (Decoder Value -> Parser a
d) = forall a. (Value -> Parser a) -> Decoder a
Decoder forall a b. (a -> b) -> a -> b
$ \case
Object Object
xs -> forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
(a -> f b) -> t a -> f (t b)
traverse Value -> Parser a
d Object
xs
Value
val -> forall a. String -> Value -> Parser a
typeMismatch String
"Array" Value
val
{-# INLINE keyMap #-}
mapLazy :: Decoder a -> Decoder (ML.Map Text a)
mapLazy :: forall a. Decoder a -> Decoder (Map Text a)
mapLazy Decoder a
dec = forall k a. Ord k => [(k, a)] -> Map k a
ML.fromList forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall k v. HashMap k v -> [(k, v)]
HL.toList forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall a. Decoder a -> Decoder (HashMap Text a)
hashMapLazy Decoder a
dec
{-# INLINE mapLazy #-}
mapStrict :: Decoder a -> Decoder (MS.Map Text a)
mapStrict :: forall a. Decoder a -> Decoder (Map Text a)
mapStrict Decoder a
dec = forall k a. Ord k => [(k, a)] -> Map k a
MS.fromList forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall k v. HashMap k v -> [(k, v)]
HL.toList forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall a. Decoder a -> Decoder (HashMap Text a)
hashMapLazy Decoder a
dec
{-# INLINE mapStrict #-}
jsonNull :: a -> Decoder a
jsonNull :: forall a. a -> Decoder a
jsonNull a
a = forall a. (Value -> Parser a) -> Decoder a
Decoder forall a b. (a -> b) -> a -> b
$ \case
Value
Null -> forall (f :: * -> *) a. Applicative f => a -> f a
pure a
a
Value
val -> forall a. String -> Value -> Parser a
typeMismatch String
"null" Value
val
{-# INLINE jsonNull #-}
key :: Key -> Decoder a -> Decoder a
key :: forall a. Key -> Decoder a -> Decoder a
key Key
t (Decoder Value -> Parser a
d) = forall a. (Value -> Parser a) -> Decoder a
Decoder forall a b. (a -> b) -> a -> b
$ \case
Object Object
v -> Value -> Parser a
d forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< Object
v forall a. FromJSON a => Object -> Key -> Parser a
.: Key
t
Value
val -> forall a. String -> Value -> Parser a
typeMismatch String
"Object" Value
val
{-# INLINE key #-}
maybeKey :: Key -> Decoder a -> Decoder (Maybe a)
maybeKey :: forall a. Key -> Decoder a -> Decoder (Maybe a)
maybeKey Key
t (Decoder Value -> Parser a
d) = forall a. (Value -> Parser a) -> Decoder a
Decoder forall a b. (a -> b) -> a -> b
$ \case
Object Object
v -> (Object
v forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
t) forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= forall b a. b -> (a -> b) -> Maybe a -> b
Prelude.maybe (forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a. Maybe a
Nothing) (forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap forall a. a -> Maybe a
Just forall b c a. (b -> c) -> (a -> b) -> a -> c
. Value -> Parser a
d)
Value
val -> forall a. String -> Value -> Parser a
typeMismatch String
"Object" Value
val
{-# INLINE maybeKey #-}
at :: [Key] -> Decoder a -> Decoder a
at :: forall a. [Key] -> Decoder a -> Decoder a
at [Key]
pth Decoder a
d = forall (t :: * -> *) a b.
Foldable t =>
(a -> b -> b) -> b -> t a -> b
foldr forall a. Key -> Decoder a -> Decoder a
key Decoder a
d [Key]
pth
{-# INLINE at #-}
index :: Int -> Decoder a -> Decoder a
index :: forall a. Int -> Decoder a -> Decoder a
index Int
i (Decoder Value -> Parser a
d) = forall a. (Value -> Parser a) -> Decoder a
Decoder forall a b. (a -> b) -> a -> b
$ \Value
val ->
case Value
val of
Array Array
vec -> case Array
vec forall a. Vector a -> Int -> Maybe a
!? Int
i of
Just Value
v -> Value -> Parser a
d Value
v
Maybe Value
Nothing -> forall a. Value -> Parser a
unexpected Value
val
Value
_ -> forall a. String -> Value -> Parser a
typeMismatch String
"Array" Value
val
{-# INLINE index #-}
indexes :: [Int] -> Decoder a -> Decoder a
indexes :: forall a. [Int] -> Decoder a -> Decoder a
indexes [Int]
pth Decoder a
d = forall (t :: * -> *) a b.
Foldable t =>
(a -> b -> b) -> b -> t a -> b
foldr forall a. Int -> Decoder a -> Decoder a
index Decoder a
d [Int]
pth
{-# INLINE indexes #-}
element :: JSONPathElement -> Decoder a -> Decoder a
element :: forall a. JSONPathElement -> Decoder a -> Decoder a
element (Key Key
txt) = forall a. Key -> Decoder a -> Decoder a
key Key
txt
element (Index Int
i) = forall a. Int -> Decoder a -> Decoder a
index Int
i
{-# INLINE element #-}
path :: JSONPath -> Decoder a -> Decoder a
path :: forall a. JSONPath -> Decoder a -> Decoder a
path JSONPath
pth Decoder a
d = forall (t :: * -> *) a b.
Foldable t =>
(a -> b -> b) -> b -> t a -> b
foldr forall a. JSONPathElement -> Decoder a -> Decoder a
element Decoder a
d JSONPath
pth
{-# INLINE path #-}
maybe :: Decoder a -> Decoder (Maybe a)
maybe :: forall a. Decoder a -> Decoder (Maybe a)
maybe (Decoder Value -> Parser a
d) =
forall a. (Value -> Parser a) -> Decoder a
Decoder forall a b. (a -> b) -> a -> b
$ \Value
val ->
case forall a b. (a -> Parser b) -> a -> Result b
parse Value -> Parser a
d Value
val of
Success a
x -> forall (f :: * -> *) a. Applicative f => a -> f a
pure (forall a. a -> Maybe a
Just a
x)
Error String
_ -> forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a. Maybe a
Nothing
{-# INLINE maybe #-}
either :: Decoder a -> Decoder (Either String a)
either :: forall a. Decoder a -> Decoder (Either String a)
either (Decoder Value -> Parser a
d) =
forall a. (Value -> Parser a) -> Decoder a
Decoder forall a b. (a -> b) -> a -> b
$ \Value
val ->
case forall a b. (a -> Parser b) -> a -> Result b
parse Value -> Parser a
d Value
val of
Success a
x -> forall (f :: * -> *) a. Applicative f => a -> f a
pure (forall a b. b -> Either a b
Right a
x)
Error String
err -> forall (f :: * -> *) a. Applicative f => a -> f a
pure (forall a b. a -> Either a b
Left String
err)
{-# INLINE either #-}
oneOf :: NonEmpty (Decoder a) -> Decoder a
oneOf :: forall a. NonEmpty (Decoder a) -> Decoder a
oneOf (Decoder a
first :| [Decoder a]
rest) =
forall (t :: * -> *) b a.
Foldable t =>
(b -> a -> b) -> b -> t a -> b
foldl forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
(<|>) Decoder a
first [Decoder a]
rest
{-# INLINE oneOf #-}
void :: Decoder Void
void :: Decoder Void
void = forall a. FromJSON a => Decoder a
auto
{-# INLINE void #-}
unit :: Decoder ()
unit :: Decoder ()
unit = forall a. FromJSON a => Decoder a
auto
{-# INLINE unit #-}
bool :: Decoder Bool
bool :: Decoder Bool
bool = forall a. FromJSON a => Decoder a
auto
{-# INLINE bool #-}
int :: Decoder Int
int :: Decoder Int
int = forall a. FromJSON a => Decoder a
auto
{-# INLINE int #-}
int8 :: Decoder Int8
int8 :: Decoder Int8
int8 = forall a. FromJSON a => Decoder a
auto
{-# INLINE int8 #-}
int16 :: Decoder Int16
int16 :: Decoder Int16
int16 = forall a. FromJSON a => Decoder a
auto
{-# INLINE int16 #-}
int32 :: Decoder Int32
int32 :: Decoder Int32
int32 = forall a. FromJSON a => Decoder a
auto
{-# INLINE int32 #-}
int64 :: Decoder Int64
int64 :: Decoder Int64
int64 = forall a. FromJSON a => Decoder a
auto
{-# INLINE int64 #-}
integer :: Decoder Integer
integer :: Decoder Integer
integer = forall a. FromJSON a => Decoder a
auto
{-# INLINE integer #-}
#if (MIN_VERSION_base(4,8,0))
natural :: Decoder Natural
natural :: Decoder Natural
natural = forall a. FromJSON a => Decoder a
auto
{-# INLINE natural #-}
#endif
word :: Decoder Word
word :: Decoder Word
word = forall a. FromJSON a => Decoder a
auto
{-# INLINE word #-}
word8 :: Decoder Word8
word8 :: Decoder Word8
word8 = forall a. FromJSON a => Decoder a
auto
{-# INLINE word8 #-}
word16 :: Decoder Word16
word16 :: Decoder Word16
word16 = forall a. FromJSON a => Decoder a
auto
{-# INLINE word16 #-}
word32 :: Decoder Word32
word32 :: Decoder Word32
word32 = forall a. FromJSON a => Decoder a
auto
{-# INLINE word32 #-}
word64 :: Decoder Word64
word64 :: Decoder Word64
word64 = forall a. FromJSON a => Decoder a
auto
{-# INLINE word64 #-}
float :: Decoder Float
float :: Decoder Float
float = forall a. FromJSON a => Decoder a
auto
{-# INLINE float #-}
double :: Decoder Double
double :: Decoder Double
double = forall a. FromJSON a => Decoder a
auto
{-# INLINE double #-}
scientific :: Decoder Scientific
scientific :: Decoder Scientific
scientific = forall a. FromJSON a => Decoder a
auto
{-# INLINE scientific #-}
char :: Decoder Char
char :: Decoder Char
char = forall a. FromJSON a => Decoder a
auto
{-# INLINE char #-}
string :: Decoder String
string :: Decoder String
string = forall a. FromJSON a => Decoder a
auto
{-# INLINE string #-}
text :: Decoder Text
text :: Decoder Text
text = forall a. FromJSON a => Decoder a
auto
{-# INLINE text #-}
uuid :: Decoder UUID
uuid :: Decoder UUID
uuid = forall a. FromJSON a => Decoder a
auto
{-# INLINE uuid #-}
version :: Decoder Version
version :: Decoder Version
version = forall a. FromJSON a => Decoder a
auto
{-# INLINE version #-}
zonedTime :: Decoder ZonedTime
zonedTime :: Decoder ZonedTime
zonedTime = forall a. FromJSON a => Decoder a
auto
{-# INLINE zonedTime #-}
localTime :: Decoder LocalTime
localTime :: Decoder LocalTime
localTime = forall a. FromJSON a => Decoder a
auto
{-# INLINE localTime #-}
timeOfDay :: Decoder TimeOfDay
timeOfDay :: Decoder TimeOfDay
timeOfDay = forall a. FromJSON a => Decoder a
auto
{-# INLINE timeOfDay #-}
utcTime :: Decoder UTCTime
utcTime :: Decoder UTCTime
utcTime = forall a. FromJSON a => Decoder a
auto
{-# INLINE utcTime #-}
day :: Decoder Day
day :: Decoder Day
day = forall a. FromJSON a => Decoder a
auto
{-# INLINE day #-}
#if (MIN_VERSION_time_compat(1,9,2))
dayOfWeek :: Decoder DayOfWeek
dayOfWeek :: Decoder DayOfWeek
dayOfWeek = forall a. FromJSON a => Decoder a
auto
{-# INLINE dayOfWeek #-}
#endif
decode :: Decoder a -> LB.ByteString -> Maybe a
decode :: forall a. Decoder a -> ByteString -> Maybe a
decode (Decoder Value -> Parser a
d) =
forall a.
Parser Value -> (Value -> Result a) -> ByteString -> Maybe a
Parser.decodeWith Parser Value
ParserI.jsonEOF (forall a b. (a -> Parser b) -> a -> Result b
parse Value -> Parser a
d)
{-# INLINE decode #-}
decode' :: Decoder a -> LB.ByteString -> Maybe a
decode' :: forall a. Decoder a -> ByteString -> Maybe a
decode' (Decoder Value -> Parser a
d) =
forall a.
Parser Value -> (Value -> Result a) -> ByteString -> Maybe a
Parser.decodeWith Parser Value
ParserI.jsonEOF' (forall a b. (a -> Parser b) -> a -> Result b
parse Value -> Parser a
d)
{-# INLINE decode' #-}
eitherDecode :: Decoder a -> LB.ByteString -> Either String a
eitherDecode :: forall a. Decoder a -> ByteString -> Either String a
eitherDecode (Decoder Value -> Parser a
d) =
forall a. Either (JSONPath, String) a -> Either String a
eitherFormatError forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a.
Parser Value
-> (Value -> IResult a)
-> ByteString
-> Either (JSONPath, String) a
Parser.eitherDecodeWith Parser Value
ParserI.jsonEOF (forall a b. (a -> Parser b) -> a -> IResult b
AI.iparse Value -> Parser a
d)
{-# INLINE eitherDecode #-}
eitherDecode' :: Decoder a -> LB.ByteString -> Either String a
eitherDecode' :: forall a. Decoder a -> ByteString -> Either String a
eitherDecode' (Decoder Value -> Parser a
d) =
forall a. Either (JSONPath, String) a -> Either String a
eitherFormatError forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a.
Parser Value
-> (Value -> IResult a)
-> ByteString
-> Either (JSONPath, String) a
Parser.eitherDecodeWith Parser Value
ParserI.jsonEOF' (forall a b. (a -> Parser b) -> a -> IResult b
AI.iparse Value -> Parser a
d)
{-# INLINE eitherDecode' #-}
decodeStrict :: Decoder a -> B.ByteString -> Maybe a
decodeStrict :: forall a. Decoder a -> ByteString -> Maybe a
decodeStrict (Decoder Value -> Parser a
d) =
forall a.
Parser Value -> (Value -> Result a) -> ByteString -> Maybe a
Parser.decodeStrictWith Parser Value
ParserI.jsonEOF (forall a b. (a -> Parser b) -> a -> Result b
parse Value -> Parser a
d)
{-# INLINE decodeStrict #-}
decodeStrict' :: Decoder a -> B.ByteString -> Maybe a
decodeStrict' :: forall a. Decoder a -> ByteString -> Maybe a
decodeStrict' (Decoder Value -> Parser a
d) =
forall a.
Parser Value -> (Value -> Result a) -> ByteString -> Maybe a
Parser.decodeStrictWith Parser Value
ParserI.jsonEOF' (forall a b. (a -> Parser b) -> a -> Result b
parse Value -> Parser a
d)
{-# INLINE decodeStrict' #-}
eitherDecodeStrict :: Decoder a -> B.ByteString -> Either String a
eitherDecodeStrict :: forall a. Decoder a -> ByteString -> Either String a
eitherDecodeStrict (Decoder Value -> Parser a
d) =
forall a. Either (JSONPath, String) a -> Either String a
eitherFormatError forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a.
Parser Value
-> (Value -> IResult a)
-> ByteString
-> Either (JSONPath, String) a
Parser.eitherDecodeStrictWith Parser Value
ParserI.jsonEOF (forall a b. (a -> Parser b) -> a -> IResult b
AI.iparse Value -> Parser a
d)
{-# INLINE eitherDecodeStrict #-}
eitherDecodeStrict' :: Decoder a -> B.ByteString -> Either String a
eitherDecodeStrict' :: forall a. Decoder a -> ByteString -> Either String a
eitherDecodeStrict' (Decoder Value -> Parser a
d) =
forall a. Either (JSONPath, String) a -> Either String a
eitherFormatError forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a.
Parser Value
-> (Value -> IResult a)
-> ByteString
-> Either (JSONPath, String) a
Parser.eitherDecodeStrictWith Parser Value
ParserI.jsonEOF' (forall a b. (a -> Parser b) -> a -> IResult b
AI.iparse Value -> Parser a
d)
{-# INLINE eitherDecodeStrict' #-}
decodeFileStrict :: Decoder a -> FilePath -> IO (Maybe a)
decodeFileStrict :: forall a. Decoder a -> String -> IO (Maybe a)
decodeFileStrict Decoder a
dec =
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (forall a. Decoder a -> ByteString -> Maybe a
decodeStrict Decoder a
dec) forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> IO ByteString
B.readFile
{-# INLINE decodeFileStrict #-}
decodeFileStrict' :: Decoder a -> FilePath -> IO (Maybe a)
decodeFileStrict' :: forall a. Decoder a -> String -> IO (Maybe a)
decodeFileStrict' Decoder a
dec =
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (forall a. Decoder a -> ByteString -> Maybe a
decodeStrict' Decoder a
dec) forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> IO ByteString
B.readFile
{-# INLINE decodeFileStrict' #-}
eitherDecodeFileStrict :: Decoder a -> FilePath -> IO (Either String a)
eitherDecodeFileStrict :: forall a. Decoder a -> String -> IO (Either String a)
eitherDecodeFileStrict Decoder a
dec =
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (forall a. Decoder a -> ByteString -> Either String a
eitherDecodeStrict Decoder a
dec) forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> IO ByteString
B.readFile
{-# INLINE eitherDecodeFileStrict #-}
eitherDecodeFileStrict' :: Decoder a -> FilePath -> IO (Either String a)
eitherDecodeFileStrict' :: forall a. Decoder a -> String -> IO (Either String a)
eitherDecodeFileStrict' Decoder a
dec =
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (forall a. Decoder a -> ByteString -> Either String a
eitherDecodeStrict' Decoder a
dec) forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> IO ByteString
B.readFile
{-# INLINE eitherDecodeFileStrict' #-}
parseMaybe :: Decoder a -> Value -> Maybe a
parseMaybe :: forall a. Decoder a -> Value -> Maybe a
parseMaybe (Decoder Value -> Parser a
f) = forall a b. (a -> Parser b) -> a -> Maybe b
ATypes.parseMaybe Value -> Parser a
f
{-# INLINE parseMaybe #-}
parseEither :: Decoder a -> Value -> Either String a
parseEither :: forall a. Decoder a -> Value -> Either String a
parseEither (Decoder Value -> Parser a
f) = forall a b. (a -> Parser b) -> a -> Either String b
ATypes.parseEither Value -> Parser a
f
{-# INLINE parseEither #-}
eitherFormatError :: Either (JSONPath, String) a -> Either String a
eitherFormatError :: forall a. Either (JSONPath, String) a -> Either String a
eitherFormatError = forall a c b. (a -> c) -> (b -> c) -> Either a b -> c
Prelude.either (forall a b. a -> Either a b
Left forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b c. (a -> b -> c) -> (a, b) -> c
uncurry JSONPath -> String -> String
AI.formatError) forall a b. b -> Either a b
Right
{-# INLINE eitherFormatError #-}
#if !(MIN_VERSION_aeson(1,4,3))
unexpected :: Value -> Parser a
unexpected actual = Fail.fail $ "unexpected " ++ typeOf actual
{-# INLINE unexpected #-}
typeOf :: Value -> String
typeOf v = case v of
Object _ -> "Object"
Array _ -> "Array"
String _ -> "String"
Number _ -> "Number"
Bool _ -> "Boolean"
Null -> "Null"
{-# INLINE typeOf #-}
#endif