{-# 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
, 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
)
#if MIN_VERSION_aeson(1,0,0)
import Data.Aeson.Text (encodeToTextBuilder)
#else
import Data.Aeson.Encode (encodeToTextBuilder)
#endif
import Data.Aeson.Types (Pair, parseMaybe, parseEither, Parser)
import Data.ByteString (ByteString)
import Data.Conduit ((.|), runConduitRes)
import qualified Data.Conduit.List as CL
import qualified Data.HashMap.Strict as M
import qualified Data.HashSet as HashSet
import Data.Text.Encoding (encodeUtf8)
import qualified Data.Text as T
import qualified Data.Text.Encoding as TE
import qualified Data.Text.Lazy as TL
import Data.Text.Lazy.Builder (toLazyText)
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
data EncodeOptions = EncodeOptions
{ encodeOptionsStringStyle :: Text -> ( Tag, Style )
, encodeOptionsFormat :: FormatOptions
}
setStringStyle :: (Text -> ( Tag, Style )) -> EncodeOptions -> EncodeOptions
setStringStyle s opts = opts { encodeOptionsStringStyle = s }
setFormat :: FormatOptions -> EncodeOptions -> EncodeOptions
setFormat f opts = opts { encodeOptionsFormat = f }
isSpecialString :: Text -> Bool
isSpecialString s = s `HashSet.member` specialStrings || isNumeric s
defaultEncodeOptions :: EncodeOptions
defaultEncodeOptions = EncodeOptions
{ encodeOptionsStringStyle = \s ->
case () of
()
| "\n" `T.isInfixOf` s -> ( NoTag, Literal )
| isSpecialString s -> ( NoTag, SingleQuoted )
| otherwise -> ( StrTag, PlainNoTag )
, encodeOptionsFormat = defaultFormatOptions
}
encode :: ToJSON a => a -> ByteString
encode = encodeWith defaultEncodeOptions
encodeWith :: ToJSON a => EncodeOptions -> a -> ByteString
encodeWith opts obj = unsafePerformIO $ runConduitRes
$ CL.sourceList (objToEvents 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 (objToEvents opts $ toJSON obj)
.| Y.encodeFileWith (encodeOptionsFormat opts) fp
objToEvents :: EncodeOptions -> Value -> [Y.Event]
objToEvents opts o = (:) EventStreamStart
. (:) EventDocumentStart
$ objToEvents' o
[ EventDocumentEnd
, EventStreamEnd
]
where
objToEvents' :: Value -> [Y.Event] -> [Y.Event]
objToEvents' (Array list) rest =
EventSequenceStart NoTag AnySequence Nothing
: foldr objToEvents' (EventSequenceEnd : rest) (V.toList list)
objToEvents' (Object pairs) rest =
EventMappingStart NoTag AnyMapping Nothing
: foldr pairToEvents (EventMappingEnd : rest) (M.toList pairs)
objToEvents' (String "") rest = EventScalar "" NoTag SingleQuoted Nothing : rest
objToEvents' (String s) rest = EventScalar (encodeUtf8 s) tag style Nothing : rest
where
( tag, style ) = encodeOptionsStringStyle opts s
objToEvents' Null rest = EventScalar "null" NullTag PlainNoTag Nothing : rest
objToEvents' (Bool True) rest = EventScalar "true" BoolTag PlainNoTag Nothing : rest
objToEvents' (Bool False) rest = EventScalar "false" BoolTag PlainNoTag Nothing : rest
objToEvents' n@Number{} rest = EventScalar (TE.encodeUtf8 $ TL.toStrict $ toLazyText $ encodeToTextBuilder n) IntTag PlainNoTag Nothing : rest
pairToEvents :: Pair -> [Y.Event] -> [Y.Event]
pairToEvents (k, v) = objToEvents' (String k) . objToEvents' v
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
parseMonad :: Monad m => (a -> Parser b) -> a -> m b
parseMonad p = either fail return . parseEither p