{-# OPTIONS_GHC -Wno-orphans #-}
{-# LANGUAGE CPP #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TypeApplications #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE DeriveDataTypeable #-}
{-# LANGUAGE PatternGuards #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE BangPatterns #-}
{-# LANGUAGE DeriveAnyClass #-}
{-# LANGUAGE ViewPatterns #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE FunctionalDependencies #-}
{-# LANGUAGE UndecidableInstances #-}
{-# LANGUAGE InstanceSigs #-}
module Data.Yaml.Internal
(
ParseException(..)
, prettyPrintParseException
, Warning(..)
, parse
, decodeHelper
, decodeHelper_
, decodeAllHelper
, decodeAllHelper_
, textToScientific
, stringScalar
, defaultStringStyle
, isSpecialString
, specialStrings
, isNumeric
, objToStream
, objToEvents
, anyEvent
, missed
) where
#if !MIN_VERSION_base(4,8,0)
import Control.Applicative ((<$>), Applicative(..))
#endif
import Control.Applicative ((<|>))
import Control.Monad.State.Strict
import Control.Monad.Reader
import Data.Aeson
#if MIN_VERSION_aeson(2,0,0)
import qualified Data.Aeson.Key as K
import qualified Data.Aeson.KeyMap as M
import Data.Aeson.KeyMap (KeyMap)
#else
import qualified Data.HashMap.Strict as M
#endif
import Data.Aeson.Internal (formatError)
import Data.Aeson.Types hiding (parse, Parser)
import qualified Data.Attoparsec.Text as Atto
import Data.Bits (shiftL, (.|.))
import Data.ByteString (ByteString)
import qualified Data.ByteString.Builder as BB
import qualified Data.ByteString.Lazy as BL
import Data.ByteString.Builder.Scientific (scientificBuilder)
import Data.Char (toUpper, ord)
import Data.List (foldl', (\\))
import qualified Data.HashSet as HashSet
import Data.Map (Map)
import qualified Data.Map as Map
import Data.Set (Set)
import qualified Data.Set as Set
import Data.Scientific (Scientific, base10Exponent, coefficient)
import Data.Text (Text)
import qualified Data.Text as T
import Data.Text.Encoding (decodeUtf8With, encodeUtf8)
import Data.Text.Encoding.Error (lenientDecode)
import Data.Typeable
import qualified Data.Vector as V
import qualified Text.Libyaml as Y
import Text.Libyaml hiding (encode, decode, encodeFile, decodeFile)
import Control.Exception.Safe
import Streamly.Prelude (SerialT)
import Streamly.Internal.Data.Parser (Parser)
import qualified Streamly.Internal.Data.Parser as Parser
import qualified Streamly.Internal.Data.Stream.IsStream.Eliminate as Stream
import qualified Streamly.Internal.Data.Stream.StreamK as K
import Streamly.Internal.Data.Parser.ParserK.Type (fromParserK, toParserK, fromEffect)
import qualified Streamly.Internal.Data.Parser.ParserD.Type as ParserD
#if MIN_VERSION_aeson(2,0,0)
fromText :: T.Text -> K.Key
fromText :: Text -> Key
fromText = Text -> Key
K.fromText
toText :: K.Key -> T.Text
toText :: Key -> Text
toText = Key -> Text
K.toText
#else
fromText :: T.Text -> T.Text
fromText = id
toText :: Key -> T.Text
toText = id
type KeyMap a = M.HashMap Text a
type Key = Text
#endif
data ParseException = NonScalarKey
| UnknownAlias { ParseException -> AnchorName
_anchorName :: Y.AnchorName }
| UnexpectedEvent { ParseException -> Maybe Event
_received :: Maybe Event
, ParseException -> Maybe Event
_expected :: Maybe Event
}
| InvalidYaml (Maybe YamlException)
| MultipleDocuments
| AesonException String
| OtherParseException SomeException
| NonStringKey JSONPath
| NonStringKeyAlias Y.AnchorName Value
| CyclicIncludes
| LoadSettingsException FilePath ParseException
deriving (Int -> ParseException -> ShowS
[ParseException] -> ShowS
ParseException -> AnchorName
(Int -> ParseException -> ShowS)
-> (ParseException -> AnchorName)
-> ([ParseException] -> ShowS)
-> Show ParseException
forall a.
(Int -> a -> ShowS)
-> (a -> AnchorName) -> ([a] -> ShowS) -> Show a
showList :: [ParseException] -> ShowS
$cshowList :: [ParseException] -> ShowS
show :: ParseException -> AnchorName
$cshow :: ParseException -> AnchorName
showsPrec :: Int -> ParseException -> ShowS
$cshowsPrec :: Int -> ParseException -> ShowS
Show, Typeable)
instance Exception ParseException where
#if MIN_VERSION_base(4, 8, 0)
displayException :: ParseException -> AnchorName
displayException = ParseException -> AnchorName
prettyPrintParseException
#endif
prettyPrintParseException :: ParseException -> String
prettyPrintParseException :: ParseException -> AnchorName
prettyPrintParseException ParseException
pe = case ParseException
pe of
ParseException
NonScalarKey -> AnchorName
"Non scalar key"
UnknownAlias AnchorName
anchor -> AnchorName
"Unknown alias `" AnchorName -> ShowS
forall a. [a] -> [a] -> [a]
++ AnchorName
anchor AnchorName -> ShowS
forall a. [a] -> [a] -> [a]
++ AnchorName
"`"
UnexpectedEvent { _expected :: ParseException -> Maybe Event
_expected = Maybe Event
mbExpected, _received :: ParseException -> Maybe Event
_received = Maybe Event
mbUnexpected } -> [AnchorName] -> AnchorName
unlines
[ AnchorName
"Unexpected event: expected"
, AnchorName
" " AnchorName -> ShowS
forall a. [a] -> [a] -> [a]
++ Maybe Event -> AnchorName
forall a. Show a => a -> AnchorName
show Maybe Event
mbExpected
, AnchorName
"but received"
, AnchorName
" " AnchorName -> ShowS
forall a. [a] -> [a] -> [a]
++ Maybe Event -> AnchorName
forall a. Show a => a -> AnchorName
show Maybe Event
mbUnexpected
]
InvalidYaml Maybe YamlException
mbYamlError -> case Maybe YamlException
mbYamlError of
Maybe YamlException
Nothing -> AnchorName
"Unspecified YAML error"
Just YamlException
yamlError -> case YamlException
yamlError of
YamlException AnchorName
s -> AnchorName
"YAML exception:\n" AnchorName -> ShowS
forall a. [a] -> [a] -> [a]
++ AnchorName
s
YamlParseException AnchorName
problem AnchorName
context YamlMark
mark -> [AnchorName] -> AnchorName
forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat
[ AnchorName
"YAML parse exception at line " AnchorName -> ShowS
forall a. [a] -> [a] -> [a]
++ Int -> AnchorName
forall a. Show a => a -> AnchorName
show (YamlMark -> Int
yamlLine YamlMark
mark) AnchorName -> ShowS
forall a. [a] -> [a] -> [a]
++
AnchorName
", column " AnchorName -> ShowS
forall a. [a] -> [a] -> [a]
++ Int -> AnchorName
forall a. Show a => a -> AnchorName
show (YamlMark -> Int
yamlColumn YamlMark
mark)
, case AnchorName
context of
AnchorName
"" -> AnchorName
":\n"
AnchorName
_ -> AnchorName
",\n" AnchorName -> ShowS
forall a. [a] -> [a] -> [a]
++ AnchorName
context AnchorName -> ShowS
forall a. [a] -> [a] -> [a]
++ AnchorName
":\n"
, AnchorName
problem
]
ParseException
MultipleDocuments -> AnchorName
"Multiple YAML documents encountered"
AesonException AnchorName
s -> AnchorName
"Aeson exception:\n" AnchorName -> ShowS
forall a. [a] -> [a] -> [a]
++ AnchorName
s
OtherParseException SomeException
exc -> AnchorName
"Generic parse exception:\n" AnchorName -> ShowS
forall a. [a] -> [a] -> [a]
++ SomeException -> AnchorName
forall a. Show a => a -> AnchorName
show SomeException
exc
NonStringKey JSONPath
path -> JSONPath -> ShowS
formatError JSONPath
path AnchorName
"Non-string keys are not supported"
NonStringKeyAlias AnchorName
anchor Value
value -> [AnchorName] -> AnchorName
unlines
[ AnchorName
"Non-string key alias:"
, AnchorName
" Anchor name: " AnchorName -> ShowS
forall a. [a] -> [a] -> [a]
++ AnchorName
anchor
, AnchorName
" Value: " AnchorName -> ShowS
forall a. [a] -> [a] -> [a]
++ Value -> AnchorName
forall a. Show a => a -> AnchorName
show Value
value
]
ParseException
CyclicIncludes -> AnchorName
"Cyclic includes"
LoadSettingsException AnchorName
fp ParseException
exc -> AnchorName
"Could not parse file as YAML: " AnchorName -> ShowS
forall a. [a] -> [a] -> [a]
++ AnchorName
fp AnchorName -> ShowS
forall a. [a] -> [a] -> [a]
++ AnchorName
"\n" AnchorName -> ShowS
forall a. [a] -> [a] -> [a]
++ ParseException -> AnchorName
prettyPrintParseException ParseException
exc
defineAnchor :: Value -> String -> Parser (ReaderT JSONPath Parse) Event ()
defineAnchor :: Value -> AnchorName -> Parser (ReaderT JSONPath Parse) Event ()
defineAnchor Value
value AnchorName
name = (ParseState -> ParseState)
-> Parser (ReaderT JSONPath Parse) Event ()
forall s (m :: * -> *). MonadState s m => (s -> s) -> m ()
modify ((Map AnchorName Value -> Map AnchorName Value)
-> ParseState -> ParseState
modifyAnchors ((Map AnchorName Value -> Map AnchorName Value)
-> ParseState -> ParseState)
-> (Map AnchorName Value -> Map AnchorName Value)
-> ParseState
-> ParseState
forall a b. (a -> b) -> a -> b
$ AnchorName -> Value -> Map AnchorName Value -> Map AnchorName Value
forall k a. Ord k => k -> a -> Map k a -> Map k a
Map.insert AnchorName
name Value
value)
where
modifyAnchors :: (Map String Value -> Map String Value) -> ParseState -> ParseState
modifyAnchors :: (Map AnchorName Value -> Map AnchorName Value)
-> ParseState -> ParseState
modifyAnchors Map AnchorName Value -> Map AnchorName Value
f ParseState
st = ParseState
st {parseStateAnchors :: Map AnchorName Value
parseStateAnchors = Map AnchorName Value -> Map AnchorName Value
f (ParseState -> Map AnchorName Value
parseStateAnchors ParseState
st)}
lookupAnchor :: String -> Parser (ReaderT JSONPath Parse) Event (Maybe Value)
lookupAnchor :: AnchorName -> Parser (ReaderT JSONPath Parse) Event (Maybe Value)
lookupAnchor AnchorName
name = (ParseState -> Maybe Value)
-> Parser (ReaderT JSONPath Parse) Event (Maybe Value)
forall s (m :: * -> *) a. MonadState s m => (s -> a) -> m a
gets (AnchorName -> Map AnchorName Value -> Maybe Value
forall k a. Ord k => k -> Map k a -> Maybe a
Map.lookup AnchorName
name (Map AnchorName Value -> Maybe Value)
-> (ParseState -> Map AnchorName Value)
-> ParseState
-> Maybe Value
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ParseState -> Map AnchorName Value
parseStateAnchors)
data Warning = DuplicateKey !JSONPath
deriving (Warning -> Warning -> Bool
(Warning -> Warning -> Bool)
-> (Warning -> Warning -> Bool) -> Eq Warning
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Warning -> Warning -> Bool
$c/= :: Warning -> Warning -> Bool
== :: Warning -> Warning -> Bool
$c== :: Warning -> Warning -> Bool
Eq, Int -> Warning -> ShowS
[Warning] -> ShowS
Warning -> AnchorName
(Int -> Warning -> ShowS)
-> (Warning -> AnchorName) -> ([Warning] -> ShowS) -> Show Warning
forall a.
(Int -> a -> ShowS)
-> (a -> AnchorName) -> ([a] -> ShowS) -> Show a
showList :: [Warning] -> ShowS
$cshowList :: [Warning] -> ShowS
show :: Warning -> AnchorName
$cshow :: Warning -> AnchorName
showsPrec :: Int -> Warning -> ShowS
$cshowsPrec :: Int -> Warning -> ShowS
Show)
addWarning :: Warning -> Parser (ReaderT JSONPath Parse) Event ()
addWarning :: Warning -> Parser (ReaderT JSONPath Parse) Event ()
addWarning Warning
w = (ParseState -> ParseState)
-> Parser (ReaderT JSONPath Parse) Event ()
forall s (m :: * -> *). MonadState s m => (s -> s) -> m ()
modify (([Warning] -> [Warning]) -> ParseState -> ParseState
modifyWarnings (Warning
w Warning -> [Warning] -> [Warning]
forall a. a -> [a] -> [a]
:))
where
modifyWarnings :: ([Warning] -> [Warning]) -> ParseState -> ParseState
modifyWarnings :: ([Warning] -> [Warning]) -> ParseState -> ParseState
modifyWarnings [Warning] -> [Warning]
f ParseState
st = ParseState
st {parseStateWarnings :: [Warning]
parseStateWarnings = [Warning] -> [Warning]
f (ParseState -> [Warning]
parseStateWarnings ParseState
st)}
data ParseState = ParseState {
ParseState -> Map AnchorName Value
parseStateAnchors :: Map String Value
, ParseState -> [Warning]
parseStateWarnings :: [Warning]
}
type Parse = StateT ParseState IO
requireEvent :: Event -> Parser (ReaderT JSONPath Parse) Event ()
requireEvent :: Event -> Parser (ReaderT JSONPath Parse) Event ()
requireEvent Event
e = do
Maybe Event
f <- Parser (ReaderT JSONPath Parse) Event (Maybe Event)
forall (m :: * -> *) a. MonadCatch m => Parser m a (Maybe a)
anyEvent
Bool
-> Parser (ReaderT JSONPath Parse) Event ()
-> Parser (ReaderT JSONPath Parse) Event ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless (Maybe Event
f Maybe Event -> Maybe Event -> Bool
forall a. Eq a => a -> a -> Bool
== Event -> Maybe Event
forall a. a -> Maybe a
Just Event
e) (Parser (ReaderT JSONPath Parse) Event ()
-> Parser (ReaderT JSONPath Parse) Event ())
-> Parser (ReaderT JSONPath Parse) Event ()
-> Parser (ReaderT JSONPath Parse) Event ()
forall a b. (a -> b) -> a -> b
$ Maybe Event -> Parser (ReaderT JSONPath Parse) Event ()
forall (m :: * -> *) a b.
(MonadIO m, MonadThrow m) =>
Maybe Event -> Parser m a b
missed (Event -> Maybe Event
forall a. a -> Maybe a
Just Event
e)
{-# INLINE anyEvent #-}
anyEvent :: MonadCatch m => Parser m a (Maybe a)
anyEvent :: Parser m a (Maybe a)
anyEvent = Parser m a (Maybe a) -> Parser m a (Maybe a)
forall (m :: * -> *) a b.
MonadCatch m =>
Parser m a b -> Parser m a b
toParserK (Parser m a (Maybe a) -> Parser m a (Maybe a))
-> Parser m a (Maybe a) -> Parser m a (Maybe a)
forall a b. (a -> b) -> a -> b
$ (() -> a -> m (Step () (Maybe a)))
-> m (Initial () (Maybe a))
-> (() -> m (Maybe a))
-> Parser m a (Maybe a)
forall (m :: * -> *) a b s.
(s -> a -> m (Step s b))
-> m (Initial s b) -> (s -> m b) -> Parser m a b
ParserD.Parser () -> a -> m (Step () (Maybe a))
forall (f :: * -> *) p a s.
Applicative f =>
p -> a -> f (Step s (Maybe a))
step m (Initial () (Maybe a))
forall b. m (Initial () b)
initial () -> m (Maybe a)
forall (f :: * -> *) p a. Applicative f => p -> f (Maybe a)
extract
where
initial :: m (Initial () b)
initial = Initial () b -> m (Initial () b)
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Initial () b -> m (Initial () b))
-> Initial () b -> m (Initial () b)
forall a b. (a -> b) -> a -> b
$ () -> Initial () b
forall s b. s -> Initial s b
ParserD.IPartial ()
step :: p -> a -> f (Step s (Maybe a))
step p
_ a
a = Step s (Maybe a) -> f (Step s (Maybe a))
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Step s (Maybe a) -> f (Step s (Maybe a)))
-> Step s (Maybe a) -> f (Step s (Maybe a))
forall a b. (a -> b) -> a -> b
$ Int -> Maybe a -> Step s (Maybe a)
forall s b. Int -> b -> Step s b
ParserD.Done Int
0 (a -> Maybe a
forall a. a -> Maybe a
Just a
a)
extract :: p -> f (Maybe a)
extract p
_ = Maybe a -> f (Maybe a)
forall (f :: * -> *) a. Applicative f => a -> f a
pure Maybe a
forall a. Maybe a
Nothing
parse :: Parser (ReaderT JSONPath Parse) Event Value
parse :: Parser (ReaderT JSONPath Parse) Event Value
parse = do
[Value]
docs <- Parser (ReaderT JSONPath Parse) Event [Value]
parseAll
case [Value]
docs of
[] -> Value -> Parser (ReaderT JSONPath Parse) Event Value
forall (m :: * -> *) a. Monad m => a -> m a
return Value
Null
[Value
doc] -> Value -> Parser (ReaderT JSONPath Parse) Event Value
forall (m :: * -> *) a. Monad m => a -> m a
return Value
doc
[Value]
_ -> IO Value -> Parser (ReaderT JSONPath Parse) Event Value
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Value -> Parser (ReaderT JSONPath Parse) Event Value)
-> IO Value -> Parser (ReaderT JSONPath Parse) Event Value
forall a b. (a -> b) -> a -> b
$ ParseException -> IO Value
forall (m :: * -> *) e a. (MonadThrow m, Exception e) => e -> m a
throwIO ParseException
MultipleDocuments
parseAll :: Parser (ReaderT JSONPath Parse) Event [Value]
parseAll :: Parser (ReaderT JSONPath Parse) Event [Value]
parseAll = do
Maybe Event
e <- Parser (ReaderT JSONPath Parse) Event (Maybe Event)
forall (m :: * -> *) a. MonadCatch m => Parser m a (Maybe a)
anyEvent
case Maybe Event
e of
Maybe Event
Nothing -> [Value] -> Parser (ReaderT JSONPath Parse) Event [Value]
forall (m :: * -> *) a. Monad m => a -> m a
return []
Just Event
EventStreamStart ->
Parser (ReaderT JSONPath Parse) Event [Value]
parseDocs
Maybe Event
_ -> Maybe Event -> Parser (ReaderT JSONPath Parse) Event [Value]
forall (m :: * -> *) a b.
(MonadIO m, MonadThrow m) =>
Maybe Event -> Parser m a b
missed Maybe Event
e
parseDocs :: Parser (ReaderT JSONPath Parse) Event [Value]
parseDocs :: Parser (ReaderT JSONPath Parse) Event [Value]
parseDocs = do
Maybe Event
e <- Parser (ReaderT JSONPath Parse) Event (Maybe Event)
forall (m :: * -> *) a. MonadCatch m => Parser m a (Maybe a)
anyEvent
case Maybe Event
e of
Just Event
EventStreamEnd -> [Value] -> Parser (ReaderT JSONPath Parse) Event [Value]
forall (m :: * -> *) a. Monad m => a -> m a
return []
Just Event
EventDocumentStart -> do
Value
res <- Parser (ReaderT JSONPath Parse) Event Value
parseO
Event -> Parser (ReaderT JSONPath Parse) Event ()
requireEvent Event
EventDocumentEnd
(Value
res Value -> [Value] -> [Value]
forall a. a -> [a] -> [a]
:) ([Value] -> [Value])
-> Parser (ReaderT JSONPath Parse) Event [Value]
-> Parser (ReaderT JSONPath Parse) Event [Value]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Parser (ReaderT JSONPath Parse) Event [Value]
parseDocs
Maybe Event
_ -> Maybe Event -> Parser (ReaderT JSONPath Parse) Event [Value]
forall (m :: * -> *) a b.
(MonadIO m, MonadThrow m) =>
Maybe Event -> Parser m a b
missed Maybe Event
e
missed :: (MonadIO m, MonadThrow m) => Maybe Event -> Parser m a b
missed :: Maybe Event -> Parser m a b
missed Maybe Event
event = IO b -> Parser m a b
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO b -> Parser m a b) -> IO b -> Parser m a b
forall a b. (a -> b) -> a -> b
$ ParseException -> IO b
forall (m :: * -> *) e a. (MonadThrow m, Exception e) => e -> m a
throwIO (ParseException -> IO b) -> ParseException -> IO b
forall a b. (a -> b) -> a -> b
$ Maybe Event -> Maybe Event -> ParseException
UnexpectedEvent Maybe Event
event Maybe Event
forall a. Maybe a
Nothing
parseScalar :: ByteString -> Anchor -> Style -> Tag
-> Parser (ReaderT JSONPath Parse) Event Text
parseScalar :: ByteString
-> Anchor
-> Style
-> Tag
-> Parser (ReaderT JSONPath Parse) Event Text
parseScalar ByteString
v Anchor
a Style
style Tag
tag = do
let res :: Text
res = OnDecodeError -> ByteString -> Text
decodeUtf8With OnDecodeError
lenientDecode ByteString
v
(AnchorName -> Parser (ReaderT JSONPath Parse) Event ())
-> Anchor -> Parser (ReaderT JSONPath Parse) Event ()
forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
(a -> m b) -> t a -> m ()
mapM_ (Value -> AnchorName -> Parser (ReaderT JSONPath Parse) Event ()
defineAnchor (Style -> Tag -> Text -> Value
textToValue Style
style Tag
tag Text
res)) Anchor
a
Text -> Parser (ReaderT JSONPath Parse) Event Text
forall (m :: * -> *) a. Monad m => a -> m a
return Text
res
textToValue :: Style -> Tag -> Text -> Value
textToValue :: Style -> Tag -> Text -> Value
textToValue Style
SingleQuoted Tag
_ Text
t = Text -> Value
String Text
t
textToValue Style
DoubleQuoted Tag
_ Text
t = Text -> Value
String Text
t
textToValue Style
_ Tag
StrTag Text
t = Text -> Value
String Text
t
textToValue Style
Folded Tag
_ Text
t = Text -> Value
String Text
t
textToValue Style
_ Tag
_ Text
t
| Text
t Text -> [Text] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` [Text
"null", Text
"Null", Text
"NULL", Text
"~", Text
""] = Value
Null
| (Text -> Bool) -> [Text] -> Bool
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
any (Text
t Text -> Text -> Bool
`isLike`) [Text
"y", Text
"yes", Text
"on", Text
"true"] = Bool -> Value
Bool Bool
True
| (Text -> Bool) -> [Text] -> Bool
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
any (Text
t Text -> Text -> Bool
`isLike`) [Text
"n", Text
"no", Text
"off", Text
"false"] = Bool -> Value
Bool Bool
False
| Right Scientific
x <- Text -> Either AnchorName Scientific
textToScientific Text
t = Scientific -> Value
Number Scientific
x
| Bool
otherwise = Text -> Value
String Text
t
where Text
x isLike :: Text -> Text -> Bool
`isLike` Text
ref = Text
x Text -> [Text] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` [Text
ref, Text -> Text
T.toUpper Text
ref, Text
titleCased]
where titleCased :: Text
titleCased = Char -> Char
toUpper (Text -> Char
T.head Text
ref) Char -> Text -> Text
`T.cons` Text -> Text
T.tail Text
ref
textToScientific :: Text -> Either String Scientific
textToScientific :: Text -> Either AnchorName Scientific
textToScientific = Parser Scientific -> Text -> Either AnchorName Scientific
forall a. Parser a -> Text -> Either AnchorName a
Atto.parseOnly (Parser Scientific
num Parser Scientific -> Parser Text () -> Parser Scientific
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* Parser Text ()
forall t. Chunk t => Parser t ()
Atto.endOfInput)
where
num :: Parser Scientific
num = (Integer -> Scientific
forall a. Num a => Integer -> a
fromInteger (Integer -> Scientific) -> Parser Text Integer -> Parser Scientific
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (Parser Text Text
"0x" Parser Text Text -> Parser Text Integer -> Parser Text Integer
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> Parser Text Integer
forall a. (Integral a, Bits a) => Parser a
Atto.hexadecimal))
Parser Scientific -> Parser Scientific -> Parser Scientific
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> (Integer -> Scientific
forall a. Num a => Integer -> a
fromInteger (Integer -> Scientific) -> Parser Text Integer -> Parser Scientific
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (Parser Text Text
"0o" Parser Text Text -> Parser Text Integer -> Parser Text Integer
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> Parser Text Integer
octal))
Parser Scientific -> Parser Scientific -> Parser Scientific
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> Parser Scientific
Atto.scientific
octal :: Parser Text Integer
octal = (Integer -> Char -> Integer) -> Integer -> Text -> Integer
forall a. (a -> Char -> a) -> a -> Text -> a
T.foldl' Integer -> Char -> Integer
forall a. (Bits a, Num a) => a -> Char -> a
step Integer
0 (Text -> Integer) -> Parser Text Text -> Parser Text Integer
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (Char -> Bool) -> Parser Text Text
Atto.takeWhile1 Char -> Bool
isOctalDigit
where
isOctalDigit :: Char -> Bool
isOctalDigit Char
c = (Char
c Char -> Char -> Bool
forall a. Ord a => a -> a -> Bool
>= Char
'0' Bool -> Bool -> Bool
&& Char
c Char -> Char -> Bool
forall a. Ord a => a -> a -> Bool
<= Char
'7')
step :: a -> Char -> a
step a
a Char
c = (a
a a -> Int -> a
forall a. Bits a => a -> Int -> a
`shiftL` Int
3) a -> a -> a
forall a. Bits a => a -> a -> a
.|. Int -> a
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Char -> Int
ord Char
c Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
48)
parseO :: Parser (ReaderT JSONPath Parse) Event Value
parseO :: Parser (ReaderT JSONPath Parse) Event Value
parseO = do
Maybe Event
me <- Parser (ReaderT JSONPath Parse) Event (Maybe Event)
forall (m :: * -> *) a. MonadCatch m => Parser m a (Maybe a)
anyEvent
case Maybe Event
me of
Just (EventScalar ByteString
v Tag
tag Style
style Anchor
a) -> Style -> Tag -> Text -> Value
textToValue Style
style Tag
tag (Text -> Value)
-> Parser (ReaderT JSONPath Parse) Event Text
-> Parser (ReaderT JSONPath Parse) Event Value
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ByteString
-> Anchor
-> Style
-> Tag
-> Parser (ReaderT JSONPath Parse) Event Text
parseScalar ByteString
v Anchor
a Style
style Tag
tag
Just (EventSequenceStart Tag
_ SequenceStyle
_ Anchor
a) -> Int
-> Anchor
-> ([Value] -> [Value])
-> Parser (ReaderT JSONPath Parse) Event Value
parseS Int
0 Anchor
a [Value] -> [Value]
forall a. a -> a
id
Just (EventMappingStart Tag
_ MappingStyle
_ Anchor
a) -> Set Key
-> Anchor
-> KeyMap Value
-> Parser (ReaderT JSONPath Parse) Event Value
parseM Set Key
forall a. Monoid a => a
mempty Anchor
a KeyMap Value
forall v. KeyMap v
M.empty
Just (EventAlias AnchorName
an) -> do
Maybe Value
m <- AnchorName -> Parser (ReaderT JSONPath Parse) Event (Maybe Value)
lookupAnchor AnchorName
an
case Maybe Value
m of
Maybe Value
Nothing -> IO Value -> Parser (ReaderT JSONPath Parse) Event Value
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Value -> Parser (ReaderT JSONPath Parse) Event Value)
-> IO Value -> Parser (ReaderT JSONPath Parse) Event Value
forall a b. (a -> b) -> a -> b
$ ParseException -> IO Value
forall (m :: * -> *) e a. (MonadThrow m, Exception e) => e -> m a
throwIO (ParseException -> IO Value) -> ParseException -> IO Value
forall a b. (a -> b) -> a -> b
$ AnchorName -> ParseException
UnknownAlias AnchorName
an
Just Value
v -> Value -> Parser (ReaderT JSONPath Parse) Event Value
forall (m :: * -> *) a. Monad m => a -> m a
return Value
v
Maybe Event
_ -> Maybe Event -> Parser (ReaderT JSONPath Parse) Event Value
forall (m :: * -> *) a b.
(MonadIO m, MonadThrow m) =>
Maybe Event -> Parser m a b
missed Maybe Event
me
parseS :: Int
-> Y.Anchor
-> ([Value] -> [Value])
-> Parser (ReaderT JSONPath Parse) Event Value
parseS :: Int
-> Anchor
-> ([Value] -> [Value])
-> Parser (ReaderT JSONPath Parse) Event Value
parseS !Int
n Anchor
a [Value] -> [Value]
front = do
Maybe Event
me <- Parser (ReaderT JSONPath Parse) Event (Maybe Event)
-> Parser (ReaderT JSONPath Parse) Event (Maybe Event)
forall (m :: * -> *) a b.
MonadCatch m =>
Parser m a b -> Parser m a b
Parser.lookAhead Parser (ReaderT JSONPath Parse) Event (Maybe Event)
forall (m :: * -> *) a. MonadCatch m => Parser m a (Maybe a)
anyEvent
case Maybe Event
me of
Just Event
EventSequenceEnd -> do
Parser (ReaderT JSONPath Parse) Event (Maybe Event)
-> Parser (ReaderT JSONPath Parse) Event ()
forall (f :: * -> *) a. Functor f => f a -> f ()
void Parser (ReaderT JSONPath Parse) Event (Maybe Event)
forall (m :: * -> *) a. MonadCatch m => Parser m a (Maybe a)
anyEvent
let res :: Value
res = Array -> Value
Array (Array -> Value) -> Array -> Value
forall a b. (a -> b) -> a -> b
$ [Value] -> Array
forall a. [a] -> Vector a
V.fromList ([Value] -> Array) -> [Value] -> Array
forall a b. (a -> b) -> a -> b
$ [Value] -> [Value]
front []
(AnchorName -> Parser (ReaderT JSONPath Parse) Event ())
-> Anchor -> Parser (ReaderT JSONPath Parse) Event ()
forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
(a -> m b) -> t a -> m ()
mapM_ (Value -> AnchorName -> Parser (ReaderT JSONPath Parse) Event ()
defineAnchor Value
res) Anchor
a
Value -> Parser (ReaderT JSONPath Parse) Event Value
forall (m :: * -> *) a. Monad m => a -> m a
return Value
res
Maybe Event
_ -> do
Value
o <- (JSONPath -> JSONPath)
-> Parser (ReaderT JSONPath Parse) Event Value
-> Parser (ReaderT JSONPath Parse) Event Value
forall r (m :: * -> *) a. MonadReader r m => (r -> r) -> m a -> m a
local (Int -> JSONPathElement
Index Int
n JSONPathElement -> JSONPath -> JSONPath
forall a. a -> [a] -> [a]
:) Parser (ReaderT JSONPath Parse) Event Value
parseO
Int
-> Anchor
-> ([Value] -> [Value])
-> Parser (ReaderT JSONPath Parse) Event Value
parseS (Int -> Int
forall a. Enum a => a -> a
succ Int
n) Anchor
a (([Value] -> [Value])
-> Parser (ReaderT JSONPath Parse) Event Value)
-> ([Value] -> [Value])
-> Parser (ReaderT JSONPath Parse) Event Value
forall a b. (a -> b) -> a -> b
$ [Value] -> [Value]
front ([Value] -> [Value]) -> ([Value] -> [Value]) -> [Value] -> [Value]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (:) Value
o
parseM :: Set Key
-> Y.Anchor
-> KeyMap Value
-> Parser (ReaderT JSONPath Parse) Event Value
parseM :: Set Key
-> Anchor
-> KeyMap Value
-> Parser (ReaderT JSONPath Parse) Event Value
parseM Set Key
mergedKeys Anchor
a KeyMap Value
front = do
Maybe Event
me <- Parser (ReaderT JSONPath Parse) Event (Maybe Event)
forall (m :: * -> *) a. MonadCatch m => Parser m a (Maybe a)
anyEvent
case Maybe Event
me of
Just Event
EventMappingEnd -> do
let res :: Value
res = KeyMap Value -> Value
Object KeyMap Value
front
(AnchorName -> Parser (ReaderT JSONPath Parse) Event ())
-> Anchor -> Parser (ReaderT JSONPath Parse) Event ()
forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
(a -> m b) -> t a -> m ()
mapM_ (Value -> AnchorName -> Parser (ReaderT JSONPath Parse) Event ()
defineAnchor Value
res) Anchor
a
Value -> Parser (ReaderT JSONPath Parse) Event Value
forall (m :: * -> *) a. Monad m => a -> m a
return Value
res
Maybe Event
_ -> do
Key
s <- case Maybe Event
me of
Just (EventScalar ByteString
v Tag
tag Style
style Anchor
a') -> Text -> Key
fromText (Text -> Key)
-> Parser (ReaderT JSONPath Parse) Event Text
-> Parser (ReaderT JSONPath Parse) Event Key
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ByteString
-> Anchor
-> Style
-> Tag
-> Parser (ReaderT JSONPath Parse) Event Text
parseScalar ByteString
v Anchor
a' Style
style Tag
tag
Just (EventAlias AnchorName
an) -> do
Maybe Value
m <- AnchorName -> Parser (ReaderT JSONPath Parse) Event (Maybe Value)
lookupAnchor AnchorName
an
case Maybe Value
m of
Maybe Value
Nothing -> IO Key -> Parser (ReaderT JSONPath Parse) Event Key
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Key -> Parser (ReaderT JSONPath Parse) Event Key)
-> IO Key -> Parser (ReaderT JSONPath Parse) Event Key
forall a b. (a -> b) -> a -> b
$ ParseException -> IO Key
forall (m :: * -> *) e a. (MonadThrow m, Exception e) => e -> m a
throwIO (ParseException -> IO Key) -> ParseException -> IO Key
forall a b. (a -> b) -> a -> b
$ AnchorName -> ParseException
UnknownAlias AnchorName
an
Just (String Text
t) -> Key -> Parser (ReaderT JSONPath Parse) Event Key
forall (m :: * -> *) a. Monad m => a -> m a
return (Key -> Parser (ReaderT JSONPath Parse) Event Key)
-> Key -> Parser (ReaderT JSONPath Parse) Event Key
forall a b. (a -> b) -> a -> b
$ Text -> Key
fromText Text
t
Just Value
v -> IO Key -> Parser (ReaderT JSONPath Parse) Event Key
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Key -> Parser (ReaderT JSONPath Parse) Event Key)
-> IO Key -> Parser (ReaderT JSONPath Parse) Event Key
forall a b. (a -> b) -> a -> b
$ ParseException -> IO Key
forall (m :: * -> *) e a. (MonadThrow m, Exception e) => e -> m a
throwIO (ParseException -> IO Key) -> ParseException -> IO Key
forall a b. (a -> b) -> a -> b
$ AnchorName -> Value -> ParseException
NonStringKeyAlias AnchorName
an Value
v
Maybe Event
_ -> do
JSONPath
path <- Parser (ReaderT JSONPath Parse) Event JSONPath
forall r (m :: * -> *). MonadReader r m => m r
ask
IO Key -> Parser (ReaderT JSONPath Parse) Event Key
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Key -> Parser (ReaderT JSONPath Parse) Event Key)
-> IO Key -> Parser (ReaderT JSONPath Parse) Event Key
forall a b. (a -> b) -> a -> b
$ ParseException -> IO Key
forall (m :: * -> *) e a. (MonadThrow m, Exception e) => e -> m a
throwIO (ParseException -> IO Key) -> ParseException -> IO Key
forall a b. (a -> b) -> a -> b
$ JSONPath -> ParseException
NonStringKey JSONPath
path
(Set Key
mergedKeys', KeyMap Value
al') <- (JSONPath -> JSONPath)
-> Parser (ReaderT JSONPath Parse) Event (Set Key, KeyMap Value)
-> Parser (ReaderT JSONPath Parse) Event (Set Key, KeyMap Value)
forall r (m :: * -> *) a. MonadReader r m => (r -> r) -> m a -> m a
local (Key -> JSONPathElement
Key Key
s JSONPathElement -> JSONPath -> JSONPath
forall a. a -> [a] -> [a]
:) (Parser (ReaderT JSONPath Parse) Event (Set Key, KeyMap Value)
-> Parser (ReaderT JSONPath Parse) Event (Set Key, KeyMap Value))
-> Parser (ReaderT JSONPath Parse) Event (Set Key, KeyMap Value)
-> Parser (ReaderT JSONPath Parse) Event (Set Key, KeyMap Value)
forall a b. (a -> b) -> a -> b
$ do
Value
o <- Parser (ReaderT JSONPath Parse) Event Value
parseO
let al :: Parser (ReaderT JSONPath Parse) Event (Set Key, KeyMap Value)
al = do
Bool
-> Parser (ReaderT JSONPath Parse) Event ()
-> Parser (ReaderT JSONPath Parse) Event ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (Key -> KeyMap Value -> Bool
forall a. Key -> KeyMap a -> Bool
M.member Key
s KeyMap Value
front Bool -> Bool -> Bool
&& Key -> Set Key -> Bool
forall a. Ord a => a -> Set a -> Bool
Set.notMember Key
s Set Key
mergedKeys) (Parser (ReaderT JSONPath Parse) Event ()
-> Parser (ReaderT JSONPath Parse) Event ())
-> Parser (ReaderT JSONPath Parse) Event ()
-> Parser (ReaderT JSONPath Parse) Event ()
forall a b. (a -> b) -> a -> b
$ do
JSONPath
path <- JSONPath -> JSONPath
forall a. [a] -> [a]
reverse (JSONPath -> JSONPath)
-> Parser (ReaderT JSONPath Parse) Event JSONPath
-> Parser (ReaderT JSONPath Parse) Event JSONPath
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Parser (ReaderT JSONPath Parse) Event JSONPath
forall r (m :: * -> *). MonadReader r m => m r
ask
Warning -> Parser (ReaderT JSONPath Parse) Event ()
addWarning (JSONPath -> Warning
DuplicateKey JSONPath
path)
(Set Key, KeyMap Value)
-> Parser (ReaderT JSONPath Parse) Event (Set Key, KeyMap Value)
forall (m :: * -> *) a. Monad m => a -> m a
return (Key -> Set Key -> Set Key
forall a. Ord a => a -> Set a -> Set a
Set.delete Key
s Set Key
mergedKeys, Key -> Value -> KeyMap Value -> KeyMap Value
forall v. Key -> v -> KeyMap v -> KeyMap v
M.insert Key
s Value
o KeyMap Value
front)
if Key
s Key -> Key -> Bool
forall a. Eq a => a -> a -> Bool
== Key
"<<"
then case Value
o of
Object KeyMap Value
l -> (Set Key, KeyMap Value)
-> Parser (ReaderT JSONPath Parse) Event (Set Key, KeyMap Value)
forall (m :: * -> *) a. Monad m => a -> m a
return (KeyMap Value -> (Set Key, KeyMap Value)
merge KeyMap Value
l)
Array Array
l -> (Set Key, KeyMap Value)
-> Parser (ReaderT JSONPath Parse) Event (Set Key, KeyMap Value)
forall (m :: * -> *) a. Monad m => a -> m a
return ((Set Key, KeyMap Value)
-> Parser (ReaderT JSONPath Parse) Event (Set Key, KeyMap Value))
-> (Set Key, KeyMap Value)
-> Parser (ReaderT JSONPath Parse) Event (Set Key, KeyMap Value)
forall a b. (a -> b) -> a -> b
$ KeyMap Value -> (Set Key, KeyMap Value)
merge (KeyMap Value -> (Set Key, KeyMap Value))
-> KeyMap Value -> (Set Key, KeyMap Value)
forall a b. (a -> b) -> a -> b
$ (KeyMap Value -> Value -> KeyMap Value)
-> KeyMap Value -> [Value] -> KeyMap Value
forall (t :: * -> *) b a.
Foldable t =>
(b -> a -> b) -> b -> t a -> b
foldl' KeyMap Value -> Value -> KeyMap Value
mergeObjects KeyMap Value
forall v. KeyMap v
M.empty ([Value] -> KeyMap Value) -> [Value] -> KeyMap Value
forall a b. (a -> b) -> a -> b
$ Array -> [Value]
forall a. Vector a -> [a]
V.toList Array
l
Value
_ -> Parser (ReaderT JSONPath Parse) Event (Set Key, KeyMap Value)
al
else Parser (ReaderT JSONPath Parse) Event (Set Key, KeyMap Value)
al
Set Key
-> Anchor
-> KeyMap Value
-> Parser (ReaderT JSONPath Parse) Event Value
parseM Set Key
mergedKeys' Anchor
a KeyMap Value
al'
where mergeObjects :: KeyMap Value -> Value -> KeyMap Value
mergeObjects KeyMap Value
al (Object KeyMap Value
om) = KeyMap Value -> KeyMap Value -> KeyMap Value
forall v. KeyMap v -> KeyMap v -> KeyMap v
M.union KeyMap Value
al KeyMap Value
om
mergeObjects KeyMap Value
al Value
_ = KeyMap Value
al
merge :: KeyMap Value -> (Set Key, KeyMap Value)
merge KeyMap Value
xs = ([Key] -> Set Key
forall a. Ord a => [a] -> Set a
Set.fromList (KeyMap Value -> [Key]
forall v. KeyMap v -> [Key]
M.keys KeyMap Value
xs [Key] -> [Key] -> [Key]
forall a. Eq a => [a] -> [a] -> [a]
\\ KeyMap Value -> [Key]
forall v. KeyMap v -> [Key]
M.keys KeyMap Value
front), KeyMap Value -> KeyMap Value -> KeyMap Value
forall v. KeyMap v -> KeyMap v -> KeyMap v
M.union KeyMap Value
front KeyMap Value
xs)
parseSrc :: Parser (ReaderT JSONPath Parse) Event val
-> SerialT IO Event
-> IO (val, ParseState)
parseSrc :: Parser (ReaderT JSONPath Parse) Event val
-> SerialT IO Event -> IO (val, ParseState)
parseSrc Parser (ReaderT JSONPath Parse) Event val
eventParser SerialT IO Event
src =
(StateT ParseState IO val -> ParseState -> IO (val, ParseState))
-> ParseState -> StateT ParseState IO val -> IO (val, ParseState)
forall a b c. (a -> b -> c) -> b -> a -> c
flip StateT ParseState IO val -> ParseState -> IO (val, ParseState)
forall s (m :: * -> *) a. StateT s m a -> s -> m (a, s)
runStateT (Map AnchorName Value -> [Warning] -> ParseState
ParseState Map AnchorName Value
forall k a. Map k a
Map.empty []) (StateT ParseState IO val -> IO (val, ParseState))
-> StateT ParseState IO val -> IO (val, ParseState)
forall a b. (a -> b) -> a -> b
$
(ReaderT JSONPath Parse val
-> JSONPath -> StateT ParseState IO val)
-> JSONPath
-> ReaderT JSONPath Parse val
-> StateT ParseState IO val
forall a b c. (a -> b -> c) -> b -> a -> c
flip ReaderT JSONPath Parse val -> JSONPath -> StateT ParseState IO val
forall r (m :: * -> *) a. ReaderT r m a -> r -> m a
runReaderT [] (ReaderT JSONPath Parse val -> StateT ParseState IO val)
-> ReaderT JSONPath Parse val -> StateT ParseState IO val
forall a b. (a -> b) -> a -> b
$
Parser (ReaderT JSONPath Parse) Event val
-> SerialT (ReaderT JSONPath Parse) Event
-> ReaderT JSONPath Parse val
forall (m :: * -> *) a b.
MonadThrow m =>
Parser m a b -> SerialT m a -> m b
Stream.parse Parser (ReaderT JSONPath Parse) Event val
eventParser ((forall x. IO x -> ReaderT JSONPath Parse x)
-> SerialT IO Event -> SerialT (ReaderT JSONPath Parse) Event
forall (t :: (* -> *) -> * -> *) (m :: * -> *) (n :: * -> *) a.
(IsStream t, Monad m, Monad n) =>
(forall x. m x -> n x) -> t m a -> t n a
K.hoist forall x. IO x -> ReaderT JSONPath Parse x
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO SerialT IO Event
src)
mkHelper :: Parser (ReaderT JSONPath Parse) Event val
-> (SomeException -> IO (Either ParseException a))
-> ((val, ParseState) -> Either ParseException a)
-> SerialT IO Event
-> IO (Either ParseException a)
mkHelper :: Parser (ReaderT JSONPath Parse) Event val
-> (SomeException -> IO (Either ParseException a))
-> ((val, ParseState) -> Either ParseException a)
-> SerialT IO Event
-> IO (Either ParseException a)
mkHelper Parser (ReaderT JSONPath Parse) Event val
eventParser SomeException -> IO (Either ParseException a)
onOtherExc (val, ParseState) -> Either ParseException a
extractResults SerialT IO Event
src = IO (Either ParseException a)
-> [Handler IO (Either ParseException a)]
-> IO (Either ParseException a)
forall (m :: * -> *) a.
(MonadCatch m, MonadThrow m) =>
m a -> [Handler m a] -> m a
catches
((val, ParseState) -> Either ParseException a
extractResults ((val, ParseState) -> Either ParseException a)
-> IO (val, ParseState) -> IO (Either ParseException a)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Parser (ReaderT JSONPath Parse) Event val
-> SerialT IO Event -> IO (val, ParseState)
forall val.
Parser (ReaderT JSONPath Parse) Event val
-> SerialT IO Event -> IO (val, ParseState)
parseSrc Parser (ReaderT JSONPath Parse) Event val
eventParser SerialT IO Event
src)
[ (ParseException -> IO (Either ParseException a))
-> Handler IO (Either ParseException a)
forall (m :: * -> *) a e. Exception e => (e -> m a) -> Handler m a
Handler ((ParseException -> IO (Either ParseException a))
-> Handler IO (Either ParseException a))
-> (ParseException -> IO (Either ParseException a))
-> Handler IO (Either ParseException a)
forall a b. (a -> b) -> a -> b
$ \ParseException
pe -> Either ParseException a -> IO (Either ParseException a)
forall (m :: * -> *) a. Monad m => a -> m a
return (Either ParseException a -> IO (Either ParseException a))
-> Either ParseException a -> IO (Either ParseException a)
forall a b. (a -> b) -> a -> b
$ ParseException -> Either ParseException a
forall a b. a -> Either a b
Left (ParseException
pe :: ParseException)
, (YamlException -> IO (Either ParseException a))
-> Handler IO (Either ParseException a)
forall (m :: * -> *) a e. Exception e => (e -> m a) -> Handler m a
Handler ((YamlException -> IO (Either ParseException a))
-> Handler IO (Either ParseException a))
-> (YamlException -> IO (Either ParseException a))
-> Handler IO (Either ParseException a)
forall a b. (a -> b) -> a -> b
$ \YamlException
ye -> Either ParseException a -> IO (Either ParseException a)
forall (m :: * -> *) a. Monad m => a -> m a
return (Either ParseException a -> IO (Either ParseException a))
-> Either ParseException a -> IO (Either ParseException a)
forall a b. (a -> b) -> a -> b
$ ParseException -> Either ParseException a
forall a b. a -> Either a b
Left (ParseException -> Either ParseException a)
-> ParseException -> Either ParseException a
forall a b. (a -> b) -> a -> b
$ Maybe YamlException -> ParseException
InvalidYaml (Maybe YamlException -> ParseException)
-> Maybe YamlException -> ParseException
forall a b. (a -> b) -> a -> b
$ YamlException -> Maybe YamlException
forall a. a -> Maybe a
Just (YamlException
ye :: YamlException)
, (SomeAsyncException -> IO (Either ParseException a))
-> Handler IO (Either ParseException a)
forall (m :: * -> *) a e. Exception e => (e -> m a) -> Handler m a
Handler ((SomeAsyncException -> IO (Either ParseException a))
-> Handler IO (Either ParseException a))
-> (SomeAsyncException -> IO (Either ParseException a))
-> Handler IO (Either ParseException a)
forall a b. (a -> b) -> a -> b
$ \SomeAsyncException
sae -> SomeAsyncException -> IO (Either ParseException a)
forall (m :: * -> *) e a. (MonadThrow m, Exception e) => e -> m a
throwIO (SomeAsyncException
sae :: SomeAsyncException)
, (SomeException -> IO (Either ParseException a))
-> Handler IO (Either ParseException a)
forall (m :: * -> *) a e. Exception e => (e -> m a) -> Handler m a
Handler SomeException -> IO (Either ParseException a)
onOtherExc
]
decodeHelper :: FromJSON a
=> SerialT IO Y.Event
-> IO (Either ParseException ([Warning], Either String a))
decodeHelper :: SerialT IO Event
-> IO (Either ParseException ([Warning], Either AnchorName a))
decodeHelper = Parser (ReaderT JSONPath Parse) Event Value
-> (SomeException
-> IO (Either ParseException ([Warning], Either AnchorName a)))
-> ((Value, ParseState)
-> Either ParseException ([Warning], Either AnchorName a))
-> SerialT IO Event
-> IO (Either ParseException ([Warning], Either AnchorName a))
forall val a.
Parser (ReaderT JSONPath Parse) Event val
-> (SomeException -> IO (Either ParseException a))
-> ((val, ParseState) -> Either ParseException a)
-> SerialT IO Event
-> IO (Either ParseException a)
mkHelper Parser (ReaderT JSONPath Parse) Event Value
parse SomeException
-> IO (Either ParseException ([Warning], Either AnchorName a))
forall (m :: * -> *) e a. (MonadThrow m, Exception e) => e -> m a
throwIO (((Value, ParseState)
-> Either ParseException ([Warning], Either AnchorName a))
-> SerialT IO Event
-> IO (Either ParseException ([Warning], Either AnchorName a)))
-> ((Value, ParseState)
-> Either ParseException ([Warning], Either AnchorName a))
-> SerialT IO Event
-> IO (Either ParseException ([Warning], Either AnchorName a))
forall a b. (a -> b) -> a -> b
$ \(Value
v, ParseState
st) ->
([Warning], Either AnchorName a)
-> Either ParseException ([Warning], Either AnchorName a)
forall a b. b -> Either a b
Right (ParseState -> [Warning]
parseStateWarnings ParseState
st, (Value -> Parser a) -> Value -> Either AnchorName a
forall a b. (a -> Parser b) -> a -> Either AnchorName b
parseEither Value -> Parser a
forall a. FromJSON a => Value -> Parser a
parseJSON Value
v)
decodeAllHelper :: FromJSON a
=> SerialT IO Event
-> IO (Either ParseException ([Warning], Either String [a]))
decodeAllHelper :: SerialT IO Event
-> IO (Either ParseException ([Warning], Either AnchorName [a]))
decodeAllHelper = Parser (ReaderT JSONPath Parse) Event [Value]
-> (SomeException
-> IO (Either ParseException ([Warning], Either AnchorName [a])))
-> (([Value], ParseState)
-> Either ParseException ([Warning], Either AnchorName [a]))
-> SerialT IO Event
-> IO (Either ParseException ([Warning], Either AnchorName [a]))
forall val a.
Parser (ReaderT JSONPath Parse) Event val
-> (SomeException -> IO (Either ParseException a))
-> ((val, ParseState) -> Either ParseException a)
-> SerialT IO Event
-> IO (Either ParseException a)
mkHelper Parser (ReaderT JSONPath Parse) Event [Value]
parseAll SomeException
-> IO (Either ParseException ([Warning], Either AnchorName [a]))
forall (m :: * -> *) e a. (MonadThrow m, Exception e) => e -> m a
throwIO ((([Value], ParseState)
-> Either ParseException ([Warning], Either AnchorName [a]))
-> SerialT IO Event
-> IO (Either ParseException ([Warning], Either AnchorName [a])))
-> (([Value], ParseState)
-> Either ParseException ([Warning], Either AnchorName [a]))
-> SerialT IO Event
-> IO (Either ParseException ([Warning], Either AnchorName [a]))
forall a b. (a -> b) -> a -> b
$ \([Value]
vs, ParseState
st) ->
([Warning], Either AnchorName [a])
-> Either ParseException ([Warning], Either AnchorName [a])
forall a b. b -> Either a b
Right (ParseState -> [Warning]
parseStateWarnings ParseState
st, (Value -> Either AnchorName a) -> [Value] -> Either AnchorName [a]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM ((Value -> Parser a) -> Value -> Either AnchorName a
forall a b. (a -> Parser b) -> a -> Either AnchorName b
parseEither Value -> Parser a
forall a. FromJSON a => Value -> Parser a
parseJSON) [Value]
vs)
catchLeft :: SomeException -> IO (Either ParseException a)
catchLeft :: SomeException -> IO (Either ParseException a)
catchLeft = Either ParseException a -> IO (Either ParseException a)
forall (m :: * -> *) a. Monad m => a -> m a
return (Either ParseException a -> IO (Either ParseException a))
-> (SomeException -> Either ParseException a)
-> SomeException
-> IO (Either ParseException a)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ParseException -> Either ParseException a
forall a b. a -> Either a b
Left (ParseException -> Either ParseException a)
-> (SomeException -> ParseException)
-> SomeException
-> Either ParseException a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SomeException -> ParseException
OtherParseException
decodeHelper_ :: FromJSON a
=> SerialT IO Event
-> IO (Either ParseException ([Warning], a))
decodeHelper_ :: SerialT IO Event -> IO (Either ParseException ([Warning], a))
decodeHelper_ = Parser (ReaderT JSONPath Parse) Event Value
-> (SomeException -> IO (Either ParseException ([Warning], a)))
-> ((Value, ParseState) -> Either ParseException ([Warning], a))
-> SerialT IO Event
-> IO (Either ParseException ([Warning], a))
forall val a.
Parser (ReaderT JSONPath Parse) Event val
-> (SomeException -> IO (Either ParseException a))
-> ((val, ParseState) -> Either ParseException a)
-> SerialT IO Event
-> IO (Either ParseException a)
mkHelper Parser (ReaderT JSONPath Parse) Event Value
parse SomeException -> IO (Either ParseException ([Warning], a))
forall a. SomeException -> IO (Either ParseException a)
catchLeft (((Value, ParseState) -> Either ParseException ([Warning], a))
-> SerialT IO Event -> IO (Either ParseException ([Warning], a)))
-> ((Value, ParseState) -> Either ParseException ([Warning], a))
-> SerialT IO Event
-> IO (Either ParseException ([Warning], a))
forall a b. (a -> b) -> a -> b
$ \(Value
v, ParseState
st) ->
case (Value -> Parser a) -> Value -> Either AnchorName a
forall a b. (a -> Parser b) -> a -> Either AnchorName b
parseEither Value -> Parser a
forall a. FromJSON a => Value -> Parser a
parseJSON Value
v of
Left AnchorName
e -> ParseException -> Either ParseException ([Warning], a)
forall a b. a -> Either a b
Left (ParseException -> Either ParseException ([Warning], a))
-> ParseException -> Either ParseException ([Warning], a)
forall a b. (a -> b) -> a -> b
$ AnchorName -> ParseException
AesonException AnchorName
e
Right a
x -> ([Warning], a) -> Either ParseException ([Warning], a)
forall a b. b -> Either a b
Right (ParseState -> [Warning]
parseStateWarnings ParseState
st, a
x)
decodeAllHelper_ :: FromJSON a
=> SerialT IO Event
-> IO (Either ParseException ([Warning], [a]))
decodeAllHelper_ :: SerialT IO Event -> IO (Either ParseException ([Warning], [a]))
decodeAllHelper_ = Parser (ReaderT JSONPath Parse) Event [Value]
-> (SomeException -> IO (Either ParseException ([Warning], [a])))
-> (([Value], ParseState)
-> Either ParseException ([Warning], [a]))
-> SerialT IO Event
-> IO (Either ParseException ([Warning], [a]))
forall val a.
Parser (ReaderT JSONPath Parse) Event val
-> (SomeException -> IO (Either ParseException a))
-> ((val, ParseState) -> Either ParseException a)
-> SerialT IO Event
-> IO (Either ParseException a)
mkHelper Parser (ReaderT JSONPath Parse) Event [Value]
parseAll SomeException -> IO (Either ParseException ([Warning], [a]))
forall a. SomeException -> IO (Either ParseException a)
catchLeft ((([Value], ParseState) -> Either ParseException ([Warning], [a]))
-> SerialT IO Event -> IO (Either ParseException ([Warning], [a])))
-> (([Value], ParseState)
-> Either ParseException ([Warning], [a]))
-> SerialT IO Event
-> IO (Either ParseException ([Warning], [a]))
forall a b. (a -> b) -> a -> b
$ \([Value]
vs, ParseState
st) ->
case (Value -> Either AnchorName a) -> [Value] -> Either AnchorName [a]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM ((Value -> Parser a) -> Value -> Either AnchorName a
forall a b. (a -> Parser b) -> a -> Either AnchorName b
parseEither Value -> Parser a
forall a. FromJSON a => Value -> Parser a
parseJSON) [Value]
vs of
Left AnchorName
e -> ParseException -> Either ParseException ([Warning], [a])
forall a b. a -> Either a b
Left (ParseException -> Either ParseException ([Warning], [a]))
-> ParseException -> Either ParseException ([Warning], [a])
forall a b. (a -> b) -> a -> b
$ AnchorName -> ParseException
AesonException AnchorName
e
Right [a]
xs -> ([Warning], [a]) -> Either ParseException ([Warning], [a])
forall a b. b -> Either a b
Right (ParseState -> [Warning]
parseStateWarnings ParseState
st, [a]
xs)
type StringStyle = Text -> ( Tag, Style )
stringScalar :: StringStyle -> Maybe Text -> Text -> Event
stringScalar :: StringStyle -> Maybe Text -> Text -> Event
stringScalar StringStyle
_ Maybe Text
anchor Text
"" = ByteString -> Tag -> Style -> Anchor -> Event
EventScalar ByteString
"" Tag
NoTag Style
SingleQuoted (Text -> AnchorName
T.unpack (Text -> AnchorName) -> Maybe Text -> Anchor
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Maybe Text
anchor)
stringScalar StringStyle
stringStyle Maybe Text
anchor Text
s = ByteString -> Tag -> Style -> Anchor -> Event
EventScalar (Text -> ByteString
encodeUtf8 Text
s) Tag
tag Style
style (Text -> AnchorName
T.unpack (Text -> AnchorName) -> Maybe Text -> Anchor
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Maybe Text
anchor)
where
( Tag
tag, Style
style ) = StringStyle
stringStyle Text
s
defaultStringStyle :: StringStyle
defaultStringStyle :: StringStyle
defaultStringStyle = \Text
s ->
case () of
()
| Text
"\n" Text -> Text -> Bool
`T.isInfixOf` Text
s -> ( Tag
NoTag, Style
Literal )
| Text -> Bool
isSpecialString Text
s -> ( Tag
NoTag, Style
SingleQuoted )
| Bool
otherwise -> ( Tag
NoTag, Style
PlainNoTag )
isSpecialString :: Text -> Bool
isSpecialString :: Text -> Bool
isSpecialString Text
s = Text
s Text -> HashSet Text -> Bool
forall a. (Eq a, Hashable a) => a -> HashSet a -> Bool
`HashSet.member` HashSet Text
specialStrings Bool -> Bool -> Bool
|| Text -> Bool
isNumeric Text
s
specialStrings :: HashSet.HashSet Text
specialStrings :: HashSet Text
specialStrings = [Text] -> HashSet Text
forall a. (Eq a, Hashable a) => [a] -> HashSet a
HashSet.fromList ([Text] -> HashSet Text) -> [Text] -> HashSet Text
forall a b. (a -> b) -> a -> b
$ Text -> [Text]
T.words
Text
"y Y yes Yes YES n N no No NO true True TRUE false False FALSE on On ON off Off OFF null Null NULL ~ *"
isNumeric :: Text -> Bool
isNumeric :: Text -> Bool
isNumeric = (AnchorName -> Bool)
-> (Scientific -> Bool) -> Either AnchorName Scientific -> Bool
forall a c b. (a -> c) -> (b -> c) -> Either a b -> c
either (Bool -> AnchorName -> Bool
forall a b. a -> b -> a
const Bool
False) (Bool -> Scientific -> Bool
forall a b. a -> b -> a
const Bool
True) (Either AnchorName Scientific -> Bool)
-> (Text -> Either AnchorName Scientific) -> Text -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> Either AnchorName Scientific
textToScientific
objToStream :: ToJSON a => StringStyle -> a -> [Y.Event]
objToStream :: StringStyle -> a -> [Event]
objToStream StringStyle
stringStyle a
o =
(:) Event
EventStreamStart
([Event] -> [Event]) -> ([Event] -> [Event]) -> [Event] -> [Event]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (:) Event
EventDocumentStart
([Event] -> [Event]) -> [Event] -> [Event]
forall a b. (a -> b) -> a -> b
$ StringStyle -> a -> [Event] -> [Event]
forall a. ToJSON a => StringStyle -> a -> [Event] -> [Event]
objToEvents StringStyle
stringStyle a
o
[ Event
EventDocumentEnd
, Event
EventStreamEnd
]
objToEvents :: ToJSON a => StringStyle -> a -> [Y.Event] -> [Y.Event]
objToEvents :: StringStyle -> a -> [Event] -> [Event]
objToEvents StringStyle
stringStyle = Value -> [Event] -> [Event]
objToEvents' (Value -> [Event] -> [Event])
-> (a -> Value) -> a -> [Event] -> [Event]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. a -> Value
forall a. ToJSON a => a -> Value
toJSON
where
objToEvents' :: Value -> [Event] -> [Event]
objToEvents' (Array Array
list) [Event]
rest =
Tag -> SequenceStyle -> Anchor -> Event
EventSequenceStart Tag
NoTag SequenceStyle
AnySequence Anchor
forall a. Maybe a
Nothing
Event -> [Event] -> [Event]
forall a. a -> [a] -> [a]
: (Value -> [Event] -> [Event]) -> [Event] -> [Value] -> [Event]
forall (t :: * -> *) a b.
Foldable t =>
(a -> b -> b) -> b -> t a -> b
foldr Value -> [Event] -> [Event]
objToEvents' (Event
EventSequenceEnd Event -> [Event] -> [Event]
forall a. a -> [a] -> [a]
: [Event]
rest) (Array -> [Value]
forall a. Vector a -> [a]
V.toList Array
list)
objToEvents' (Object KeyMap Value
o) [Event]
rest =
Tag -> MappingStyle -> Anchor -> Event
EventMappingStart Tag
NoTag MappingStyle
AnyMapping Anchor
forall a. Maybe a
Nothing
Event -> [Event] -> [Event]
forall a. a -> [a] -> [a]
: (Pair -> [Event] -> [Event]) -> [Event] -> [Pair] -> [Event]
forall (t :: * -> *) a b.
Foldable t =>
(a -> b -> b) -> b -> t a -> b
foldr Pair -> [Event] -> [Event]
pairToEvents (Event
EventMappingEnd Event -> [Event] -> [Event]
forall a. a -> [a] -> [a]
: [Event]
rest) (KeyMap Value -> [Pair]
forall v. KeyMap v -> [(Key, v)]
M.toList KeyMap Value
o)
where
pairToEvents :: Pair -> [Y.Event] -> [Y.Event]
pairToEvents :: Pair -> [Event] -> [Event]
pairToEvents (Key
k, Value
v) = Value -> [Event] -> [Event]
objToEvents' (Text -> Value
String (Text -> Value) -> Text -> Value
forall a b. (a -> b) -> a -> b
$ Key -> Text
toText Key
k) ([Event] -> [Event]) -> ([Event] -> [Event]) -> [Event] -> [Event]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Value -> [Event] -> [Event]
objToEvents' Value
v
objToEvents' (String Text
s) [Event]
rest = StringStyle -> Maybe Text -> Text -> Event
stringScalar StringStyle
stringStyle Maybe Text
forall a. Maybe a
Nothing Text
s Event -> [Event] -> [Event]
forall a. a -> [a] -> [a]
: [Event]
rest
objToEvents' Value
Null [Event]
rest = ByteString -> Tag -> Style -> Anchor -> Event
EventScalar ByteString
"null" Tag
NullTag Style
PlainNoTag Anchor
forall a. Maybe a
Nothing Event -> [Event] -> [Event]
forall a. a -> [a] -> [a]
: [Event]
rest
objToEvents' (Bool Bool
True) [Event]
rest = ByteString -> Tag -> Style -> Anchor -> Event
EventScalar ByteString
"true" Tag
BoolTag Style
PlainNoTag Anchor
forall a. Maybe a
Nothing Event -> [Event] -> [Event]
forall a. a -> [a] -> [a]
: [Event]
rest
objToEvents' (Bool Bool
False) [Event]
rest = ByteString -> Tag -> Style -> Anchor -> Event
EventScalar ByteString
"false" Tag
BoolTag Style
PlainNoTag Anchor
forall a. Maybe a
Nothing Event -> [Event] -> [Event]
forall a. a -> [a] -> [a]
: [Event]
rest
objToEvents' (Number Scientific
s) [Event]
rest =
let builder :: Builder
builder
| Scientific -> Int
base10Exponent Scientific
s Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
0 = Integer -> Builder
BB.integerDec (Integer -> Builder) -> Integer -> Builder
forall a b. (a -> b) -> a -> b
$ Scientific -> Integer
coefficient Scientific
s
| Bool
otherwise = Scientific -> Builder
scientificBuilder Scientific
s
lbs :: ByteString
lbs = Builder -> ByteString
BB.toLazyByteString Builder
builder
bs :: ByteString
bs = ByteString -> ByteString
BL.toStrict ByteString
lbs
in ByteString -> Tag -> Style -> Anchor -> Event
EventScalar ByteString
bs Tag
IntTag Style
PlainNoTag Anchor
forall a. Maybe a
Nothing Event -> [Event] -> [Event]
forall a. a -> [a] -> [a]
: [Event]
rest
instance (MonadThrow m, MonadReader r m, MonadCatch m) => MonadReader r (Parser m a) where
{-# INLINE ask #-}
ask :: Parser m a r
ask = m r -> Parser m a r
forall (m :: * -> *) b a. Monad m => m b -> Parser m a b
fromEffect m r
forall r (m :: * -> *). MonadReader r m => m r
ask
{-# INLINE local #-}
local :: (r -> r) -> Parser m a a -> Parser m a a
local r -> r
f (Parser m a a -> Parser m a a
forall (m :: * -> *) a b.
MonadThrow m =>
Parser m a b -> Parser m a b
fromParserK -> ParserD.Parser s -> a -> m (Step s a)
step m (Initial s a)
init' s -> m a
extract) =
Parser m a a -> Parser m a a
forall (m :: * -> *) a b.
MonadCatch m =>
Parser m a b -> Parser m a b
toParserK (Parser m a a -> Parser m a a) -> Parser m a a -> Parser m a a
forall a b. (a -> b) -> a -> b
$ (s -> a -> m (Step s a))
-> m (Initial s a) -> (s -> m a) -> Parser m a a
forall (m :: * -> *) a b s.
(s -> a -> m (Step s b))
-> m (Initial s b) -> (s -> m b) -> Parser m a b
ParserD.Parser (((r -> r) -> m (Step s a) -> m (Step s a)
forall r (m :: * -> *) a. MonadReader r m => (r -> r) -> m a -> m a
local r -> r
f (m (Step s a) -> m (Step s a))
-> (a -> m (Step s a)) -> a -> m (Step s a)
forall b c a. (b -> c) -> (a -> b) -> a -> c
.) ((a -> m (Step s a)) -> a -> m (Step s a))
-> (s -> a -> m (Step s a)) -> s -> a -> m (Step s a)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. s -> a -> m (Step s a)
step)
((r -> r) -> m (Initial s a) -> m (Initial s a)
forall r (m :: * -> *) a. MonadReader r m => (r -> r) -> m a -> m a
local r -> r
f m (Initial s a)
init')
((r -> r) -> m a -> m a
forall r (m :: * -> *) a. MonadReader r m => (r -> r) -> m a -> m a
local r -> r
f (m a -> m a) -> (s -> m a) -> s -> m a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. s -> m a
extract)
instance (MonadThrow m, MonadState s m) => MonadState s (Parser m a) where
{-# INLINE get #-}
get :: Parser m a s
get = m s -> Parser m a s
forall (m :: * -> *) b a. Monad m => m b -> Parser m a b
fromEffect m s
forall s (m :: * -> *). MonadState s m => m s
get
{-# INLINE put #-}
put :: s -> Parser m a ()
put = m () -> Parser m a ()
forall (m :: * -> *) b a. Monad m => m b -> Parser m a b
fromEffect (m () -> Parser m a ()) -> (s -> m ()) -> s -> Parser m a ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. s -> m ()
forall s (m :: * -> *). MonadState s m => s -> m ()
put
instance (MonadThrow m, MonadIO m) => MonadIO (Parser m a) where
{-# INLINE liftIO #-}
liftIO :: IO a -> Parser m a a
liftIO = m a -> Parser m a a
forall (m :: * -> *) b a. Monad m => m b -> Parser m a b
fromEffect (m a -> Parser m a a) -> (IO a -> m a) -> IO a -> Parser m a a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO