{-# LANGUAGE CPP #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE OverloadedStrings #-}
#if (defined (ghcjs_HOST_OS))
module Data.Yaml {-# WARNING "GHCJS is not supported yet (will break at runtime once called)." #-}
#else
module Data.Yaml
#endif
(
encode
, encodeWith
, encodeFile
, encodeFileWith
, decodeEither'
, decodeFileEither
, decodeFileWithWarnings
, decodeThrow
, decodeFileThrow
, decodeAllEither'
, decodeAllFileEither
, decodeAllFileWithWarnings
, decodeAllThrow
, decodeAllFileThrow
, decodeHelper
, Value (..)
, Parser
, Object
, Array
, ParseException(..)
, prettyPrintParseException
, YamlException (..)
, YamlMark (..)
, object
, array
, (.=)
, (.:)
, (.:?)
, (.!=)
, withObject
, withText
, withArray
, withScientific
, withBool
, parseMonad
, parseEither
, parseMaybe
, ToJSON (..)
, FromJSON (..)
, isSpecialString
, EncodeOptions
, defaultEncodeOptions
, defaultStringStyle
, setStringStyle
, setFormat
, FormatOptions
, defaultFormatOptions
, setWidth
, decode
, decodeFile
, decodeEither
) where
#if !MIN_VERSION_base(4,8,0)
import Control.Applicative((<$>))
#endif
import Control.Exception
import Control.Monad.IO.Class (MonadIO, liftIO)
import Control.Monad.Trans.Resource (MonadThrow, throwM)
import Data.Aeson
( Value (..), ToJSON (..), FromJSON (..), object
, (.=) , (.:) , (.:?) , (.!=)
, Object, Array
, withObject, withText, withArray, withScientific, withBool
)
import Data.Aeson.Types (parseMaybe, parseEither, Parser)
import Data.ByteString (ByteString)
import Data.Conduit ((.|), runConduitRes)
import qualified Data.Conduit.List as CL
import qualified Data.Vector as V
import System.IO.Unsafe (unsafePerformIO)
import Data.Text (Text)
import Data.Yaml.Internal
import Text.Libyaml hiding (encode, decode, encodeFile, decodeFile, encodeWith, encodeFileWith)
import qualified Text.Libyaml as Y
setStringStyle :: (Text -> ( Tag, Style )) -> EncodeOptions -> EncodeOptions
setStringStyle :: (Text -> (Tag, Style)) -> EncodeOptions -> EncodeOptions
setStringStyle Text -> (Tag, Style)
s EncodeOptions
opts = EncodeOptions
opts { encodeOptionsStringStyle = s }
setFormat :: FormatOptions -> EncodeOptions -> EncodeOptions
setFormat :: FormatOptions -> EncodeOptions -> EncodeOptions
setFormat FormatOptions
f EncodeOptions
opts = EncodeOptions
opts { encodeOptionsFormat = f }
data EncodeOptions = EncodeOptions
{ EncodeOptions -> Text -> (Tag, Style)
encodeOptionsStringStyle :: Text -> ( Tag, Style )
, EncodeOptions -> FormatOptions
encodeOptionsFormat :: FormatOptions
}
defaultEncodeOptions :: EncodeOptions
defaultEncodeOptions :: EncodeOptions
defaultEncodeOptions = EncodeOptions
{ encodeOptionsStringStyle :: Text -> (Tag, Style)
encodeOptionsStringStyle = Text -> (Tag, Style)
defaultStringStyle
, encodeOptionsFormat :: FormatOptions
encodeOptionsFormat = FormatOptions
defaultFormatOptions
}
encode :: ToJSON a => a -> ByteString
encode :: forall a. ToJSON a => a -> ByteString
encode = EncodeOptions -> a -> ByteString
forall a. ToJSON a => EncodeOptions -> a -> ByteString
encodeWith EncodeOptions
defaultEncodeOptions
encodeWith :: ToJSON a => EncodeOptions -> a -> ByteString
encodeWith :: forall a. ToJSON a => EncodeOptions -> a -> ByteString
encodeWith EncodeOptions
opts a
obj = IO ByteString -> ByteString
forall a. IO a -> a
unsafePerformIO (IO ByteString -> ByteString) -> IO ByteString -> ByteString
forall a b. (a -> b) -> a -> b
$ ConduitT () Void (ResourceT IO) ByteString -> IO ByteString
forall (m :: * -> *) r.
MonadUnliftIO m =>
ConduitT () Void (ResourceT m) r -> m r
runConduitRes
(ConduitT () Void (ResourceT IO) ByteString -> IO ByteString)
-> ConduitT () Void (ResourceT IO) ByteString -> IO ByteString
forall a b. (a -> b) -> a -> b
$ [Event] -> ConduitT () Event (ResourceT IO) ()
forall (m :: * -> *) a i. Monad m => [a] -> ConduitT i a m ()
CL.sourceList ((Text -> (Tag, Style)) -> Value -> [Event]
forall a. ToJSON a => (Text -> (Tag, Style)) -> a -> [Event]
objToStream (EncodeOptions -> Text -> (Tag, Style)
encodeOptionsStringStyle EncodeOptions
opts) (Value -> [Event]) -> Value -> [Event]
forall a b. (a -> b) -> a -> b
$ a -> Value
forall a. ToJSON a => a -> Value
toJSON a
obj)
ConduitT () Event (ResourceT IO) ()
-> ConduitT Event Void (ResourceT IO) ByteString
-> ConduitT () Void (ResourceT IO) ByteString
forall (m :: * -> *) a b c r.
Monad m =>
ConduitT a b m () -> ConduitT b c m r -> ConduitT a c m r
.| FormatOptions -> ConduitT Event Void (ResourceT IO) ByteString
forall (m :: * -> *) o.
MonadResource m =>
FormatOptions -> ConduitM Event o m ByteString
Y.encodeWith (EncodeOptions -> FormatOptions
encodeOptionsFormat EncodeOptions
opts)
encodeFile :: ToJSON a => FilePath -> a -> IO ()
encodeFile :: forall a. ToJSON a => FilePath -> a -> IO ()
encodeFile = EncodeOptions -> FilePath -> a -> IO ()
forall a. ToJSON a => EncodeOptions -> FilePath -> a -> IO ()
encodeFileWith EncodeOptions
defaultEncodeOptions
encodeFileWith :: ToJSON a => EncodeOptions -> FilePath -> a -> IO ()
encodeFileWith :: forall a. ToJSON a => EncodeOptions -> FilePath -> a -> IO ()
encodeFileWith EncodeOptions
opts FilePath
fp a
obj = ConduitT () Void (ResourceT IO) () -> IO ()
forall (m :: * -> *) r.
MonadUnliftIO m =>
ConduitT () Void (ResourceT m) r -> m r
runConduitRes
(ConduitT () Void (ResourceT IO) () -> IO ())
-> ConduitT () Void (ResourceT IO) () -> IO ()
forall a b. (a -> b) -> a -> b
$ [Event] -> ConduitT () Event (ResourceT IO) ()
forall (m :: * -> *) a i. Monad m => [a] -> ConduitT i a m ()
CL.sourceList ((Text -> (Tag, Style)) -> Value -> [Event]
forall a. ToJSON a => (Text -> (Tag, Style)) -> a -> [Event]
objToStream (EncodeOptions -> Text -> (Tag, Style)
encodeOptionsStringStyle EncodeOptions
opts) (Value -> [Event]) -> Value -> [Event]
forall a b. (a -> b) -> a -> b
$ a -> Value
forall a. ToJSON a => a -> Value
toJSON a
obj)
ConduitT () Event (ResourceT IO) ()
-> ConduitT Event Void (ResourceT IO) ()
-> ConduitT () Void (ResourceT IO) ()
forall (m :: * -> *) a b c r.
Monad m =>
ConduitT a b m () -> ConduitT b c m r -> ConduitT a c m r
.| FormatOptions -> FilePath -> ConduitT Event Void (ResourceT IO) ()
forall (m :: * -> *) o.
MonadResource m =>
FormatOptions -> FilePath -> ConduitM Event o m ()
Y.encodeFileWith (EncodeOptions -> FormatOptions
encodeOptionsFormat EncodeOptions
opts) FilePath
fp
decode :: FromJSON a
=> ByteString
-> Maybe a
decode :: forall a. FromJSON a => ByteString -> Maybe a
decode ByteString
bs = IO (Maybe a) -> Maybe a
forall a. IO a -> a
unsafePerformIO
(IO (Maybe a) -> Maybe a) -> IO (Maybe a) -> Maybe a
forall a b. (a -> b) -> a -> b
$ (ParseException -> Maybe a)
-> (([Warning], Maybe a) -> Maybe a)
-> Either ParseException ([Warning], Maybe a)
-> Maybe a
forall a c b. (a -> c) -> (b -> c) -> Either a b -> c
either (Maybe a -> ParseException -> Maybe a
forall a b. a -> b -> a
const Maybe a
forall a. Maybe a
Nothing) ([Warning], Maybe a) -> Maybe a
forall a b. (a, b) -> b
snd
(Either ParseException ([Warning], Maybe a) -> Maybe a)
-> IO (Either ParseException ([Warning], Maybe a)) -> IO (Maybe a)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ConduitM () Event Parse ()
-> IO (Either ParseException ([Warning], Maybe a))
forall a.
FromJSON a =>
ConduitM () Event Parse ()
-> IO (Either ParseException ([Warning], a))
decodeHelper_ (ByteString -> ConduitM () Event Parse ()
forall (m :: * -> *) i.
MonadResource m =>
ByteString -> ConduitM i Event m ()
Y.decode ByteString
bs)
{-# DEPRECATED decode "Please use decodeEither or decodeThrow, which provide information on how the decode failed" #-}
decodeFile :: FromJSON a
=> FilePath
-> IO (Maybe a)
decodeFile :: forall a. FromJSON a => FilePath -> IO (Maybe a)
decodeFile FilePath
fp = ((([Warning], Either FilePath (Maybe a))
-> Either FilePath (Maybe a))
-> Either ParseException ([Warning], Either FilePath (Maybe a))
-> Either ParseException (Either FilePath (Maybe a))
forall a b.
(a -> b) -> Either ParseException a -> Either ParseException b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ([Warning], Either FilePath (Maybe a)) -> Either FilePath (Maybe a)
forall a b. (a, b) -> b
snd (Either ParseException ([Warning], Either FilePath (Maybe a))
-> Either ParseException (Either FilePath (Maybe a)))
-> IO
(Either ParseException ([Warning], Either FilePath (Maybe a)))
-> IO (Either ParseException (Either FilePath (Maybe a)))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ConduitM () Event Parse ()
-> IO
(Either ParseException ([Warning], Either FilePath (Maybe a)))
forall a.
FromJSON a =>
ConduitM () Event Parse ()
-> IO (Either ParseException ([Warning], Either FilePath a))
decodeHelper (FilePath -> ConduitM () Event Parse ()
forall (m :: * -> *) i.
MonadResource m =>
FilePath -> ConduitM i Event m ()
Y.decodeFile FilePath
fp)) IO (Either ParseException (Either FilePath (Maybe a)))
-> (Either ParseException (Either FilePath (Maybe a))
-> IO (Maybe a))
-> IO (Maybe a)
forall a b. IO a -> (a -> IO b) -> IO b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= (ParseException -> IO (Maybe a))
-> (Either FilePath (Maybe a) -> IO (Maybe a))
-> Either ParseException (Either FilePath (Maybe a))
-> IO (Maybe a)
forall a c b. (a -> c) -> (b -> c) -> Either a b -> c
either ParseException -> IO (Maybe a)
forall e a. Exception e => e -> IO a
throwIO (Maybe a -> IO (Maybe a)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (Maybe a -> IO (Maybe a))
-> (Either FilePath (Maybe a) -> Maybe a)
-> Either FilePath (Maybe a)
-> IO (Maybe a)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (FilePath -> Maybe a)
-> (Maybe a -> Maybe a) -> Either FilePath (Maybe a) -> Maybe a
forall a c b. (a -> c) -> (b -> c) -> Either a b -> c
either (Maybe a -> FilePath -> Maybe a
forall a b. a -> b -> a
const Maybe a
forall a. Maybe a
Nothing) Maybe a -> Maybe a
forall a. a -> a
id)
{-# DEPRECATED decodeFile "Please use decodeFileEither, which does not confused type-directed and runtime exceptions." #-}
decodeFileEither
:: FromJSON a
=> FilePath
-> IO (Either ParseException a)
decodeFileEither :: forall a. FromJSON a => FilePath -> IO (Either ParseException a)
decodeFileEither = (Either ParseException ([Warning], a) -> Either ParseException a)
-> IO (Either ParseException ([Warning], a))
-> IO (Either ParseException a)
forall a b. (a -> b) -> IO a -> IO b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ((([Warning], a) -> a)
-> Either ParseException ([Warning], a) -> Either ParseException a
forall a b.
(a -> b) -> Either ParseException a -> Either ParseException b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ([Warning], a) -> a
forall a b. (a, b) -> b
snd) (IO (Either ParseException ([Warning], a))
-> IO (Either ParseException a))
-> (FilePath -> IO (Either ParseException ([Warning], a)))
-> FilePath
-> IO (Either ParseException a)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. FilePath -> IO (Either ParseException ([Warning], a))
forall a.
FromJSON a =>
FilePath -> IO (Either ParseException ([Warning], a))
decodeFileWithWarnings
decodeAllFileEither
:: FromJSON a
=> FilePath
-> IO (Either ParseException [a])
decodeAllFileEither :: forall a. FromJSON a => FilePath -> IO (Either ParseException [a])
decodeAllFileEither = (Either ParseException ([Warning], [a])
-> Either ParseException [a])
-> IO (Either ParseException ([Warning], [a]))
-> IO (Either ParseException [a])
forall a b. (a -> b) -> IO a -> IO b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ((([Warning], [a]) -> [a])
-> Either ParseException ([Warning], [a])
-> Either ParseException [a]
forall a b.
(a -> b) -> Either ParseException a -> Either ParseException b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ([Warning], [a]) -> [a]
forall a b. (a, b) -> b
snd) (IO (Either ParseException ([Warning], [a]))
-> IO (Either ParseException [a]))
-> (FilePath -> IO (Either ParseException ([Warning], [a])))
-> FilePath
-> IO (Either ParseException [a])
forall b c a. (b -> c) -> (a -> b) -> a -> c
. FilePath -> IO (Either ParseException ([Warning], [a]))
forall a.
FromJSON a =>
FilePath -> IO (Either ParseException ([Warning], [a]))
decodeAllFileWithWarnings
decodeFileWithWarnings
:: FromJSON a
=> FilePath
-> IO (Either ParseException ([Warning], a))
decodeFileWithWarnings :: forall a.
FromJSON a =>
FilePath -> IO (Either ParseException ([Warning], a))
decodeFileWithWarnings = ConduitM () Event Parse ()
-> IO (Either ParseException ([Warning], a))
forall a.
FromJSON a =>
ConduitM () Event Parse ()
-> IO (Either ParseException ([Warning], a))
decodeHelper_ (ConduitM () Event Parse ()
-> IO (Either ParseException ([Warning], a)))
-> (FilePath -> ConduitM () Event Parse ())
-> FilePath
-> IO (Either ParseException ([Warning], a))
forall b c a. (b -> c) -> (a -> b) -> a -> c
. FilePath -> ConduitM () Event Parse ()
forall (m :: * -> *) i.
MonadResource m =>
FilePath -> ConduitM i Event m ()
Y.decodeFile
decodeAllFileWithWarnings
:: FromJSON a
=> FilePath
-> IO (Either ParseException ([Warning], [a]))
decodeAllFileWithWarnings :: forall a.
FromJSON a =>
FilePath -> IO (Either ParseException ([Warning], [a]))
decodeAllFileWithWarnings = ConduitM () Event Parse ()
-> IO (Either ParseException ([Warning], [a]))
forall a.
FromJSON a =>
ConduitM () Event Parse ()
-> IO (Either ParseException ([Warning], [a]))
decodeAllHelper_ (ConduitM () Event Parse ()
-> IO (Either ParseException ([Warning], [a])))
-> (FilePath -> ConduitM () Event Parse ())
-> FilePath
-> IO (Either ParseException ([Warning], [a]))
forall b c a. (b -> c) -> (a -> b) -> a -> c
. FilePath -> ConduitM () Event Parse ()
forall (m :: * -> *) i.
MonadResource m =>
FilePath -> ConduitM i Event m ()
Y.decodeFile
decodeEither :: FromJSON a => ByteString -> Either String a
decodeEither :: forall a. FromJSON a => ByteString -> Either FilePath a
decodeEither ByteString
bs = IO (Either FilePath a) -> Either FilePath a
forall a. IO a -> a
unsafePerformIO
(IO (Either FilePath a) -> Either FilePath a)
-> IO (Either FilePath a) -> Either FilePath a
forall a b. (a -> b) -> a -> b
$ (ParseException -> Either FilePath a)
-> (Either FilePath a -> Either FilePath a)
-> Either ParseException (Either FilePath a)
-> Either FilePath a
forall a c b. (a -> c) -> (b -> c) -> Either a b -> c
either (FilePath -> Either FilePath a
forall a b. a -> Either a b
Left (FilePath -> Either FilePath a)
-> (ParseException -> FilePath)
-> ParseException
-> Either FilePath a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ParseException -> FilePath
prettyPrintParseException) Either FilePath a -> Either FilePath a
forall a. a -> a
id
(Either ParseException (Either FilePath a) -> Either FilePath a)
-> IO (Either ParseException (Either FilePath a))
-> IO (Either FilePath a)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ((([Warning], Either FilePath a) -> Either FilePath a)
-> Either ParseException ([Warning], Either FilePath a)
-> Either ParseException (Either FilePath a)
forall a b.
(a -> b) -> Either ParseException a -> Either ParseException b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ([Warning], Either FilePath a) -> Either FilePath a
forall a b. (a, b) -> b
snd (Either ParseException ([Warning], Either FilePath a)
-> Either ParseException (Either FilePath a))
-> IO (Either ParseException ([Warning], Either FilePath a))
-> IO (Either ParseException (Either FilePath a))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ConduitM () Event Parse ()
-> IO (Either ParseException ([Warning], Either FilePath a))
forall a.
FromJSON a =>
ConduitM () Event Parse ()
-> IO (Either ParseException ([Warning], Either FilePath a))
decodeHelper (ByteString -> ConduitM () Event Parse ()
forall (m :: * -> *) i.
MonadResource m =>
ByteString -> ConduitM i Event m ()
Y.decode ByteString
bs))
{-# DEPRECATED decodeEither "Please use decodeEither' or decodeThrow, which provide more useful failures" #-}
decodeEither' :: FromJSON a => ByteString -> Either ParseException a
decodeEither' :: forall a. FromJSON a => ByteString -> Either ParseException a
decodeEither' = (ParseException -> Either ParseException a)
-> (Either FilePath a -> Either ParseException a)
-> Either ParseException (Either FilePath a)
-> Either ParseException a
forall a c b. (a -> c) -> (b -> c) -> Either a b -> c
either ParseException -> Either ParseException a
forall a b. a -> Either a b
Left ((FilePath -> Either ParseException a)
-> (a -> Either ParseException a)
-> Either FilePath a
-> Either ParseException a
forall a c b. (a -> c) -> (b -> c) -> Either a b -> c
either (ParseException -> Either ParseException a
forall a b. a -> Either a b
Left (ParseException -> Either ParseException a)
-> (FilePath -> ParseException)
-> FilePath
-> Either ParseException a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. FilePath -> ParseException
AesonException) a -> Either ParseException a
forall a b. b -> Either a b
Right)
(Either ParseException (Either FilePath a)
-> Either ParseException a)
-> (ByteString -> Either ParseException (Either FilePath a))
-> ByteString
-> Either ParseException a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. IO (Either ParseException (Either FilePath a))
-> Either ParseException (Either FilePath a)
forall a. IO a -> a
unsafePerformIO
(IO (Either ParseException (Either FilePath a))
-> Either ParseException (Either FilePath a))
-> (ByteString -> IO (Either ParseException (Either FilePath a)))
-> ByteString
-> Either ParseException (Either FilePath a)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Either ParseException ([Warning], Either FilePath a)
-> Either ParseException (Either FilePath a))
-> IO (Either ParseException ([Warning], Either FilePath a))
-> IO (Either ParseException (Either FilePath a))
forall a b. (a -> b) -> IO a -> IO b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ((([Warning], Either FilePath a) -> Either FilePath a)
-> Either ParseException ([Warning], Either FilePath a)
-> Either ParseException (Either FilePath a)
forall a b.
(a -> b) -> Either ParseException a -> Either ParseException b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ([Warning], Either FilePath a) -> Either FilePath a
forall a b. (a, b) -> b
snd) (IO (Either ParseException ([Warning], Either FilePath a))
-> IO (Either ParseException (Either FilePath a)))
-> (ByteString
-> IO (Either ParseException ([Warning], Either FilePath a)))
-> ByteString
-> IO (Either ParseException (Either FilePath a))
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ConduitM () Event Parse ()
-> IO (Either ParseException ([Warning], Either FilePath a))
forall a.
FromJSON a =>
ConduitM () Event Parse ()
-> IO (Either ParseException ([Warning], Either FilePath a))
decodeHelper
(ConduitM () Event Parse ()
-> IO (Either ParseException ([Warning], Either FilePath a)))
-> (ByteString -> ConduitM () Event Parse ())
-> ByteString
-> IO (Either ParseException ([Warning], Either FilePath a))
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> ConduitM () Event Parse ()
forall (m :: * -> *) i.
MonadResource m =>
ByteString -> ConduitM i Event m ()
Y.decode
decodeAllEither' :: FromJSON a => ByteString -> Either ParseException [a]
decodeAllEither' :: forall a. FromJSON a => ByteString -> Either ParseException [a]
decodeAllEither' = (ParseException -> Either ParseException [a])
-> (Either FilePath [a] -> Either ParseException [a])
-> Either ParseException (Either FilePath [a])
-> Either ParseException [a]
forall a c b. (a -> c) -> (b -> c) -> Either a b -> c
either ParseException -> Either ParseException [a]
forall a b. a -> Either a b
Left ((FilePath -> Either ParseException [a])
-> ([a] -> Either ParseException [a])
-> Either FilePath [a]
-> Either ParseException [a]
forall a c b. (a -> c) -> (b -> c) -> Either a b -> c
either (ParseException -> Either ParseException [a]
forall a b. a -> Either a b
Left (ParseException -> Either ParseException [a])
-> (FilePath -> ParseException)
-> FilePath
-> Either ParseException [a]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. FilePath -> ParseException
AesonException) [a] -> Either ParseException [a]
forall a b. b -> Either a b
Right)
(Either ParseException (Either FilePath [a])
-> Either ParseException [a])
-> (ByteString -> Either ParseException (Either FilePath [a]))
-> ByteString
-> Either ParseException [a]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. IO (Either ParseException (Either FilePath [a]))
-> Either ParseException (Either FilePath [a])
forall a. IO a -> a
unsafePerformIO
(IO (Either ParseException (Either FilePath [a]))
-> Either ParseException (Either FilePath [a]))
-> (ByteString -> IO (Either ParseException (Either FilePath [a])))
-> ByteString
-> Either ParseException (Either FilePath [a])
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Either ParseException ([Warning], Either FilePath [a])
-> Either ParseException (Either FilePath [a]))
-> IO (Either ParseException ([Warning], Either FilePath [a]))
-> IO (Either ParseException (Either FilePath [a]))
forall a b. (a -> b) -> IO a -> IO b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ((([Warning], Either FilePath [a]) -> Either FilePath [a])
-> Either ParseException ([Warning], Either FilePath [a])
-> Either ParseException (Either FilePath [a])
forall a b.
(a -> b) -> Either ParseException a -> Either ParseException b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ([Warning], Either FilePath [a]) -> Either FilePath [a]
forall a b. (a, b) -> b
snd) (IO (Either ParseException ([Warning], Either FilePath [a]))
-> IO (Either ParseException (Either FilePath [a])))
-> (ByteString
-> IO (Either ParseException ([Warning], Either FilePath [a])))
-> ByteString
-> IO (Either ParseException (Either FilePath [a]))
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ConduitM () Event Parse ()
-> IO (Either ParseException ([Warning], Either FilePath [a]))
forall a.
FromJSON a =>
ConduitM () Event Parse ()
-> IO (Either ParseException ([Warning], Either FilePath [a]))
decodeAllHelper
(ConduitM () Event Parse ()
-> IO (Either ParseException ([Warning], Either FilePath [a])))
-> (ByteString -> ConduitM () Event Parse ())
-> ByteString
-> IO (Either ParseException ([Warning], Either FilePath [a]))
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> ConduitM () Event Parse ()
forall (m :: * -> *) i.
MonadResource m =>
ByteString -> ConduitM i Event m ()
Y.decode
decodeThrow :: (MonadThrow m, FromJSON a) => ByteString -> m a
decodeThrow :: forall (m :: * -> *) a.
(MonadThrow m, FromJSON a) =>
ByteString -> m a
decodeThrow = (ParseException -> m a)
-> (a -> m a) -> Either ParseException a -> m a
forall a c b. (a -> c) -> (b -> c) -> Either a b -> c
either ParseException -> m a
forall e a. (HasCallStack, Exception e) => e -> m a
forall (m :: * -> *) e a.
(MonadThrow m, HasCallStack, Exception e) =>
e -> m a
throwM a -> m a
forall a. a -> m a
forall (m :: * -> *) a. Monad m => a -> m a
return (Either ParseException a -> m a)
-> (ByteString -> Either ParseException a) -> ByteString -> m a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> Either ParseException a
forall a. FromJSON a => ByteString -> Either ParseException a
decodeEither'
decodeAllThrow :: (MonadThrow m, FromJSON a) => ByteString -> m [a]
decodeAllThrow :: forall (m :: * -> *) a.
(MonadThrow m, FromJSON a) =>
ByteString -> m [a]
decodeAllThrow = (ParseException -> m [a])
-> ([a] -> m [a]) -> Either ParseException [a] -> m [a]
forall a c b. (a -> c) -> (b -> c) -> Either a b -> c
either ParseException -> m [a]
forall e a. (HasCallStack, Exception e) => e -> m a
forall (m :: * -> *) e a.
(MonadThrow m, HasCallStack, Exception e) =>
e -> m a
throwM [a] -> m [a]
forall a. a -> m a
forall (m :: * -> *) a. Monad m => a -> m a
return (Either ParseException [a] -> m [a])
-> (ByteString -> Either ParseException [a]) -> ByteString -> m [a]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> Either ParseException [a]
forall a. FromJSON a => ByteString -> Either ParseException [a]
decodeAllEither'
decodeFileThrow :: (MonadIO m, FromJSON a) => FilePath -> m a
decodeFileThrow :: forall (m :: * -> *) a. (MonadIO m, FromJSON a) => FilePath -> m a
decodeFileThrow FilePath
f = IO a -> m a
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO a -> m a) -> IO a -> m a
forall a b. (a -> b) -> a -> b
$ FilePath -> IO (Either ParseException a)
forall a. FromJSON a => FilePath -> IO (Either ParseException a)
decodeFileEither FilePath
f IO (Either ParseException a)
-> (Either ParseException a -> IO a) -> IO a
forall a b. IO a -> (a -> IO b) -> IO b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= (ParseException -> IO a)
-> (a -> IO a) -> Either ParseException a -> IO a
forall a c b. (a -> c) -> (b -> c) -> Either a b -> c
either ParseException -> IO a
forall e a. Exception e => e -> IO a
throwIO a -> IO a
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return
decodeAllFileThrow :: (MonadIO m, FromJSON a) => FilePath -> m [a]
decodeAllFileThrow :: forall (m :: * -> *) a.
(MonadIO m, FromJSON a) =>
FilePath -> m [a]
decodeAllFileThrow FilePath
f = IO [a] -> m [a]
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO [a] -> m [a]) -> IO [a] -> m [a]
forall a b. (a -> b) -> a -> b
$ FilePath -> IO (Either ParseException [a])
forall a. FromJSON a => FilePath -> IO (Either ParseException [a])
decodeAllFileEither FilePath
f IO (Either ParseException [a])
-> (Either ParseException [a] -> IO [a]) -> IO [a]
forall a b. IO a -> (a -> IO b) -> IO b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= (ParseException -> IO [a])
-> ([a] -> IO [a]) -> Either ParseException [a] -> IO [a]
forall a c b. (a -> c) -> (b -> c) -> Either a b -> c
either ParseException -> IO [a]
forall e a. Exception e => e -> IO a
throwIO [a] -> IO [a]
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return
array :: [Value] -> Value
array :: [Value] -> Value
array = Array -> Value
Array (Array -> Value) -> ([Value] -> Array) -> [Value] -> Value
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Value] -> Array
forall a. [a] -> Vector a
V.fromList
#if MIN_VERSION_base(4, 13, 0)
parseMonad :: MonadFail m => (a -> Parser b) -> a -> m b
#else
parseMonad :: Monad m => (a -> Parser b) -> a -> m b
#endif
parseMonad :: forall (m :: * -> *) a b.
MonadFail m =>
(a -> Parser b) -> a -> m b
parseMonad a -> Parser b
p = (FilePath -> m b) -> (b -> m b) -> Either FilePath b -> m b
forall a c b. (a -> c) -> (b -> c) -> Either a b -> c
either FilePath -> m b
forall a. FilePath -> m a
forall (m :: * -> *) a. MonadFail m => FilePath -> m a
fail b -> m b
forall a. a -> m a
forall (m :: * -> *) a. Monad m => a -> m a
return (Either FilePath b -> m b) -> (a -> Either FilePath b) -> a -> m b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (a -> Parser b) -> a -> Either FilePath b
forall a b. (a -> Parser b) -> a -> Either FilePath b
parseEither a -> Parser b
p
{-# DEPRECATED parseMonad "With the MonadFail split, this function is going to be removed in the future. Please migrate to parseEither." #-}