{-# LANGUAGE BangPatterns #-}
{-# LANGUAGE CPP #-}
{-# LANGUAGE NoImplicitPrelude #-}
{-# LANGUAGE OverloadedStrings #-}
#if __GLASGOW_HASKELL__ <= 710 && __GLASGOW_HASKELL__ >= 706
{-# OPTIONS_GHC -fsimpl-tick-factor=300 #-}
#endif
module Data.Aeson.Parser.Internal
(
json, jsonEOF
, jsonWith
, jsonLast
, jsonAccum
, jsonNoDup
, value
, jstring
, jstring_
, scientific
, json', jsonEOF'
, jsonWith'
, jsonLast'
, jsonAccum'
, jsonNoDup'
, value'
, decodeWith
, decodeStrictWith
, eitherDecodeWith
, eitherDecodeStrictWith
, fromListAccum
, parseListNoDup
) where
import Prelude.Compat
import Control.Applicative ((<|>))
import Control.Monad (void, when)
import Data.Aeson.Types.Internal (IResult(..), JSONPath, Object, Result(..), Value(..))
import Data.Attoparsec.ByteString.Char8 (Parser, char, decimal, endOfInput, isDigit_w8, signed, string)
import Data.Function (fix)
import Data.Functor.Compat (($>))
import Data.Scientific (Scientific)
import Data.Text (Text)
import qualified Data.Text.Encoding as TE
import Data.Vector (Vector)
import qualified Data.Vector as Vector (empty, fromList, fromListN, reverse)
import qualified Data.Attoparsec.ByteString as A
import qualified Data.Attoparsec.Lazy as L
import qualified Data.ByteString as B
import qualified Data.ByteString.Unsafe as B
import qualified Data.ByteString.Lazy as L
import qualified Data.ByteString.Lazy as BSL
import qualified Data.ByteString.Lazy.Char8 as C
import qualified Data.ByteString.Builder as B
import qualified Data.HashMap.Strict as H
import qualified Data.Scientific as Sci
import Data.Aeson.Parser.Unescape (unescapeText)
#define BACKSLASH 92
#define CLOSE_CURLY 125
#define CLOSE_SQUARE 93
#define COMMA 44
#define DOUBLE_QUOTE 34
#define OPEN_CURLY 123
#define OPEN_SQUARE 91
#define C_0 48
#define C_9 57
#define C_A 65
#define C_F 70
#define C_a 97
#define C_f 102
#define C_n 110
#define C_t 116
json :: Parser Value
json = value
json' :: Parser Value
json' = value'
object_ :: ([(Text, Value)] -> Either String Object) -> Parser Value -> Parser Value
object_ mkObject val = {-# SCC "object_" #-} Object <$> objectValues mkObject jstring val
{-# INLINE object_ #-}
object_' :: ([(Text, Value)] -> Either String Object) -> Parser Value -> Parser Value
object_' mkObject val' = {-# SCC "object_'" #-} do
!vals <- objectValues mkObject jstring' val'
return (Object vals)
where
jstring' = do
!s <- jstring
return s
{-# INLINE object_' #-}
objectValues :: ([(Text, Value)] -> Either String Object)
-> Parser Text -> Parser Value -> Parser (H.HashMap Text Value)
objectValues mkObject str val = do
skipSpace
w <- A.peekWord8'
if w == CLOSE_CURLY
then A.anyWord8 >> return H.empty
else loop []
where
loop acc = do
k <- (str A.<?> "object key") <* skipSpace <* (char ':' A.<?> "':'")
v <- (val A.<?> "object value") <* skipSpace
ch <- A.satisfy (\w -> w == COMMA || w == CLOSE_CURLY) A.<?> "',' or '}'"
let acc' = (k, v) : acc
if ch == COMMA
then skipSpace >> loop acc'
else case mkObject acc' of
Left err -> fail err
Right obj -> pure obj
{-# INLINE objectValues #-}
array_ :: Parser Value -> Parser Value
array_ val = {-# SCC "array_" #-} Array <$> arrayValues val
{-# INLINE array_ #-}
array_' :: Parser Value -> Parser Value
array_' val = {-# SCC "array_'" #-} do
!vals <- arrayValues val
return (Array vals)
{-# INLINE array_' #-}
arrayValues :: Parser Value -> Parser (Vector Value)
arrayValues val = do
skipSpace
w <- A.peekWord8'
if w == CLOSE_SQUARE
then A.anyWord8 >> return Vector.empty
else loop [] 1
where
loop acc !len = do
v <- (val A.<?> "json list value") <* skipSpace
ch <- A.satisfy (\w -> w == COMMA || w == CLOSE_SQUARE) A.<?> "',' or ']'"
if ch == COMMA
then skipSpace >> loop (v:acc) (len+1)
else return (Vector.reverse (Vector.fromListN len (v:acc)))
{-# INLINE arrayValues #-}
value :: Parser Value
value = jsonWith (pure . H.fromList)
jsonWith :: ([(Text, Value)] -> Either String Object) -> Parser Value
jsonWith mkObject = fix $ \value_ -> do
skipSpace
w <- A.peekWord8'
case w of
DOUBLE_QUOTE -> A.anyWord8 *> (String <$> jstring_)
OPEN_CURLY -> A.anyWord8 *> object_ mkObject value_
OPEN_SQUARE -> A.anyWord8 *> array_ value_
C_f -> string "false" $> Bool False
C_t -> string "true" $> Bool True
C_n -> string "null" $> Null
_ | w >= 48 && w <= 57 || w == 45
-> Number <$> scientific
| otherwise -> fail "not a valid json value"
{-# INLINE jsonWith #-}
jsonLast :: Parser Value
jsonLast = jsonWith (Right . H.fromListWith (const id))
jsonAccum :: Parser Value
jsonAccum = jsonWith (Right . fromListAccum)
jsonNoDup :: Parser Value
jsonNoDup = jsonWith parseListNoDup
fromListAccum :: [(Text, Value)] -> Object
fromListAccum =
fmap (Array . Vector.fromList . ($ [])) . H.fromListWith (.) . (fmap . fmap) (:)
parseListNoDup :: [(Text, Value)] -> Either String Object
parseListNoDup =
H.traverseWithKey unwrap . H.fromListWith (\_ _ -> Nothing) . (fmap . fmap) Just
where
unwrap k Nothing = Left $ "found duplicate key: " ++ show k
unwrap _ (Just v) = Right v
value' :: Parser Value
value' = jsonWith' (pure . H.fromList)
jsonWith' :: ([(Text, Value)] -> Either String Object) -> Parser Value
jsonWith' mkObject = fix $ \value_ -> do
skipSpace
w <- A.peekWord8'
case w of
DOUBLE_QUOTE -> do
!s <- A.anyWord8 *> jstring_
return (String s)
OPEN_CURLY -> A.anyWord8 *> object_' mkObject value_
OPEN_SQUARE -> A.anyWord8 *> array_' value_
C_f -> string "false" $> Bool False
C_t -> string "true" $> Bool True
C_n -> string "null" $> Null
_ | w >= 48 && w <= 57 || w == 45
-> do
!n <- scientific
return (Number n)
| otherwise -> fail "not a valid json value"
{-# INLINE jsonWith' #-}
jsonLast' :: Parser Value
jsonLast' = jsonWith' (pure . H.fromListWith (const id))
jsonAccum' :: Parser Value
jsonAccum' = jsonWith' (pure . fromListAccum)
jsonNoDup' :: Parser Value
jsonNoDup' = jsonWith' parseListNoDup
jstring :: Parser Text
jstring = A.word8 DOUBLE_QUOTE *> jstring_
jstring_ :: Parser Text
{-# INLINE jstring_ #-}
jstring_ = do
s <- A.takeWhile (\w -> w /= DOUBLE_QUOTE && w /= BACKSLASH && w >= 0x20 && w < 0x80)
let txt = TE.decodeUtf8 s
mw <- A.peekWord8
case mw of
Nothing -> fail "string without end"
Just DOUBLE_QUOTE -> A.anyWord8 $> txt
Just w | w < 0x20 -> fail "unescaped control character"
_ -> jstringSlow s
jstringSlow :: B.ByteString -> Parser Text
{-# INLINE jstringSlow #-}
jstringSlow s' = {-# SCC "jstringSlow" #-} do
s <- A.scan startState go <* A.anyWord8
case unescapeText (B.append s' s) of
Right r -> return r
Left err -> fail $ show err
where
startState = False
go a c
| a = Just False
| c == DOUBLE_QUOTE = Nothing
| otherwise = let a' = c == backslash
in Just a'
where backslash = BACKSLASH
decodeWith :: Parser Value -> (Value -> Result a) -> L.ByteString -> Maybe a
decodeWith p to s =
case L.parse p s of
L.Done _ v -> case to v of
Success a -> Just a
_ -> Nothing
_ -> Nothing
{-# INLINE decodeWith #-}
decodeStrictWith :: Parser Value -> (Value -> Result a) -> B.ByteString
-> Maybe a
decodeStrictWith p to s =
case either Error to (A.parseOnly p s) of
Success a -> Just a
_ -> Nothing
{-# INLINE decodeStrictWith #-}
eitherDecodeWith :: Parser Value -> (Value -> IResult a) -> L.ByteString
-> Either (JSONPath, String) a
eitherDecodeWith p to s =
case L.parse p s of
L.Done _ v -> case to v of
ISuccess a -> Right a
IError path msg -> Left (path, msg)
L.Fail notparsed ctx msg -> Left ([], buildMsg notparsed ctx msg)
where
buildMsg :: L.ByteString -> [String] -> String -> String
buildMsg notYetParsed [] msg = msg ++ formatErrorLine notYetParsed
buildMsg notYetParsed (expectation:_) msg =
msg ++ ". Expecting " ++ expectation ++ formatErrorLine notYetParsed
{-# INLINE eitherDecodeWith #-}
formatErrorLine :: L.ByteString -> String
formatErrorLine bs =
C.unpack .
(\bs' ->
if BSL.null bs'
then BSL.empty
else
B.toLazyByteString $
B.stringUtf8 " at '" <> B.lazyByteString bs' <> B.stringUtf8 "'"
) .
BSL.takeWhile (10 /=) .
BSL.filter (`notElem` [9, 13, 32, 34, 47, 92]) .
BSL.take 100 $ bs
eitherDecodeStrictWith :: Parser Value -> (Value -> IResult a) -> B.ByteString
-> Either (JSONPath, String) a
eitherDecodeStrictWith p to s =
case either (IError []) to (A.parseOnly p s) of
ISuccess a -> Right a
IError path msg -> Left (path, msg)
{-# INLINE eitherDecodeStrictWith #-}
jsonEOF :: Parser Value
jsonEOF = json <* skipSpace <* endOfInput
jsonEOF' :: Parser Value
jsonEOF' = json' <* skipSpace <* endOfInput
skipSpace :: Parser ()
skipSpace = A.skipWhile $ \w -> w == 0x20 || w == 0x0a || w == 0x0d || w == 0x09
{-# INLINE skipSpace #-}
data SP = SP !Integer {-# UNPACK #-}!Int
decimal0 :: Parser Integer
decimal0 = do
let zero = 48
digits <- A.takeWhile1 isDigit_w8
if B.length digits > 1 && B.unsafeHead digits == zero
then fail "leading zero"
else return (bsToInteger digits)
scientific :: Parser Scientific
scientific = do
let minus = 45
plus = 43
sign <- A.peekWord8'
let !positive = sign == plus || sign /= minus
when (sign == plus || sign == minus) $
void A.anyWord8
n <- decimal0
let f fracDigits = SP (B.foldl' step n fracDigits)
(negate $ B.length fracDigits)
step a w = a * 10 + fromIntegral (w - 48)
dotty <- A.peekWord8
SP c e <- case dotty of
Just 46 -> A.anyWord8 *> (f <$> A.takeWhile1 isDigit_w8)
_ -> pure (SP n 0)
let !signedCoeff | positive = c
| otherwise = -c
let littleE = 101
bigE = 69
(A.satisfy (\ex -> ex == littleE || ex == bigE) *>
fmap (Sci.scientific signedCoeff . (e +)) (signed decimal)) <|>
return (Sci.scientific signedCoeff e)
{-# INLINE scientific #-}
bsToInteger :: B.ByteString -> Integer
bsToInteger bs
| l > 40 = valInteger 10 l [ fromIntegral (w - 48) | w <- B.unpack bs ]
| otherwise = bsToIntegerSimple bs
where
l = B.length bs
bsToIntegerSimple :: B.ByteString -> Integer
bsToIntegerSimple = B.foldl' step 0 where
step a b = a * 10 + fromIntegral (b - 48)
valInteger :: Integer -> Int -> [Integer] -> Integer
valInteger = go
where
go :: Integer -> Int -> [Integer] -> Integer
go _ _ [] = 0
go _ _ [d] = d
go b l ds
| l > 40 = b' `seq` go b' l' (combine b ds')
| otherwise = valSimple b ds
where
ds' = if even l then ds else 0 : ds
b' = b * b
l' = (l + 1) `quot` 2
combine b (d1 : d2 : ds) = d `seq` (d : combine b ds)
where
d = d1 * b + d2
combine _ [] = []
combine _ [_] = errorWithoutStackTrace "this should not happen"
valSimple :: Integer -> [Integer] -> Integer
valSimple base = go 0
where
go r [] = r
go r (d : ds) = r' `seq` go r' ds
where
r' = r * base + fromIntegral d