{-# 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
      
    , 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 s opts = opts { encodeOptionsStringStyle = s }
setFormat :: FormatOptions -> EncodeOptions -> EncodeOptions
setFormat f opts = opts { encodeOptionsFormat = f }
data EncodeOptions = EncodeOptions
  { encodeOptionsStringStyle :: Text -> ( Tag, Style )
  , encodeOptionsFormat :: FormatOptions
  }
defaultEncodeOptions :: EncodeOptions
defaultEncodeOptions = EncodeOptions
  { encodeOptionsStringStyle = defaultStringStyle
  , encodeOptionsFormat = defaultFormatOptions
  }
encode :: ToJSON a => a -> ByteString
encode = encodeWith defaultEncodeOptions
encodeWith :: ToJSON a => EncodeOptions -> a -> ByteString
encodeWith opts obj = unsafePerformIO $ runConduitRes
    $ CL.sourceList (objToStream (encodeOptionsStringStyle opts) $ toJSON obj)
   .| Y.encodeWith (encodeOptionsFormat opts)
encodeFile :: ToJSON a => FilePath -> a -> IO ()
encodeFile = encodeFileWith defaultEncodeOptions
encodeFileWith :: ToJSON a => EncodeOptions -> FilePath -> a -> IO ()
encodeFileWith opts fp obj = runConduitRes
    $ CL.sourceList (objToStream (encodeOptionsStringStyle opts) $ toJSON obj)
   .| Y.encodeFileWith (encodeOptionsFormat opts) fp
decode :: FromJSON a
       => ByteString
       -> Maybe a
decode bs = unsafePerformIO
          $ either (const Nothing) snd
          <$> decodeHelper_ (Y.decode bs)
{-# DEPRECATED decode "Please use decodeEither or decodeThrow, which provide information on how the decode failed" #-}
decodeFile :: FromJSON a
           => FilePath
           -> IO (Maybe a)
decodeFile fp = (fmap snd <$> decodeHelper (Y.decodeFile fp)) >>= either throwIO (return . either (const Nothing) id)
{-# DEPRECATED decodeFile "Please use decodeFileEither, which does not confused type-directed and runtime exceptions." #-}
decodeFileEither
    :: FromJSON a
    => FilePath
    -> IO (Either ParseException a)
decodeFileEither = fmap (fmap snd) . decodeFileWithWarnings
decodeFileWithWarnings
    :: FromJSON a
    => FilePath
    -> IO (Either ParseException ([Warning], a))
decodeFileWithWarnings = decodeHelper_ . Y.decodeFile
decodeEither :: FromJSON a => ByteString -> Either String a
decodeEither bs = unsafePerformIO
                $ either (Left . prettyPrintParseException) id
                <$> (fmap snd <$> decodeHelper (Y.decode bs))
{-# DEPRECATED decodeEither "Please use decodeEither' or decodeThrow, which provide more useful failures" #-}
decodeEither' :: FromJSON a => ByteString -> Either ParseException a
decodeEither' = either Left (either (Left . AesonException) Right)
              . unsafePerformIO
              . fmap (fmap snd) . decodeHelper
              . Y.decode
decodeThrow :: (MonadThrow m, FromJSON a) => ByteString -> m a
decodeThrow = either throwM return . decodeEither'
decodeFileThrow :: (MonadIO m, FromJSON a) => FilePath -> m a
decodeFileThrow f = liftIO $ decodeFileEither f >>= either throwIO return
array :: [Value] -> Value
array = Array . 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 p = either fail return . parseEither p
{-# DEPRECATED parseMonad "With the MonadFail split, this function is going to be removed in the future. Please migrate to parseEither." #-}