{-# LANGUAGE CPP #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE OverloadedStrings #-}

-- | Provides a high-level interface for processing YAML files.
--
-- This module reuses most of the infrastructure from the @aeson@ package.
-- This means that you can use all of the existing tools for JSON
-- processing for processing YAML files. As a result, much of the
-- documentation below mentions JSON; do not let that confuse you, it's
-- intentional.
--
-- For the most part, YAML content translates directly into JSON, and
-- therefore there is very little data loss. If you need to deal with YAML
-- more directly (e.g., directly deal with aliases), you should use the
-- "Text.Libyaml" module instead.
--
-- For documentation on the @aeson@ types, functions, classes, and
-- operators, please see the @Data.Aeson@ module of the @aeson@ package.
--
-- Look in the examples directory of the source repository for some initial
-- pointers on how to use this library.

#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
    ( -- * Encoding
      encode
    , encodeWith
    , encodeFile
    , encodeFileWith
      -- * Decoding
    , decodeEither'
    , decodeFileEither
    , decodeFileWithWarnings
    , decodeThrow
    , decodeFileThrow
      -- ** Decoding multiple documents
      --
      -- | For situations where we need to be able to parse multiple documents
      -- separated by `---` in a YAML stream, these functions decode a list of
      -- values rather than a single value.
    , decodeAllEither'
    , decodeAllFileEither
    , decodeAllFileWithWarnings
    , decodeAllThrow
    , decodeAllFileThrow
      -- ** More control over decoding
    , decodeHelper
      -- * Types
    , Value (..)
    , Parser
    , Object
    , Array
    , ParseException(..)
    , prettyPrintParseException
    , YamlException (..)
    , YamlMark (..)
      -- * Constructors and accessors
    , object
    , array
    , (.=)
    , (.:)
    , (.:?)
    , (.!=)
      -- ** With helpers (since 0.8.23)
    , withObject
    , withText
    , withArray
    , withScientific
    , withBool
      -- * Parsing
    , parseMonad
    , parseEither
    , parseMaybe
      -- * Classes
    , ToJSON (..)
    , FromJSON (..)
      -- * Custom encoding
    , isSpecialString
    , EncodeOptions
    , defaultEncodeOptions
    , defaultStringStyle
    , setStringStyle
    , setFormat
    , FormatOptions
    , defaultFormatOptions
    , setWidth
    ) where
#if !MIN_VERSION_base(4,8,0)
import Control.Applicative((<$>))
#endif
import Control.Monad.IO.Class (MonadIO, liftIO)
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 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

import Control.Exception.Safe

import qualified Streamly.Data.Stream as S

-- | Set the string style in the encoded YAML. This is a function that decides
-- for each string the type of YAML string to output.
--
-- __WARNING__: You must ensure that special strings (like @"yes"@\/@"no"@\/@"null"@\/@"1234"@) are not encoded with the 'Plain' style, because
-- then they will be decoded as boolean, null or numeric values. You can use 'isSpecialString' to detect them.
--
-- By default, strings are encoded as follows:
--
-- * Any string containing a newline character uses the 'Literal' style
--
-- * Otherwise, any special string (see 'isSpecialString') uses 'SingleQuoted'
--
-- * Otherwise, use 'Plain'
--
-- @since 0.10.2.0
setStringStyle :: (Text -> ( Tag, Style )) -> EncodeOptions -> EncodeOptions
setStringStyle :: (Text -> (Tag, Style)) -> EncodeOptions -> EncodeOptions
setStringStyle Text -> (Tag, Style)
s EncodeOptions
opts = EncodeOptions
opts { encodeOptionsStringStyle = s }

-- | Set the encoding formatting for the encoded YAML. By default, this is `defaultFormatOptions`.
--
-- @since 0.10.2.0
setFormat :: FormatOptions -> EncodeOptions -> EncodeOptions
setFormat :: FormatOptions -> EncodeOptions -> EncodeOptions
setFormat FormatOptions
f EncodeOptions
opts = EncodeOptions
opts { encodeOptionsFormat = f }

-- |
-- @since 0.10.2.0
data EncodeOptions = EncodeOptions
  { EncodeOptions -> Text -> (Tag, Style)
encodeOptionsStringStyle :: Text -> ( Tag, Style )
  , EncodeOptions -> FormatOptions
encodeOptionsFormat :: FormatOptions
  }

-- |
-- @since 0.10.2.0
defaultEncodeOptions :: EncodeOptions
defaultEncodeOptions :: EncodeOptions
defaultEncodeOptions = EncodeOptions
  { encodeOptionsStringStyle :: Text -> (Tag, Style)
encodeOptionsStringStyle = Text -> (Tag, Style)
defaultStringStyle
  , encodeOptionsFormat :: FormatOptions
encodeOptionsFormat = FormatOptions
defaultFormatOptions
  }

-- | Encode a value into its YAML representation.
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

-- | Encode a value into its YAML representation with custom styling.
--
-- @since 0.10.2.0
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
$ FormatOptions -> Stream IO Event -> IO ByteString
forall (m :: * -> *).
(MonadCatch m, MonadIO m, MonadMask m) =>
FormatOptions -> Stream m Event -> m ByteString
Y.encodeWith (EncodeOptions -> FormatOptions
encodeOptionsFormat EncodeOptions
opts) ([Event] -> Stream IO Event
forall (m :: * -> *) a. Applicative m => [a] -> Stream m a
S.fromList ([Event] -> Stream IO Event) -> [Event] -> Stream IO Event
forall a b. (a -> b) -> a -> b
$ (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)

-- | Encode a value into its YAML representation and save to the given file.
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

-- | Encode a value into its YAML representation with custom styling and save to the given file.
--
-- @since 0.10.2.0
encodeFileWith :: ToJSON a => EncodeOptions -> FilePath -> a -> IO ()
encodeFileWith :: forall a. ToJSON a => EncodeOptions -> FilePath -> a -> IO ()
encodeFileWith EncodeOptions
opts FilePath
fp a
obj = FormatOptions -> FilePath -> Stream IO Event -> IO ()
forall (m :: * -> *).
(MonadCatch m, MonadIO m, MonadMask m) =>
FormatOptions -> FilePath -> Stream m Event -> m ()
Y.encodeFileWith (EncodeOptions -> FormatOptions
encodeOptionsFormat EncodeOptions
opts) FilePath
fp ([Event] -> Stream IO Event
forall (m :: * -> *) a. Applicative m => [a] -> Stream m a
S.fromList ([Event] -> Stream IO Event) -> [Event] -> Stream IO Event
forall a b. (a -> b) -> a -> b
$ (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)

-- | A version of 'decodeFile' which should not throw runtime exceptions.
--
-- @since 0.8.4
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

-- | Like `decodeFileEither`, but decode multiple documents.
--
-- @since 0.11.5.0
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

-- | A version of `decodeFileEither` that returns warnings along with the parse
-- result.
--
-- @since 0.10.0
decodeFileWithWarnings
    :: FromJSON a
    => FilePath
    -> IO (Either ParseException ([Warning], a))
decodeFileWithWarnings :: forall a.
FromJSON a =>
FilePath -> IO (Either ParseException ([Warning], a))
decodeFileWithWarnings = Stream IO Event -> IO (Either ParseException ([Warning], a))
forall a.
FromJSON a =>
Stream IO Event -> IO (Either ParseException ([Warning], a))
decodeHelper_ (Stream IO Event -> IO (Either ParseException ([Warning], a)))
-> (FilePath -> Stream IO Event)
-> FilePath
-> IO (Either ParseException ([Warning], a))
forall b c a. (b -> c) -> (a -> b) -> a -> c
. FilePath -> Stream IO Event
forall (m :: * -> *).
(MonadCatch m, MonadIO m, MonadMask m) =>
FilePath -> Stream m Event
Y.decodeFile

-- | Like `decodeFileWithWarnings`, but decode multiple documents.
--
-- @since 0.11.5.0
decodeAllFileWithWarnings
    :: FromJSON a
    => FilePath
    -> IO (Either ParseException ([Warning], [a]))
decodeAllFileWithWarnings :: forall a.
FromJSON a =>
FilePath -> IO (Either ParseException ([Warning], [a]))
decodeAllFileWithWarnings = Stream IO Event -> IO (Either ParseException ([Warning], [a]))
forall a.
FromJSON a =>
Stream IO Event -> IO (Either ParseException ([Warning], [a]))
decodeAllHelper_ (Stream IO Event -> IO (Either ParseException ([Warning], [a])))
-> (FilePath -> Stream IO Event)
-> FilePath
-> IO (Either ParseException ([Warning], [a]))
forall b c a. (b -> c) -> (a -> b) -> a -> c
. FilePath -> Stream IO Event
forall (m :: * -> *).
(MonadCatch m, MonadIO m, MonadMask m) =>
FilePath -> Stream m Event
Y.decodeFile


-- | More helpful version of 'decodeEither' which returns the 'YamlException'.
--
-- @since 0.8.3
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
. Stream IO Event
-> IO (Either ParseException ([Warning], Either FilePath a))
forall a.
FromJSON a =>
Stream IO Event
-> IO (Either ParseException ([Warning], Either FilePath a))
decodeHelper
              (Stream IO Event
 -> IO (Either ParseException ([Warning], Either FilePath a)))
-> (ByteString -> Stream IO Event)
-> ByteString
-> IO (Either ParseException ([Warning], Either FilePath a))
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> Stream IO Event
forall (m :: * -> *).
(MonadCatch m, MonadIO m, MonadMask m) =>
ByteString -> Stream m Event
Y.decode

-- | Like 'decodeEither'', but decode multiple documents.
--
-- @since 0.11.5.0
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
. Stream IO Event
-> IO (Either ParseException ([Warning], Either FilePath [a]))
forall a.
FromJSON a =>
Stream IO Event
-> IO (Either ParseException ([Warning], Either FilePath [a]))
decodeAllHelper
                 (Stream IO Event
 -> IO (Either ParseException ([Warning], Either FilePath [a])))
-> (ByteString -> Stream IO Event)
-> ByteString
-> IO (Either ParseException ([Warning], Either FilePath [a]))
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> Stream IO Event
forall (m :: * -> *).
(MonadCatch m, MonadIO m, MonadMask m) =>
ByteString -> Stream m Event
Y.decode

-- | A version of 'decodeEither'' lifted to MonadThrow
--
-- @since 0.8.31
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 (m :: * -> *) e a.
(HasCallStack, MonadThrow m, 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'

-- | Like `decodeThrow`, but decode multiple documents.
--
-- @since 0.11.5.0
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 (m :: * -> *) e a.
(HasCallStack, MonadThrow m, 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'

-- | A version of 'decodeFileEither' lifted to MonadIO
--
-- @since 0.8.31
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 (m :: * -> *) e a.
(HasCallStack, MonadThrow m, Exception e) =>
e -> m a
throwIO a -> IO a
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return

-- | Like `decodeFileThrow`, but decode multiple documents.
--
-- @since 0.11.5.0
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 (m :: * -> *) e a.
(HasCallStack, MonadThrow m, Exception e) =>
e -> m a
throwIO [a] -> IO [a]
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return

-- | Construct a new 'Value' from a list of 'Value's.
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." #-}