{-# LANGUAGE EmptyDataDecls #-}
{-# LANGUAGE ForeignFunctionInterface #-}
{-# LANGUAGE DeriveDataTypeable #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE CPP #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE ScopedTypeVariables #-}

-- | Low-level, streaming YAML interface. For a higher-level interface, see
-- "Data.Yaml".
module Text.Libyaml
    ( -- * The event stream
      MarkedEvent(..)
    , Event (..)
    , Style (..)
    , SequenceStyle (..)
    , MappingStyle (..)
    , Tag (..)
    , AnchorName
    , Anchor
      -- * Encoding and decoding
    , encode
    , encodeWith
    , decode
    , decodeMarked
    , encodeFile
    , decodeFile
    , decodeFileMarked
    , encodeFileWith
    , FormatOptions
    , defaultFormatOptions
    , setWidth
    , setTagRendering
    , renderScalarTags
    , renderAllTags
    , renderNoTags
    , renderUriTags
      -- * Error handling
    , YamlException (..)
    , YamlMark (..)
    ) where

import Prelude hiding (pi)

import Data.Bits ((.|.))
import Foreign.C
import Foreign.Ptr
import Foreign.ForeignPtr
#if MIN_VERSION_base(4,7,0)
import Foreign.ForeignPtr.Unsafe
#endif
import Foreign.Marshal.Alloc
import qualified System.Posix.Internals as Posix

#if !MIN_VERSION_base(4,8,0)
import Control.Applicative
#endif
import Control.Exception (mask_, throwIO, Exception, finally)
import Control.Monad
import Control.Monad.IO.Class
import Control.Monad.Trans.Resource
import Data.Conduit hiding (Source, Sink, Conduit)
import Data.Data

import Data.ByteString (ByteString, packCString, packCStringLen)
import qualified Data.ByteString.Char8 as B8
import qualified Data.ByteString.Internal as B
import qualified Data.ByteString.Unsafe as BU

#if WINDOWS && __GLASGOW_HASKELL__ >= 806
import System.Directory (removeFile)
import qualified Control.Exception
#endif

data Event =
      EventStreamStart
    | EventStreamEnd
    | EventDocumentStart
    | EventDocumentEnd
    | EventAlias !AnchorName
    | EventScalar !ByteString !Tag !Style !Anchor
    | EventSequenceStart !Tag !SequenceStyle !Anchor
    | EventSequenceEnd
    | EventMappingStart !Tag !MappingStyle !Anchor
    | EventMappingEnd
    deriving (Int -> Event -> ShowS
[Event] -> ShowS
Event -> String
(Int -> Event -> ShowS)
-> (Event -> String) -> ([Event] -> ShowS) -> Show Event
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Event] -> ShowS
$cshowList :: [Event] -> ShowS
show :: Event -> String
$cshow :: Event -> String
showsPrec :: Int -> Event -> ShowS
$cshowsPrec :: Int -> Event -> ShowS
Show, Event -> Event -> Bool
(Event -> Event -> Bool) -> (Event -> Event -> Bool) -> Eq Event
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Event -> Event -> Bool
$c/= :: Event -> Event -> Bool
== :: Event -> Event -> Bool
$c== :: Event -> Event -> Bool
Eq)

-- | Event with start and end marks.
--
-- @since 0.10.4.0
data MarkedEvent = MarkedEvent
    { MarkedEvent -> Event
yamlEvent     :: Event
    , MarkedEvent -> YamlMark
yamlStartMark :: YamlMark
    , MarkedEvent -> YamlMark
yamlEndMark   :: YamlMark
    }

-- | Style for scalars - e.g. quoted / folded
-- 
data Style = Any
           | Plain
           | SingleQuoted
           | DoubleQuoted
           | Literal
           | Folded
           | PlainNoTag
    deriving (Int -> Style -> ShowS
[Style] -> ShowS
Style -> String
(Int -> Style -> ShowS)
-> (Style -> String) -> ([Style] -> ShowS) -> Show Style
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Style] -> ShowS
$cshowList :: [Style] -> ShowS
show :: Style -> String
$cshow :: Style -> String
showsPrec :: Int -> Style -> ShowS
$cshowsPrec :: Int -> Style -> ShowS
Show, ReadPrec [Style]
ReadPrec Style
Int -> ReadS Style
ReadS [Style]
(Int -> ReadS Style)
-> ReadS [Style]
-> ReadPrec Style
-> ReadPrec [Style]
-> Read Style
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [Style]
$creadListPrec :: ReadPrec [Style]
readPrec :: ReadPrec Style
$creadPrec :: ReadPrec Style
readList :: ReadS [Style]
$creadList :: ReadS [Style]
readsPrec :: Int -> ReadS Style
$creadsPrec :: Int -> ReadS Style
Read, Style -> Style -> Bool
(Style -> Style -> Bool) -> (Style -> Style -> Bool) -> Eq Style
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Style -> Style -> Bool
$c/= :: Style -> Style -> Bool
== :: Style -> Style -> Bool
$c== :: Style -> Style -> Bool
Eq, Int -> Style
Style -> Int
Style -> [Style]
Style -> Style
Style -> Style -> [Style]
Style -> Style -> Style -> [Style]
(Style -> Style)
-> (Style -> Style)
-> (Int -> Style)
-> (Style -> Int)
-> (Style -> [Style])
-> (Style -> Style -> [Style])
-> (Style -> Style -> [Style])
-> (Style -> Style -> Style -> [Style])
-> Enum Style
forall a.
(a -> a)
-> (a -> a)
-> (Int -> a)
-> (a -> Int)
-> (a -> [a])
-> (a -> a -> [a])
-> (a -> a -> [a])
-> (a -> a -> a -> [a])
-> Enum a
enumFromThenTo :: Style -> Style -> Style -> [Style]
$cenumFromThenTo :: Style -> Style -> Style -> [Style]
enumFromTo :: Style -> Style -> [Style]
$cenumFromTo :: Style -> Style -> [Style]
enumFromThen :: Style -> Style -> [Style]
$cenumFromThen :: Style -> Style -> [Style]
enumFrom :: Style -> [Style]
$cenumFrom :: Style -> [Style]
fromEnum :: Style -> Int
$cfromEnum :: Style -> Int
toEnum :: Int -> Style
$ctoEnum :: Int -> Style
pred :: Style -> Style
$cpred :: Style -> Style
succ :: Style -> Style
$csucc :: Style -> Style
Enum, Style
Style -> Style -> Bounded Style
forall a. a -> a -> Bounded a
maxBound :: Style
$cmaxBound :: Style
minBound :: Style
$cminBound :: Style
Bounded, Eq Style
Eq Style =>
(Style -> Style -> Ordering)
-> (Style -> Style -> Bool)
-> (Style -> Style -> Bool)
-> (Style -> Style -> Bool)
-> (Style -> Style -> Bool)
-> (Style -> Style -> Style)
-> (Style -> Style -> Style)
-> Ord Style
Style -> Style -> Bool
Style -> Style -> Ordering
Style -> Style -> Style
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: Style -> Style -> Style
$cmin :: Style -> Style -> Style
max :: Style -> Style -> Style
$cmax :: Style -> Style -> Style
>= :: Style -> Style -> Bool
$c>= :: Style -> Style -> Bool
> :: Style -> Style -> Bool
$c> :: Style -> Style -> Bool
<= :: Style -> Style -> Bool
$c<= :: Style -> Style -> Bool
< :: Style -> Style -> Bool
$c< :: Style -> Style -> Bool
compare :: Style -> Style -> Ordering
$ccompare :: Style -> Style -> Ordering
$cp1Ord :: Eq Style
Ord, Typeable Style
DataType
Constr
Typeable Style =>
(forall (c :: * -> *).
 (forall d b. Data d => c (d -> b) -> d -> c b)
 -> (forall g. g -> c g) -> Style -> c Style)
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c Style)
-> (Style -> Constr)
-> (Style -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
    Typeable t =>
    (forall d. Data d => c (t d)) -> Maybe (c Style))
-> (forall (t :: * -> * -> *) (c :: * -> *).
    Typeable t =>
    (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Style))
-> ((forall b. Data b => b -> b) -> Style -> Style)
-> (forall r r'.
    (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Style -> r)
-> (forall r r'.
    (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Style -> r)
-> (forall u. (forall d. Data d => d -> u) -> Style -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> Style -> u)
-> (forall (m :: * -> *).
    Monad m =>
    (forall d. Data d => d -> m d) -> Style -> m Style)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> Style -> m Style)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> Style -> m Style)
-> Data Style
Style -> DataType
Style -> Constr
(forall b. Data b => b -> b) -> Style -> Style
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Style -> c Style
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Style
forall a.
Typeable a =>
(forall (c :: * -> *).
 (forall d b. Data d => c (d -> b) -> d -> c b)
 -> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
    Typeable t =>
    (forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
    Typeable t =>
    (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
    (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
    (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
    Monad m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u. Int -> (forall d. Data d => d -> u) -> Style -> u
forall u. (forall d. Data d => d -> u) -> Style -> [u]
forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Style -> r
forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Style -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Style -> m Style
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Style -> m Style
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Style
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Style -> c Style
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Style)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Style)
$cPlainNoTag :: Constr
$cFolded :: Constr
$cLiteral :: Constr
$cDoubleQuoted :: Constr
$cSingleQuoted :: Constr
$cPlain :: Constr
$cAny :: Constr
$tStyle :: DataType
gmapMo :: (forall d. Data d => d -> m d) -> Style -> m Style
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Style -> m Style
gmapMp :: (forall d. Data d => d -> m d) -> Style -> m Style
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Style -> m Style
gmapM :: (forall d. Data d => d -> m d) -> Style -> m Style
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Style -> m Style
gmapQi :: Int -> (forall d. Data d => d -> u) -> Style -> u
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Style -> u
gmapQ :: (forall d. Data d => d -> u) -> Style -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> Style -> [u]
gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Style -> r
$cgmapQr :: forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Style -> r
gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Style -> r
$cgmapQl :: forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Style -> r
gmapT :: (forall b. Data b => b -> b) -> Style -> Style
$cgmapT :: (forall b. Data b => b -> b) -> Style -> Style
dataCast2 :: (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Style)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Style)
dataCast1 :: (forall d. Data d => c (t d)) -> Maybe (c Style)
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Style)
dataTypeOf :: Style -> DataType
$cdataTypeOf :: Style -> DataType
toConstr :: Style -> Constr
$ctoConstr :: Style -> Constr
gunfold :: (forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Style
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Style
gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Style -> c Style
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Style -> c Style
$cp1Data :: Typeable Style
Data, Typeable)

-- | Style for sequences - e.g. block or flow
-- 
-- @since 0.9.0
data SequenceStyle = AnySequence | BlockSequence | FlowSequence
    deriving (Int -> SequenceStyle -> ShowS
[SequenceStyle] -> ShowS
SequenceStyle -> String
(Int -> SequenceStyle -> ShowS)
-> (SequenceStyle -> String)
-> ([SequenceStyle] -> ShowS)
-> Show SequenceStyle
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [SequenceStyle] -> ShowS
$cshowList :: [SequenceStyle] -> ShowS
show :: SequenceStyle -> String
$cshow :: SequenceStyle -> String
showsPrec :: Int -> SequenceStyle -> ShowS
$cshowsPrec :: Int -> SequenceStyle -> ShowS
Show, SequenceStyle -> SequenceStyle -> Bool
(SequenceStyle -> SequenceStyle -> Bool)
-> (SequenceStyle -> SequenceStyle -> Bool) -> Eq SequenceStyle
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SequenceStyle -> SequenceStyle -> Bool
$c/= :: SequenceStyle -> SequenceStyle -> Bool
== :: SequenceStyle -> SequenceStyle -> Bool
$c== :: SequenceStyle -> SequenceStyle -> Bool
Eq, Int -> SequenceStyle
SequenceStyle -> Int
SequenceStyle -> [SequenceStyle]
SequenceStyle -> SequenceStyle
SequenceStyle -> SequenceStyle -> [SequenceStyle]
SequenceStyle -> SequenceStyle -> SequenceStyle -> [SequenceStyle]
(SequenceStyle -> SequenceStyle)
-> (SequenceStyle -> SequenceStyle)
-> (Int -> SequenceStyle)
-> (SequenceStyle -> Int)
-> (SequenceStyle -> [SequenceStyle])
-> (SequenceStyle -> SequenceStyle -> [SequenceStyle])
-> (SequenceStyle -> SequenceStyle -> [SequenceStyle])
-> (SequenceStyle
    -> SequenceStyle -> SequenceStyle -> [SequenceStyle])
-> Enum SequenceStyle
forall a.
(a -> a)
-> (a -> a)
-> (Int -> a)
-> (a -> Int)
-> (a -> [a])
-> (a -> a -> [a])
-> (a -> a -> [a])
-> (a -> a -> a -> [a])
-> Enum a
enumFromThenTo :: SequenceStyle -> SequenceStyle -> SequenceStyle -> [SequenceStyle]
$cenumFromThenTo :: SequenceStyle -> SequenceStyle -> SequenceStyle -> [SequenceStyle]
enumFromTo :: SequenceStyle -> SequenceStyle -> [SequenceStyle]
$cenumFromTo :: SequenceStyle -> SequenceStyle -> [SequenceStyle]
enumFromThen :: SequenceStyle -> SequenceStyle -> [SequenceStyle]
$cenumFromThen :: SequenceStyle -> SequenceStyle -> [SequenceStyle]
enumFrom :: SequenceStyle -> [SequenceStyle]
$cenumFrom :: SequenceStyle -> [SequenceStyle]
fromEnum :: SequenceStyle -> Int
$cfromEnum :: SequenceStyle -> Int
toEnum :: Int -> SequenceStyle
$ctoEnum :: Int -> SequenceStyle
pred :: SequenceStyle -> SequenceStyle
$cpred :: SequenceStyle -> SequenceStyle
succ :: SequenceStyle -> SequenceStyle
$csucc :: SequenceStyle -> SequenceStyle
Enum, SequenceStyle
SequenceStyle -> SequenceStyle -> Bounded SequenceStyle
forall a. a -> a -> Bounded a
maxBound :: SequenceStyle
$cmaxBound :: SequenceStyle
minBound :: SequenceStyle
$cminBound :: SequenceStyle
Bounded, Eq SequenceStyle
Eq SequenceStyle =>
(SequenceStyle -> SequenceStyle -> Ordering)
-> (SequenceStyle -> SequenceStyle -> Bool)
-> (SequenceStyle -> SequenceStyle -> Bool)
-> (SequenceStyle -> SequenceStyle -> Bool)
-> (SequenceStyle -> SequenceStyle -> Bool)
-> (SequenceStyle -> SequenceStyle -> SequenceStyle)
-> (SequenceStyle -> SequenceStyle -> SequenceStyle)
-> Ord SequenceStyle
SequenceStyle -> SequenceStyle -> Bool
SequenceStyle -> SequenceStyle -> Ordering
SequenceStyle -> SequenceStyle -> SequenceStyle
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: SequenceStyle -> SequenceStyle -> SequenceStyle
$cmin :: SequenceStyle -> SequenceStyle -> SequenceStyle
max :: SequenceStyle -> SequenceStyle -> SequenceStyle
$cmax :: SequenceStyle -> SequenceStyle -> SequenceStyle
>= :: SequenceStyle -> SequenceStyle -> Bool
$c>= :: SequenceStyle -> SequenceStyle -> Bool
> :: SequenceStyle -> SequenceStyle -> Bool
$c> :: SequenceStyle -> SequenceStyle -> Bool
<= :: SequenceStyle -> SequenceStyle -> Bool
$c<= :: SequenceStyle -> SequenceStyle -> Bool
< :: SequenceStyle -> SequenceStyle -> Bool
$c< :: SequenceStyle -> SequenceStyle -> Bool
compare :: SequenceStyle -> SequenceStyle -> Ordering
$ccompare :: SequenceStyle -> SequenceStyle -> Ordering
$cp1Ord :: Eq SequenceStyle
Ord, Typeable SequenceStyle
DataType
Constr
Typeable SequenceStyle =>
(forall (c :: * -> *).
 (forall d b. Data d => c (d -> b) -> d -> c b)
 -> (forall g. g -> c g) -> SequenceStyle -> c SequenceStyle)
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c SequenceStyle)
-> (SequenceStyle -> Constr)
-> (SequenceStyle -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
    Typeable t =>
    (forall d. Data d => c (t d)) -> Maybe (c SequenceStyle))
-> (forall (t :: * -> * -> *) (c :: * -> *).
    Typeable t =>
    (forall d e. (Data d, Data e) => c (t d e))
    -> Maybe (c SequenceStyle))
-> ((forall b. Data b => b -> b) -> SequenceStyle -> SequenceStyle)
-> (forall r r'.
    (r -> r' -> r)
    -> r -> (forall d. Data d => d -> r') -> SequenceStyle -> r)
-> (forall r r'.
    (r' -> r -> r)
    -> r -> (forall d. Data d => d -> r') -> SequenceStyle -> r)
-> (forall u. (forall d. Data d => d -> u) -> SequenceStyle -> [u])
-> (forall u.
    Int -> (forall d. Data d => d -> u) -> SequenceStyle -> u)
-> (forall (m :: * -> *).
    Monad m =>
    (forall d. Data d => d -> m d) -> SequenceStyle -> m SequenceStyle)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> SequenceStyle -> m SequenceStyle)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> SequenceStyle -> m SequenceStyle)
-> Data SequenceStyle
SequenceStyle -> DataType
SequenceStyle -> Constr
(forall b. Data b => b -> b) -> SequenceStyle -> SequenceStyle
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> SequenceStyle -> c SequenceStyle
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c SequenceStyle
forall a.
Typeable a =>
(forall (c :: * -> *).
 (forall d b. Data d => c (d -> b) -> d -> c b)
 -> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
    Typeable t =>
    (forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
    Typeable t =>
    (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
    (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
    (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
    Monad m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u. Int -> (forall d. Data d => d -> u) -> SequenceStyle -> u
forall u. (forall d. Data d => d -> u) -> SequenceStyle -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> SequenceStyle -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> SequenceStyle -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> SequenceStyle -> m SequenceStyle
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> SequenceStyle -> m SequenceStyle
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c SequenceStyle
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> SequenceStyle -> c SequenceStyle
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c SequenceStyle)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c SequenceStyle)
$cFlowSequence :: Constr
$cBlockSequence :: Constr
$cAnySequence :: Constr
$tSequenceStyle :: DataType
gmapMo :: (forall d. Data d => d -> m d) -> SequenceStyle -> m SequenceStyle
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> SequenceStyle -> m SequenceStyle
gmapMp :: (forall d. Data d => d -> m d) -> SequenceStyle -> m SequenceStyle
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> SequenceStyle -> m SequenceStyle
gmapM :: (forall d. Data d => d -> m d) -> SequenceStyle -> m SequenceStyle
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> SequenceStyle -> m SequenceStyle
gmapQi :: Int -> (forall d. Data d => d -> u) -> SequenceStyle -> u
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> SequenceStyle -> u
gmapQ :: (forall d. Data d => d -> u) -> SequenceStyle -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> SequenceStyle -> [u]
gmapQr :: (r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> SequenceStyle -> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> SequenceStyle -> r
gmapQl :: (r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> SequenceStyle -> r
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> SequenceStyle -> r
gmapT :: (forall b. Data b => b -> b) -> SequenceStyle -> SequenceStyle
$cgmapT :: (forall b. Data b => b -> b) -> SequenceStyle -> SequenceStyle
dataCast2 :: (forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c SequenceStyle)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c SequenceStyle)
dataCast1 :: (forall d. Data d => c (t d)) -> Maybe (c SequenceStyle)
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c SequenceStyle)
dataTypeOf :: SequenceStyle -> DataType
$cdataTypeOf :: SequenceStyle -> DataType
toConstr :: SequenceStyle -> Constr
$ctoConstr :: SequenceStyle -> Constr
gunfold :: (forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c SequenceStyle
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c SequenceStyle
gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> SequenceStyle -> c SequenceStyle
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> SequenceStyle -> c SequenceStyle
$cp1Data :: Typeable SequenceStyle
Data, Typeable)

-- | Style for mappings - e.g. block or flow
-- 
-- @since 0.9.0
data MappingStyle = AnyMapping | BlockMapping | FlowMapping
    deriving (Int -> MappingStyle -> ShowS
[MappingStyle] -> ShowS
MappingStyle -> String
(Int -> MappingStyle -> ShowS)
-> (MappingStyle -> String)
-> ([MappingStyle] -> ShowS)
-> Show MappingStyle
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [MappingStyle] -> ShowS
$cshowList :: [MappingStyle] -> ShowS
show :: MappingStyle -> String
$cshow :: MappingStyle -> String
showsPrec :: Int -> MappingStyle -> ShowS
$cshowsPrec :: Int -> MappingStyle -> ShowS
Show, MappingStyle -> MappingStyle -> Bool
(MappingStyle -> MappingStyle -> Bool)
-> (MappingStyle -> MappingStyle -> Bool) -> Eq MappingStyle
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: MappingStyle -> MappingStyle -> Bool
$c/= :: MappingStyle -> MappingStyle -> Bool
== :: MappingStyle -> MappingStyle -> Bool
$c== :: MappingStyle -> MappingStyle -> Bool
Eq, Int -> MappingStyle
MappingStyle -> Int
MappingStyle -> [MappingStyle]
MappingStyle -> MappingStyle
MappingStyle -> MappingStyle -> [MappingStyle]
MappingStyle -> MappingStyle -> MappingStyle -> [MappingStyle]
(MappingStyle -> MappingStyle)
-> (MappingStyle -> MappingStyle)
-> (Int -> MappingStyle)
-> (MappingStyle -> Int)
-> (MappingStyle -> [MappingStyle])
-> (MappingStyle -> MappingStyle -> [MappingStyle])
-> (MappingStyle -> MappingStyle -> [MappingStyle])
-> (MappingStyle -> MappingStyle -> MappingStyle -> [MappingStyle])
-> Enum MappingStyle
forall a.
(a -> a)
-> (a -> a)
-> (Int -> a)
-> (a -> Int)
-> (a -> [a])
-> (a -> a -> [a])
-> (a -> a -> [a])
-> (a -> a -> a -> [a])
-> Enum a
enumFromThenTo :: MappingStyle -> MappingStyle -> MappingStyle -> [MappingStyle]
$cenumFromThenTo :: MappingStyle -> MappingStyle -> MappingStyle -> [MappingStyle]
enumFromTo :: MappingStyle -> MappingStyle -> [MappingStyle]
$cenumFromTo :: MappingStyle -> MappingStyle -> [MappingStyle]
enumFromThen :: MappingStyle -> MappingStyle -> [MappingStyle]
$cenumFromThen :: MappingStyle -> MappingStyle -> [MappingStyle]
enumFrom :: MappingStyle -> [MappingStyle]
$cenumFrom :: MappingStyle -> [MappingStyle]
fromEnum :: MappingStyle -> Int
$cfromEnum :: MappingStyle -> Int
toEnum :: Int -> MappingStyle
$ctoEnum :: Int -> MappingStyle
pred :: MappingStyle -> MappingStyle
$cpred :: MappingStyle -> MappingStyle
succ :: MappingStyle -> MappingStyle
$csucc :: MappingStyle -> MappingStyle
Enum, MappingStyle
MappingStyle -> MappingStyle -> Bounded MappingStyle
forall a. a -> a -> Bounded a
maxBound :: MappingStyle
$cmaxBound :: MappingStyle
minBound :: MappingStyle
$cminBound :: MappingStyle
Bounded, Eq MappingStyle
Eq MappingStyle =>
(MappingStyle -> MappingStyle -> Ordering)
-> (MappingStyle -> MappingStyle -> Bool)
-> (MappingStyle -> MappingStyle -> Bool)
-> (MappingStyle -> MappingStyle -> Bool)
-> (MappingStyle -> MappingStyle -> Bool)
-> (MappingStyle -> MappingStyle -> MappingStyle)
-> (MappingStyle -> MappingStyle -> MappingStyle)
-> Ord MappingStyle
MappingStyle -> MappingStyle -> Bool
MappingStyle -> MappingStyle -> Ordering
MappingStyle -> MappingStyle -> MappingStyle
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: MappingStyle -> MappingStyle -> MappingStyle
$cmin :: MappingStyle -> MappingStyle -> MappingStyle
max :: MappingStyle -> MappingStyle -> MappingStyle
$cmax :: MappingStyle -> MappingStyle -> MappingStyle
>= :: MappingStyle -> MappingStyle -> Bool
$c>= :: MappingStyle -> MappingStyle -> Bool
> :: MappingStyle -> MappingStyle -> Bool
$c> :: MappingStyle -> MappingStyle -> Bool
<= :: MappingStyle -> MappingStyle -> Bool
$c<= :: MappingStyle -> MappingStyle -> Bool
< :: MappingStyle -> MappingStyle -> Bool
$c< :: MappingStyle -> MappingStyle -> Bool
compare :: MappingStyle -> MappingStyle -> Ordering
$ccompare :: MappingStyle -> MappingStyle -> Ordering
$cp1Ord :: Eq MappingStyle
Ord, Typeable MappingStyle
DataType
Constr
Typeable MappingStyle =>
(forall (c :: * -> *).
 (forall d b. Data d => c (d -> b) -> d -> c b)
 -> (forall g. g -> c g) -> MappingStyle -> c MappingStyle)
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c MappingStyle)
-> (MappingStyle -> Constr)
-> (MappingStyle -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
    Typeable t =>
    (forall d. Data d => c (t d)) -> Maybe (c MappingStyle))
-> (forall (t :: * -> * -> *) (c :: * -> *).
    Typeable t =>
    (forall d e. (Data d, Data e) => c (t d e))
    -> Maybe (c MappingStyle))
-> ((forall b. Data b => b -> b) -> MappingStyle -> MappingStyle)
-> (forall r r'.
    (r -> r' -> r)
    -> r -> (forall d. Data d => d -> r') -> MappingStyle -> r)
-> (forall r r'.
    (r' -> r -> r)
    -> r -> (forall d. Data d => d -> r') -> MappingStyle -> r)
-> (forall u. (forall d. Data d => d -> u) -> MappingStyle -> [u])
-> (forall u.
    Int -> (forall d. Data d => d -> u) -> MappingStyle -> u)
-> (forall (m :: * -> *).
    Monad m =>
    (forall d. Data d => d -> m d) -> MappingStyle -> m MappingStyle)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> MappingStyle -> m MappingStyle)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> MappingStyle -> m MappingStyle)
-> Data MappingStyle
MappingStyle -> DataType
MappingStyle -> Constr
(forall b. Data b => b -> b) -> MappingStyle -> MappingStyle
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> MappingStyle -> c MappingStyle
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c MappingStyle
forall a.
Typeable a =>
(forall (c :: * -> *).
 (forall d b. Data d => c (d -> b) -> d -> c b)
 -> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
    Typeable t =>
    (forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
    Typeable t =>
    (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
    (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
    (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
    Monad m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u. Int -> (forall d. Data d => d -> u) -> MappingStyle -> u
forall u. (forall d. Data d => d -> u) -> MappingStyle -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> MappingStyle -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> MappingStyle -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> MappingStyle -> m MappingStyle
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> MappingStyle -> m MappingStyle
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c MappingStyle
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> MappingStyle -> c MappingStyle
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c MappingStyle)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c MappingStyle)
$cFlowMapping :: Constr
$cBlockMapping :: Constr
$cAnyMapping :: Constr
$tMappingStyle :: DataType
gmapMo :: (forall d. Data d => d -> m d) -> MappingStyle -> m MappingStyle
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> MappingStyle -> m MappingStyle
gmapMp :: (forall d. Data d => d -> m d) -> MappingStyle -> m MappingStyle
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> MappingStyle -> m MappingStyle
gmapM :: (forall d. Data d => d -> m d) -> MappingStyle -> m MappingStyle
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> MappingStyle -> m MappingStyle
gmapQi :: Int -> (forall d. Data d => d -> u) -> MappingStyle -> u
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> MappingStyle -> u
gmapQ :: (forall d. Data d => d -> u) -> MappingStyle -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> MappingStyle -> [u]
gmapQr :: (r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> MappingStyle -> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> MappingStyle -> r
gmapQl :: (r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> MappingStyle -> r
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> MappingStyle -> r
gmapT :: (forall b. Data b => b -> b) -> MappingStyle -> MappingStyle
$cgmapT :: (forall b. Data b => b -> b) -> MappingStyle -> MappingStyle
dataCast2 :: (forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c MappingStyle)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c MappingStyle)
dataCast1 :: (forall d. Data d => c (t d)) -> Maybe (c MappingStyle)
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c MappingStyle)
dataTypeOf :: MappingStyle -> DataType
$cdataTypeOf :: MappingStyle -> DataType
toConstr :: MappingStyle -> Constr
$ctoConstr :: MappingStyle -> Constr
gunfold :: (forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c MappingStyle
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c MappingStyle
gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> MappingStyle -> c MappingStyle
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> MappingStyle -> c MappingStyle
$cp1Data :: Typeable MappingStyle
Data, Typeable)

data Tag = StrTag
         | FloatTag
         | NullTag
         | BoolTag
         | SetTag
         | IntTag
         | SeqTag
         | MapTag
         | UriTag String
         | NoTag
    deriving (Int -> Tag -> ShowS
[Tag] -> ShowS
Tag -> String
(Int -> Tag -> ShowS)
-> (Tag -> String) -> ([Tag] -> ShowS) -> Show Tag
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Tag] -> ShowS
$cshowList :: [Tag] -> ShowS
show :: Tag -> String
$cshow :: Tag -> String
showsPrec :: Int -> Tag -> ShowS
$cshowsPrec :: Int -> Tag -> ShowS
Show, Tag -> Tag -> Bool
(Tag -> Tag -> Bool) -> (Tag -> Tag -> Bool) -> Eq Tag
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Tag -> Tag -> Bool
$c/= :: Tag -> Tag -> Bool
== :: Tag -> Tag -> Bool
$c== :: Tag -> Tag -> Bool
Eq, ReadPrec [Tag]
ReadPrec Tag
Int -> ReadS Tag
ReadS [Tag]
(Int -> ReadS Tag)
-> ReadS [Tag] -> ReadPrec Tag -> ReadPrec [Tag] -> Read Tag
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [Tag]
$creadListPrec :: ReadPrec [Tag]
readPrec :: ReadPrec Tag
$creadPrec :: ReadPrec Tag
readList :: ReadS [Tag]
$creadList :: ReadS [Tag]
readsPrec :: Int -> ReadS Tag
$creadsPrec :: Int -> ReadS Tag
Read, Typeable Tag
DataType
Constr
Typeable Tag =>
(forall (c :: * -> *).
 (forall d b. Data d => c (d -> b) -> d -> c b)
 -> (forall g. g -> c g) -> Tag -> c Tag)
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c Tag)
-> (Tag -> Constr)
-> (Tag -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
    Typeable t =>
    (forall d. Data d => c (t d)) -> Maybe (c Tag))
-> (forall (t :: * -> * -> *) (c :: * -> *).
    Typeable t =>
    (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Tag))
-> ((forall b. Data b => b -> b) -> Tag -> Tag)
-> (forall r r'.
    (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Tag -> r)
-> (forall r r'.
    (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Tag -> r)
-> (forall u. (forall d. Data d => d -> u) -> Tag -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> Tag -> u)
-> (forall (m :: * -> *).
    Monad m =>
    (forall d. Data d => d -> m d) -> Tag -> m Tag)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> Tag -> m Tag)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> Tag -> m Tag)
-> Data Tag
Tag -> DataType
Tag -> Constr
(forall b. Data b => b -> b) -> Tag -> Tag
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Tag -> c Tag
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Tag
forall a.
Typeable a =>
(forall (c :: * -> *).
 (forall d b. Data d => c (d -> b) -> d -> c b)
 -> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
    Typeable t =>
    (forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
    Typeable t =>
    (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
    (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
    (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
    Monad m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u. Int -> (forall d. Data d => d -> u) -> Tag -> u
forall u. (forall d. Data d => d -> u) -> Tag -> [u]
forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Tag -> r
forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Tag -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Tag -> m Tag
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Tag -> m Tag
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Tag
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Tag -> c Tag
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Tag)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Tag)
$cNoTag :: Constr
$cUriTag :: Constr
$cMapTag :: Constr
$cSeqTag :: Constr
$cIntTag :: Constr
$cSetTag :: Constr
$cBoolTag :: Constr
$cNullTag :: Constr
$cFloatTag :: Constr
$cStrTag :: Constr
$tTag :: DataType
gmapMo :: (forall d. Data d => d -> m d) -> Tag -> m Tag
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Tag -> m Tag
gmapMp :: (forall d. Data d => d -> m d) -> Tag -> m Tag
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Tag -> m Tag
gmapM :: (forall d. Data d => d -> m d) -> Tag -> m Tag
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Tag -> m Tag
gmapQi :: Int -> (forall d. Data d => d -> u) -> Tag -> u
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Tag -> u
gmapQ :: (forall d. Data d => d -> u) -> Tag -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> Tag -> [u]
gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Tag -> r
$cgmapQr :: forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Tag -> r
gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Tag -> r
$cgmapQl :: forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Tag -> r
gmapT :: (forall b. Data b => b -> b) -> Tag -> Tag
$cgmapT :: (forall b. Data b => b -> b) -> Tag -> Tag
dataCast2 :: (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Tag)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Tag)
dataCast1 :: (forall d. Data d => c (t d)) -> Maybe (c Tag)
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Tag)
dataTypeOf :: Tag -> DataType
$cdataTypeOf :: Tag -> DataType
toConstr :: Tag -> Constr
$ctoConstr :: Tag -> Constr
gunfold :: (forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Tag
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Tag
gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Tag -> c Tag
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Tag -> c Tag
$cp1Data :: Typeable Tag
Data, Typeable)

tagSuppressed :: Tag -> Bool
tagSuppressed :: Tag -> Bool
tagSuppressed (Tag
NoTag) = Bool
True
tagSuppressed (UriTag "") = Bool
True
tagSuppressed _ = Bool
False

type AnchorName = String
type Anchor = Maybe AnchorName

tagToString :: Tag -> String
tagToString :: Tag -> String
tagToString StrTag = "tag:yaml.org,2002:str"
tagToString FloatTag = "tag:yaml.org,2002:float"
tagToString NullTag = "tag:yaml.org,2002:null"
tagToString BoolTag = "tag:yaml.org,2002:bool"
tagToString SetTag = "tag:yaml.org,2002:set"
tagToString IntTag = "tag:yaml.org,2002:int"
tagToString SeqTag = "tag:yaml.org,2002:seq"
tagToString MapTag = "tag:yaml.org,2002:map"
tagToString (UriTag s :: String
s) = String
s
tagToString NoTag = ""

bsToTag :: ByteString -> Tag
bsToTag :: ByteString -> Tag
bsToTag = String -> Tag
stringToTag (String -> Tag) -> (ByteString -> String) -> ByteString -> Tag
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> String
B8.unpack

stringToTag :: String -> Tag
stringToTag :: String -> Tag
stringToTag "tag:yaml.org,2002:str" = Tag
StrTag
stringToTag "tag:yaml.org,2002:float" = Tag
FloatTag
stringToTag "tag:yaml.org,2002:null" = Tag
NullTag
stringToTag "tag:yaml.org,2002:bool" = Tag
BoolTag
stringToTag "tag:yaml.org,2002:set" = Tag
SetTag
stringToTag "tag:yaml.org,2002:int" = Tag
IntTag
stringToTag "tag:yaml.org,2002:seq" = Tag
SeqTag
stringToTag "tag:yaml.org,2002:map" = Tag
MapTag
stringToTag "" = Tag
NoTag
stringToTag s :: String
s = String -> Tag
UriTag String
s

data ParserStruct
type Parser = Ptr ParserStruct
parserSize :: Int
parserSize :: Int
parserSize = 480

data EventRawStruct
type EventRaw = Ptr EventRawStruct
eventSize :: Int
eventSize :: Int
eventSize = 104

foreign import ccall unsafe "yaml_parser_initialize"
    c_yaml_parser_initialize :: Parser -> IO CInt

foreign import ccall unsafe "yaml_parser_delete"
    c_yaml_parser_delete :: Parser -> IO ()

foreign import ccall unsafe "yaml_parser_set_input_string"
    c_yaml_parser_set_input_string :: Parser
                                   -> Ptr CUChar
                                   -> CULong
                                   -> IO ()

foreign import ccall unsafe "yaml_parser_set_input_file"
    c_yaml_parser_set_input_file :: Parser
                                 -> File
                                 -> IO ()

data MarkRawStruct
type MarkRaw = Ptr MarkRawStruct

foreign import ccall unsafe "get_mark_index"
    c_get_mark_index :: MarkRaw -> IO CULong

foreign import ccall unsafe "get_mark_line"
    c_get_mark_line :: MarkRaw -> IO CULong

foreign import ccall unsafe "get_mark_column"
    c_get_mark_column :: MarkRaw -> IO CULong

getMark :: MarkRaw -> IO YamlMark
getMark :: MarkRaw -> IO YamlMark
getMark m :: MarkRaw
m = Int -> Int -> Int -> YamlMark
YamlMark
  (Int -> Int -> Int -> YamlMark)
-> IO Int -> IO (Int -> Int -> YamlMark)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (CULong -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral (CULong -> Int) -> IO CULong -> IO Int
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> MarkRaw -> IO CULong
c_get_mark_index MarkRaw
m)
  IO (Int -> Int -> YamlMark) -> IO Int -> IO (Int -> YamlMark)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (CULong -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral (CULong -> Int) -> IO CULong -> IO Int
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> MarkRaw -> IO CULong
c_get_mark_line MarkRaw
m)
  IO (Int -> YamlMark) -> IO Int -> IO YamlMark
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (CULong -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral (CULong -> Int) -> IO CULong -> IO Int
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> MarkRaw -> IO CULong
c_get_mark_column MarkRaw
m)

data FileStruct
type File = Ptr FileStruct

#ifdef WINDOWS
foreign import ccall unsafe "_fdopen"
#else
foreign import ccall unsafe "fdopen"
#endif
    c_fdopen :: CInt
             -> Ptr CChar
             -> IO File
foreign import ccall unsafe "fclose"
    c_fclose :: File
             -> IO ()

foreign import ccall unsafe "fclose_helper"
    c_fclose_helper :: File -> IO ()

foreign import ccall unsafe "yaml_parser_parse"
    c_yaml_parser_parse :: Parser -> EventRaw -> IO CInt

foreign import ccall unsafe "yaml_event_delete"
    c_yaml_event_delete :: EventRaw -> IO ()

foreign import ccall "get_parser_error_problem"
    c_get_parser_error_problem :: Parser -> IO (Ptr CUChar)

foreign import ccall "get_parser_error_context"
    c_get_parser_error_context :: Parser -> IO (Ptr CUChar)

foreign import ccall unsafe "get_parser_error_mark"
    c_get_parser_error_mark :: Parser -> IO MarkRaw

makeString :: MonadIO m => (a -> m (Ptr CUChar)) -> a -> m String
makeString :: (a -> m (Ptr CUChar)) -> a -> m String
makeString f :: a -> m (Ptr CUChar)
f a :: a
a = do
    Ptr CChar
cchar <- Ptr CUChar -> Ptr CChar
forall a b. Ptr a -> Ptr b
castPtr (Ptr CUChar -> Ptr CChar) -> m (Ptr CUChar) -> m (Ptr CChar)
forall (m :: * -> *) a1 r. Monad m => (a1 -> r) -> m a1 -> m r
`liftM` a -> m (Ptr CUChar)
f a
a
    if Ptr CChar
cchar Ptr CChar -> Ptr CChar -> Bool
forall a. Eq a => a -> a -> Bool
== Ptr CChar
forall a. Ptr a
nullPtr
        then String -> m String
forall (m :: * -> *) a. Monad m => a -> m a
return ""
        else IO String -> m String
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO String -> m String) -> IO String -> m String
forall a b. (a -> b) -> a -> b
$ Ptr CChar -> IO String
peekCString Ptr CChar
cchar

data EventType = YamlNoEvent
               | YamlStreamStartEvent
               | YamlStreamEndEvent
               | YamlDocumentStartEvent
               | YamlDocumentEndEvent
               | YamlAliasEvent
               | YamlScalarEvent
               | YamlSequenceStartEvent
               | YamlSequenceEndEvent
               | YamlMappingStartEvent
               | YamlMappingEndEvent
               deriving (Int -> EventType
EventType -> Int
EventType -> [EventType]
EventType -> EventType
EventType -> EventType -> [EventType]
EventType -> EventType -> EventType -> [EventType]
(EventType -> EventType)
-> (EventType -> EventType)
-> (Int -> EventType)
-> (EventType -> Int)
-> (EventType -> [EventType])
-> (EventType -> EventType -> [EventType])
-> (EventType -> EventType -> [EventType])
-> (EventType -> EventType -> EventType -> [EventType])
-> Enum EventType
forall a.
(a -> a)
-> (a -> a)
-> (Int -> a)
-> (a -> Int)
-> (a -> [a])
-> (a -> a -> [a])
-> (a -> a -> [a])
-> (a -> a -> a -> [a])
-> Enum a
enumFromThenTo :: EventType -> EventType -> EventType -> [EventType]
$cenumFromThenTo :: EventType -> EventType -> EventType -> [EventType]
enumFromTo :: EventType -> EventType -> [EventType]
$cenumFromTo :: EventType -> EventType -> [EventType]
enumFromThen :: EventType -> EventType -> [EventType]
$cenumFromThen :: EventType -> EventType -> [EventType]
enumFrom :: EventType -> [EventType]
$cenumFrom :: EventType -> [EventType]
fromEnum :: EventType -> Int
$cfromEnum :: EventType -> Int
toEnum :: Int -> EventType
$ctoEnum :: Int -> EventType
pred :: EventType -> EventType
$cpred :: EventType -> EventType
succ :: EventType -> EventType
$csucc :: EventType -> EventType
Enum,Int -> EventType -> ShowS
[EventType] -> ShowS
EventType -> String
(Int -> EventType -> ShowS)
-> (EventType -> String)
-> ([EventType] -> ShowS)
-> Show EventType
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [EventType] -> ShowS
$cshowList :: [EventType] -> ShowS
show :: EventType -> String
$cshow :: EventType -> String
showsPrec :: Int -> EventType -> ShowS
$cshowsPrec :: Int -> EventType -> ShowS
Show)

foreign import ccall unsafe "get_event_type"
    c_get_event_type :: EventRaw -> IO CInt

foreign import ccall unsafe "get_start_mark"
    c_get_start_mark :: EventRaw -> IO MarkRaw

foreign import ccall unsafe "get_end_mark"
    c_get_end_mark :: EventRaw -> IO MarkRaw

foreign import ccall unsafe "get_scalar_value"
    c_get_scalar_value :: EventRaw -> IO (Ptr CUChar)

foreign import ccall unsafe "get_scalar_length"
    c_get_scalar_length :: EventRaw -> IO CULong

foreign import ccall unsafe "get_scalar_tag"
    c_get_scalar_tag :: EventRaw -> IO (Ptr CUChar)

foreign import ccall unsafe "get_scalar_style"
    c_get_scalar_style :: EventRaw -> IO CInt

foreign import ccall unsafe "get_scalar_anchor"
    c_get_scalar_anchor :: EventRaw -> IO CString

foreign import ccall unsafe "get_sequence_start_anchor"
    c_get_sequence_start_anchor :: EventRaw -> IO CString

foreign import ccall unsafe "get_sequence_start_style"
    c_get_sequence_start_style :: EventRaw -> IO CInt

foreign import ccall unsafe "get_sequence_start_tag"
    c_get_sequence_start_tag :: EventRaw -> IO (Ptr CUChar)

foreign import ccall unsafe "get_mapping_start_anchor"
    c_get_mapping_start_anchor :: EventRaw -> IO CString

foreign import ccall unsafe "get_mapping_start_style"
    c_get_mapping_start_style :: EventRaw -> IO CInt

foreign import ccall unsafe "get_mapping_start_tag"
    c_get_mapping_start_tag :: EventRaw -> IO (Ptr CUChar)

foreign import ccall unsafe "get_alias_anchor"
    c_get_alias_anchor :: EventRaw -> IO CString

readAnchor :: (EventRaw -> IO CString) -> EventRaw -> IO Anchor
readAnchor :: (EventRaw -> IO (Ptr CChar)) -> EventRaw -> IO Anchor
readAnchor getAnchor :: EventRaw -> IO (Ptr CChar)
getAnchor er :: EventRaw
er = do
  Ptr CChar
yanchor <- EventRaw -> IO (Ptr CChar)
getAnchor EventRaw
er
  if Ptr CChar
yanchor Ptr CChar -> Ptr CChar -> Bool
forall a. Eq a => a -> a -> Bool
== Ptr CChar
forall a. Ptr a
nullPtr
    then Anchor -> IO Anchor
forall (m :: * -> *) a. Monad m => a -> m a
return Anchor
forall a. Maybe a
Nothing
    else String -> Anchor
forall a. a -> Maybe a
Just (String -> Anchor) -> IO String -> IO Anchor
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Ptr CChar -> IO String
peekCString Ptr CChar
yanchor

readStyle :: (Enum a) => (EventRaw -> IO CInt) -> EventRaw -> IO a
readStyle :: (EventRaw -> IO CInt) -> EventRaw -> IO a
readStyle getStyle :: EventRaw -> IO CInt
getStyle er :: EventRaw
er = Int -> a
forall a. Enum a => Int -> a
toEnum (Int -> a) -> (CInt -> Int) -> CInt -> a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. CInt -> Int
forall a. Enum a => a -> Int
fromEnum (CInt -> a) -> IO CInt -> IO a
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> EventRaw -> IO CInt
getStyle EventRaw
er 

readTag :: (EventRaw -> IO (Ptr CUChar)) -> EventRaw -> IO Tag
readTag :: (EventRaw -> IO (Ptr CUChar)) -> EventRaw -> IO Tag
readTag getTag :: EventRaw -> IO (Ptr CUChar)
getTag er :: EventRaw
er = ByteString -> Tag
bsToTag (ByteString -> Tag) -> IO ByteString -> IO Tag
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (EventRaw -> IO (Ptr CUChar)
getTag EventRaw
er IO (Ptr CUChar) -> (Ptr CUChar -> IO ByteString) -> IO ByteString
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= Ptr CChar -> IO ByteString
packCString (Ptr CChar -> IO ByteString)
-> (Ptr CUChar -> Ptr CChar) -> Ptr CUChar -> IO ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Ptr CUChar -> Ptr CChar
forall a b. Ptr a -> Ptr b
castPtr) 

getEvent :: EventRaw -> IO (Maybe MarkedEvent)
getEvent :: EventRaw -> IO (Maybe MarkedEvent)
getEvent er :: EventRaw
er = do
    CInt
et <- EventRaw -> IO CInt
c_get_event_type EventRaw
er
    YamlMark
startMark <- EventRaw -> IO MarkRaw
c_get_start_mark EventRaw
er IO MarkRaw -> (MarkRaw -> IO YamlMark) -> IO YamlMark
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= MarkRaw -> IO YamlMark
getMark
    YamlMark
endMark <- EventRaw -> IO MarkRaw
c_get_end_mark EventRaw
er IO MarkRaw -> (MarkRaw -> IO YamlMark) -> IO YamlMark
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= MarkRaw -> IO YamlMark
getMark
    Maybe Event
event <- case Int -> EventType
forall a. Enum a => Int -> a
toEnum (Int -> EventType) -> Int -> EventType
forall a b. (a -> b) -> a -> b
$ CInt -> Int
forall a. Enum a => a -> Int
fromEnum CInt
et of
        YamlNoEvent -> Maybe Event -> IO (Maybe Event)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe Event
forall a. Maybe a
Nothing
        YamlStreamStartEvent -> Maybe Event -> IO (Maybe Event)
forall (m :: * -> *) a. Monad m => a -> m a
return (Maybe Event -> IO (Maybe Event))
-> Maybe Event -> IO (Maybe Event)
forall a b. (a -> b) -> a -> b
$ Event -> Maybe Event
forall a. a -> Maybe a
Just Event
EventStreamStart
        YamlStreamEndEvent -> Maybe Event -> IO (Maybe Event)
forall (m :: * -> *) a. Monad m => a -> m a
return (Maybe Event -> IO (Maybe Event))
-> Maybe Event -> IO (Maybe Event)
forall a b. (a -> b) -> a -> b
$ Event -> Maybe Event
forall a. a -> Maybe a
Just Event
EventStreamEnd
        YamlDocumentStartEvent -> Maybe Event -> IO (Maybe Event)
forall (m :: * -> *) a. Monad m => a -> m a
return (Maybe Event -> IO (Maybe Event))
-> Maybe Event -> IO (Maybe Event)
forall a b. (a -> b) -> a -> b
$ Event -> Maybe Event
forall a. a -> Maybe a
Just Event
EventDocumentStart
        YamlDocumentEndEvent -> Maybe Event -> IO (Maybe Event)
forall (m :: * -> *) a. Monad m => a -> m a
return (Maybe Event -> IO (Maybe Event))
-> Maybe Event -> IO (Maybe Event)
forall a b. (a -> b) -> a -> b
$ Event -> Maybe Event
forall a. a -> Maybe a
Just Event
EventDocumentEnd
        YamlAliasEvent -> do
            Ptr CChar
yanchor <- EventRaw -> IO (Ptr CChar)
c_get_alias_anchor EventRaw
er
            String
anchor <- if Ptr CChar
yanchor Ptr CChar -> Ptr CChar -> Bool
forall a. Eq a => a -> a -> Bool
== Ptr CChar
forall a. Ptr a
nullPtr
                          then String -> IO String
forall a. HasCallStack => String -> a
error "got YamlAliasEvent with empty anchor"
                          else Ptr CChar -> IO String
peekCString Ptr CChar
yanchor
            Maybe Event -> IO (Maybe Event)
forall (m :: * -> *) a. Monad m => a -> m a
return (Maybe Event -> IO (Maybe Event))
-> Maybe Event -> IO (Maybe Event)
forall a b. (a -> b) -> a -> b
$ Event -> Maybe Event
forall a. a -> Maybe a
Just (Event -> Maybe Event) -> Event -> Maybe Event
forall a b. (a -> b) -> a -> b
$ String -> Event
EventAlias String
anchor
        YamlScalarEvent -> do
            Ptr CUChar
yvalue <- EventRaw -> IO (Ptr CUChar)
c_get_scalar_value EventRaw
er
            CULong
ylen <- EventRaw -> IO CULong
c_get_scalar_length EventRaw
er
            let yvalue' :: Ptr CChar
yvalue' = Ptr CUChar -> Ptr CChar
forall a b. Ptr a -> Ptr b
castPtr Ptr CUChar
yvalue
            let ylen' :: Int
ylen' = CULong -> Int
forall a. Enum a => a -> Int
fromEnum CULong
ylen
            ByteString
bs <- CStringLen -> IO ByteString
packCStringLen (Ptr CChar
yvalue', Int
ylen')
            Tag
tag <- (EventRaw -> IO (Ptr CUChar)) -> EventRaw -> IO Tag
readTag EventRaw -> IO (Ptr CUChar)
c_get_scalar_tag EventRaw
er
            Style
style <- (EventRaw -> IO CInt) -> EventRaw -> IO Style
forall a. Enum a => (EventRaw -> IO CInt) -> EventRaw -> IO a
readStyle EventRaw -> IO CInt
c_get_scalar_style EventRaw
er
            Anchor
anchor <- (EventRaw -> IO (Ptr CChar)) -> EventRaw -> IO Anchor
readAnchor EventRaw -> IO (Ptr CChar)
c_get_scalar_anchor EventRaw
er
            Maybe Event -> IO (Maybe Event)
forall (m :: * -> *) a. Monad m => a -> m a
return (Maybe Event -> IO (Maybe Event))
-> Maybe Event -> IO (Maybe Event)
forall a b. (a -> b) -> a -> b
$ Event -> Maybe Event
forall a. a -> Maybe a
Just (Event -> Maybe Event) -> Event -> Maybe Event
forall a b. (a -> b) -> a -> b
$ ByteString -> Tag -> Style -> Anchor -> Event
EventScalar ByteString
bs Tag
tag Style
style Anchor
anchor
        YamlSequenceStartEvent -> do
            Tag
tag <- (EventRaw -> IO (Ptr CUChar)) -> EventRaw -> IO Tag
readTag EventRaw -> IO (Ptr CUChar)
c_get_sequence_start_tag EventRaw
er
            SequenceStyle
style <- (EventRaw -> IO CInt) -> EventRaw -> IO SequenceStyle
forall a. Enum a => (EventRaw -> IO CInt) -> EventRaw -> IO a
readStyle EventRaw -> IO CInt
c_get_sequence_start_style EventRaw
er
            Anchor
anchor <- (EventRaw -> IO (Ptr CChar)) -> EventRaw -> IO Anchor
readAnchor EventRaw -> IO (Ptr CChar)
c_get_sequence_start_anchor EventRaw
er
            Maybe Event -> IO (Maybe Event)
forall (m :: * -> *) a. Monad m => a -> m a
return (Maybe Event -> IO (Maybe Event))
-> Maybe Event -> IO (Maybe Event)
forall a b. (a -> b) -> a -> b
$ Event -> Maybe Event
forall a. a -> Maybe a
Just (Event -> Maybe Event) -> Event -> Maybe Event
forall a b. (a -> b) -> a -> b
$ Tag -> SequenceStyle -> Anchor -> Event
EventSequenceStart Tag
tag SequenceStyle
style Anchor
anchor
        YamlSequenceEndEvent -> Maybe Event -> IO (Maybe Event)
forall (m :: * -> *) a. Monad m => a -> m a
return (Maybe Event -> IO (Maybe Event))
-> Maybe Event -> IO (Maybe Event)
forall a b. (a -> b) -> a -> b
$ Event -> Maybe Event
forall a. a -> Maybe a
Just Event
EventSequenceEnd
        YamlMappingStartEvent -> do
            Tag
tag <- (EventRaw -> IO (Ptr CUChar)) -> EventRaw -> IO Tag
readTag EventRaw -> IO (Ptr CUChar)
c_get_mapping_start_tag EventRaw
er
            MappingStyle
style <- (EventRaw -> IO CInt) -> EventRaw -> IO MappingStyle
forall a. Enum a => (EventRaw -> IO CInt) -> EventRaw -> IO a
readStyle EventRaw -> IO CInt
c_get_mapping_start_style EventRaw
er
            Anchor
anchor <- (EventRaw -> IO (Ptr CChar)) -> EventRaw -> IO Anchor
readAnchor EventRaw -> IO (Ptr CChar)
c_get_mapping_start_anchor EventRaw
er
            Maybe Event -> IO (Maybe Event)
forall (m :: * -> *) a. Monad m => a -> m a
return (Maybe Event -> IO (Maybe Event))
-> Maybe Event -> IO (Maybe Event)
forall a b. (a -> b) -> a -> b
$ Event -> Maybe Event
forall a. a -> Maybe a
Just (Event -> Maybe Event) -> Event -> Maybe Event
forall a b. (a -> b) -> a -> b
$ Tag -> MappingStyle -> Anchor -> Event
EventMappingStart Tag
tag MappingStyle
style Anchor
anchor
        YamlMappingEndEvent -> Maybe Event -> IO (Maybe Event)
forall (m :: * -> *) a. Monad m => a -> m a
return (Maybe Event -> IO (Maybe Event))
-> Maybe Event -> IO (Maybe Event)
forall a b. (a -> b) -> a -> b
$ Event -> Maybe Event
forall a. a -> Maybe a
Just Event
EventMappingEnd
    Maybe MarkedEvent -> IO (Maybe MarkedEvent)
forall (m :: * -> *) a. Monad m => a -> m a
return (Maybe MarkedEvent -> IO (Maybe MarkedEvent))
-> Maybe MarkedEvent -> IO (Maybe MarkedEvent)
forall a b. (a -> b) -> a -> b
$ (\e :: Event
e -> Event -> YamlMark -> YamlMark -> MarkedEvent
MarkedEvent Event
e YamlMark
startMark YamlMark
endMark) (Event -> MarkedEvent) -> Maybe Event -> Maybe MarkedEvent
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Maybe Event
event

-- Emitter

data EmitterStruct
type Emitter = Ptr EmitterStruct
emitterSize :: Int
emitterSize :: Int
emitterSize = 432

foreign import ccall unsafe "yaml_emitter_initialize"
    c_yaml_emitter_initialize :: Emitter -> IO CInt

foreign import ccall unsafe "yaml_emitter_delete"
    c_yaml_emitter_delete :: Emitter -> IO ()

data BufferStruct
type Buffer = Ptr BufferStruct
bufferSize :: Int
bufferSize :: Int
bufferSize = 16

foreign import ccall unsafe "buffer_init"
    c_buffer_init :: Buffer -> IO ()

foreign import ccall unsafe "get_buffer_buff"
    c_get_buffer_buff :: Buffer -> IO (Ptr CUChar)

foreign import ccall unsafe "get_buffer_used"
    c_get_buffer_used :: Buffer -> IO CULong

foreign import ccall unsafe "my_emitter_set_output"
    c_my_emitter_set_output :: Emitter -> Buffer -> IO ()

#ifndef __NO_UNICODE__
foreign import ccall unsafe "yaml_emitter_set_unicode"
    c_yaml_emitter_set_unicode :: Emitter -> CInt -> IO ()
#endif

foreign import ccall unsafe "yaml_emitter_set_output_file"
    c_yaml_emitter_set_output_file :: Emitter -> File -> IO ()

foreign import ccall unsafe "yaml_emitter_set_width"
    c_yaml_emitter_set_width :: Emitter -> CInt -> IO ()

foreign import ccall unsafe "yaml_emitter_emit"
    c_yaml_emitter_emit :: Emitter -> EventRaw -> IO CInt

foreign import ccall unsafe "yaml_stream_start_event_initialize"
    c_yaml_stream_start_event_initialize :: EventRaw -> CInt -> IO CInt

foreign import ccall unsafe "yaml_stream_end_event_initialize"
    c_yaml_stream_end_event_initialize :: EventRaw -> IO CInt

foreign import ccall unsafe "yaml_scalar_event_initialize"
    c_yaml_scalar_event_initialize
        :: EventRaw
        -> Ptr CUChar -- anchor
        -> Ptr CUChar -- tag
        -> Ptr CUChar -- value
        -> CInt       -- length
        -> CInt       -- plain_implicit
        -> CInt       -- quoted_implicit
        -> CInt       -- style
        -> IO CInt

foreign import ccall unsafe "simple_document_start"
    c_simple_document_start :: EventRaw -> IO CInt

foreign import ccall unsafe "yaml_document_end_event_initialize"
    c_yaml_document_end_event_initialize :: EventRaw -> CInt -> IO CInt

foreign import ccall unsafe "yaml_sequence_start_event_initialize"
    c_yaml_sequence_start_event_initialize
        :: EventRaw
        -> Ptr CUChar
        -> Ptr CUChar
        -> CInt
        -> CInt
        -> IO CInt

foreign import ccall unsafe "yaml_sequence_end_event_initialize"
    c_yaml_sequence_end_event_initialize :: EventRaw -> IO CInt

foreign import ccall unsafe "yaml_mapping_start_event_initialize"
    c_yaml_mapping_start_event_initialize
        :: EventRaw
        -> Ptr CUChar
        -> Ptr CUChar
        -> CInt
        -> CInt
        -> IO CInt

foreign import ccall unsafe "yaml_mapping_end_event_initialize"
    c_yaml_mapping_end_event_initialize :: EventRaw -> IO CInt

foreign import ccall unsafe "yaml_alias_event_initialize"
    c_yaml_alias_event_initialize
        :: EventRaw
        -> Ptr CUChar
        -> IO CInt

toEventRaw :: FormatOptions -> Event -> (EventRaw -> IO a) -> IO a
toEventRaw :: FormatOptions -> Event -> (EventRaw -> IO a) -> IO a
toEventRaw opts :: FormatOptions
opts e :: Event
e f :: EventRaw -> IO a
f = Int -> (EventRaw -> IO a) -> IO a
forall a b. Int -> (Ptr a -> IO b) -> IO b
allocaBytes Int
eventSize ((EventRaw -> IO a) -> IO a) -> (EventRaw -> IO a) -> IO a
forall a b. (a -> b) -> a -> b
$ \er :: EventRaw
er -> do
    CInt
ret <- case Event
e of
        EventStreamStart ->
            EventRaw -> CInt -> IO CInt
c_yaml_stream_start_event_initialize
                EventRaw
er
                0 -- YAML_ANY_ENCODING
        EventStreamEnd ->
            EventRaw -> IO CInt
c_yaml_stream_end_event_initialize EventRaw
er
        EventDocumentStart ->
            EventRaw -> IO CInt
c_simple_document_start EventRaw
er
        EventDocumentEnd ->
            EventRaw -> CInt -> IO CInt
c_yaml_document_end_event_initialize EventRaw
er 1
        EventScalar bs :: ByteString
bs thetag :: Tag
thetag style0 :: Style
style0 anchor :: Anchor
anchor -> do
            ByteString -> (CStringLen -> IO CInt) -> IO CInt
forall a. ByteString -> (CStringLen -> IO a) -> IO a
BU.unsafeUseAsCStringLen ByteString
bs ((CStringLen -> IO CInt) -> IO CInt)
-> (CStringLen -> IO CInt) -> IO CInt
forall a b. (a -> b) -> a -> b
$ \(value :: Ptr CChar
value, len :: Int
len) -> do
                let value' :: Ptr CUChar
value' = Ptr CChar -> Ptr CUChar
forall a b. Ptr a -> Ptr b
castPtr Ptr CChar
value :: Ptr CUChar
                    len' :: CInt
len' = Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
len :: CInt
                let thetag' :: String
thetag' = Tag -> String
tagToString Tag
thetag
                String -> (Ptr CChar -> IO CInt) -> IO CInt
forall a. String -> (Ptr CChar -> IO a) -> IO a
withCString String
thetag' ((Ptr CChar -> IO CInt) -> IO CInt)
-> (Ptr CChar -> IO CInt) -> IO CInt
forall a b. (a -> b) -> a -> b
$ \tag' :: Ptr CChar
tag' -> do
                    let pi0 :: CInt
pi0 = Event -> CInt
tagsImplicit Event
e
                        (pi :: CInt
pi, style :: Style
style) =
                          case Style
style0 of
                            PlainNoTag -> (1, Style
Plain)
                            x :: Style
x -> (CInt
pi0, Style
x)
                        style' :: CInt
style' = Int -> CInt
forall a. Enum a => Int -> a
toEnum (Int -> CInt) -> Int -> CInt
forall a b. (a -> b) -> a -> b
$ Style -> Int
forall a. Enum a => a -> Int
fromEnum Style
style
                        tagP :: Ptr CUChar
tagP = Ptr CChar -> Ptr CUChar
forall a b. Ptr a -> Ptr b
castPtr Ptr CChar
tag'
                    case Anchor
anchor of
                        Nothing ->
                            EventRaw
-> Ptr CUChar
-> Ptr CUChar
-> Ptr CUChar
-> CInt
-> CInt
-> CInt
-> CInt
-> IO CInt
c_yaml_scalar_event_initialize
                                EventRaw
er
                                Ptr CUChar
forall a. Ptr a
nullPtr -- anchor
                                Ptr CUChar
tagP    -- tag
                                Ptr CUChar
value'  -- value
                                CInt
len'    -- length
                                CInt
pi      -- plain_implicit
                                CInt
pi      -- quoted_implicit
                                CInt
style'  -- style
                        Just anchor' :: String
anchor' ->
                            String -> (Ptr CChar -> IO CInt) -> IO CInt
forall a. String -> (Ptr CChar -> IO a) -> IO a
withCString String
anchor' ((Ptr CChar -> IO CInt) -> IO CInt)
-> (Ptr CChar -> IO CInt) -> IO CInt
forall a b. (a -> b) -> a -> b
$ \anchorP' :: Ptr CChar
anchorP' -> do
                                let anchorP :: Ptr CUChar
anchorP = Ptr CChar -> Ptr CUChar
forall a b. Ptr a -> Ptr b
castPtr Ptr CChar
anchorP'
                                EventRaw
-> Ptr CUChar
-> Ptr CUChar
-> Ptr CUChar
-> CInt
-> CInt
-> CInt
-> CInt
-> IO CInt
c_yaml_scalar_event_initialize
                                    EventRaw
er
                                    Ptr CUChar
anchorP -- anchor
                                    Ptr CUChar
tagP    -- tag
                                    Ptr CUChar
value'  -- value
                                    CInt
len'    -- length
                                    0       -- plain_implicit
                                    CInt
pi      -- quoted_implicit
                                    CInt
style'  -- style
        EventSequenceStart tag :: Tag
tag style :: SequenceStyle
style Nothing ->
            String -> (Ptr CChar -> IO CInt) -> IO CInt
forall a. String -> (Ptr CChar -> IO a) -> IO a
withCString (Tag -> String
tagToString Tag
tag) ((Ptr CChar -> IO CInt) -> IO CInt)
-> (Ptr CChar -> IO CInt) -> IO CInt
forall a b. (a -> b) -> a -> b
$ \tag' :: Ptr CChar
tag' -> do
                let tagP :: Ptr CUChar
tagP = Ptr CChar -> Ptr CUChar
forall a b. Ptr a -> Ptr b
castPtr Ptr CChar
tag'
                EventRaw -> Ptr CUChar -> Ptr CUChar -> CInt -> CInt -> IO CInt
c_yaml_sequence_start_event_initialize
                  EventRaw
er
                  Ptr CUChar
forall a. Ptr a
nullPtr
                  Ptr CUChar
tagP
                  (Event -> CInt
tagsImplicit Event
e)
                  (Int -> CInt
forall a. Enum a => Int -> a
toEnum (Int -> CInt) -> Int -> CInt
forall a b. (a -> b) -> a -> b
$ SequenceStyle -> Int
forall a. Enum a => a -> Int
fromEnum SequenceStyle
style)
        EventSequenceStart tag :: Tag
tag style :: SequenceStyle
style (Just anchor :: String
anchor) ->
            String -> (Ptr CChar -> IO CInt) -> IO CInt
forall a. String -> (Ptr CChar -> IO a) -> IO a
withCString (Tag -> String
tagToString Tag
tag) ((Ptr CChar -> IO CInt) -> IO CInt)
-> (Ptr CChar -> IO CInt) -> IO CInt
forall a b. (a -> b) -> a -> b
$ \tag' :: Ptr CChar
tag' -> do
                let tagP :: Ptr CUChar
tagP = Ptr CChar -> Ptr CUChar
forall a b. Ptr a -> Ptr b
castPtr Ptr CChar
tag'
                String -> (Ptr CChar -> IO CInt) -> IO CInt
forall a. String -> (Ptr CChar -> IO a) -> IO a
withCString String
anchor ((Ptr CChar -> IO CInt) -> IO CInt)
-> (Ptr CChar -> IO CInt) -> IO CInt
forall a b. (a -> b) -> a -> b
$ \anchor' :: Ptr CChar
anchor' -> do
                    let anchorP :: Ptr CUChar
anchorP = Ptr CChar -> Ptr CUChar
forall a b. Ptr a -> Ptr b
castPtr Ptr CChar
anchor'
                    EventRaw -> Ptr CUChar -> Ptr CUChar -> CInt -> CInt -> IO CInt
c_yaml_sequence_start_event_initialize
                        EventRaw
er
                        Ptr CUChar
anchorP
                        Ptr CUChar
tagP
                        (Event -> CInt
tagsImplicit Event
e)
                        (Int -> CInt
forall a. Enum a => Int -> a
toEnum (Int -> CInt) -> Int -> CInt
forall a b. (a -> b) -> a -> b
$ SequenceStyle -> Int
forall a. Enum a => a -> Int
fromEnum SequenceStyle
style)
        EventSequenceEnd ->
            EventRaw -> IO CInt
c_yaml_sequence_end_event_initialize EventRaw
er
        EventMappingStart tag :: Tag
tag style :: MappingStyle
style Nothing ->
            String -> (Ptr CChar -> IO CInt) -> IO CInt
forall a. String -> (Ptr CChar -> IO a) -> IO a
withCString (Tag -> String
tagToString Tag
tag) ((Ptr CChar -> IO CInt) -> IO CInt)
-> (Ptr CChar -> IO CInt) -> IO CInt
forall a b. (a -> b) -> a -> b
$ \tag' :: Ptr CChar
tag' -> do
                let tagP :: Ptr CUChar
tagP = Ptr CChar -> Ptr CUChar
forall a b. Ptr a -> Ptr b
castPtr Ptr CChar
tag'
                EventRaw -> Ptr CUChar -> Ptr CUChar -> CInt -> CInt -> IO CInt
c_yaml_mapping_start_event_initialize
                    EventRaw
er
                    Ptr CUChar
forall a. Ptr a
nullPtr
                    Ptr CUChar
tagP
                    (Event -> CInt
tagsImplicit Event
e)
                    (Int -> CInt
forall a. Enum a => Int -> a
toEnum (Int -> CInt) -> Int -> CInt
forall a b. (a -> b) -> a -> b
$ MappingStyle -> Int
forall a. Enum a => a -> Int
fromEnum MappingStyle
style)
        EventMappingStart tag :: Tag
tag style :: MappingStyle
style (Just anchor :: String
anchor) ->
            String -> (Ptr CChar -> IO CInt) -> IO CInt
forall a. String -> (Ptr CChar -> IO a) -> IO a
withCString (Tag -> String
tagToString Tag
tag) ((Ptr CChar -> IO CInt) -> IO CInt)
-> (Ptr CChar -> IO CInt) -> IO CInt
forall a b. (a -> b) -> a -> b
$ \tag' :: Ptr CChar
tag' -> do
                String -> (Ptr CChar -> IO CInt) -> IO CInt
forall a. String -> (Ptr CChar -> IO a) -> IO a
withCString String
anchor ((Ptr CChar -> IO CInt) -> IO CInt)
-> (Ptr CChar -> IO CInt) -> IO CInt
forall a b. (a -> b) -> a -> b
$ \anchor' :: Ptr CChar
anchor' -> do
                    let tagP :: Ptr CUChar
tagP = Ptr CChar -> Ptr CUChar
forall a b. Ptr a -> Ptr b
castPtr Ptr CChar
tag'
                    let anchorP :: Ptr CUChar
anchorP = Ptr CChar -> Ptr CUChar
forall a b. Ptr a -> Ptr b
castPtr Ptr CChar
anchor'
                    EventRaw -> Ptr CUChar -> Ptr CUChar -> CInt -> CInt -> IO CInt
c_yaml_mapping_start_event_initialize
                        EventRaw
er
                        Ptr CUChar
anchorP
                        Ptr CUChar
tagP
                        (Event -> CInt
tagsImplicit Event
e)
                        (Int -> CInt
forall a. Enum a => Int -> a
toEnum (Int -> CInt) -> Int -> CInt
forall a b. (a -> b) -> a -> b
$ MappingStyle -> Int
forall a. Enum a => a -> Int
fromEnum MappingStyle
style)
        EventMappingEnd ->
            EventRaw -> IO CInt
c_yaml_mapping_end_event_initialize EventRaw
er
        EventAlias anchor :: String
anchor ->
            String -> (Ptr CChar -> IO CInt) -> IO CInt
forall a. String -> (Ptr CChar -> IO a) -> IO a
withCString String
anchor ((Ptr CChar -> IO CInt) -> IO CInt)
-> (Ptr CChar -> IO CInt) -> IO CInt
forall a b. (a -> b) -> a -> b
$ \anchorP' :: Ptr CChar
anchorP' -> do
                let anchorP :: Ptr CUChar
anchorP = Ptr CChar -> Ptr CUChar
forall a b. Ptr a -> Ptr b
castPtr Ptr CChar
anchorP'
                EventRaw -> Ptr CUChar -> IO CInt
c_yaml_alias_event_initialize
                    EventRaw
er
                    Ptr CUChar
anchorP
    Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless (CInt
ret CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
== 1) (IO () -> IO ()) -> IO () -> IO ()
forall a b. (a -> b) -> a -> b
$ ToEventRawException -> IO ()
forall e a. Exception e => e -> IO a
throwIO (ToEventRawException -> IO ()) -> ToEventRawException -> IO ()
forall a b. (a -> b) -> a -> b
$ CInt -> ToEventRawException
ToEventRawException CInt
ret
    EventRaw -> IO a
f EventRaw
er
  where
    tagsImplicit :: Event -> CInt
tagsImplicit (EventScalar _ t :: Tag
t _ _) | Tag -> Bool
tagSuppressed Tag
t = 1
    tagsImplicit (EventMappingStart t :: Tag
t _ _) | Tag -> Bool
tagSuppressed Tag
t = 1
    tagsImplicit (EventSequenceStart t :: Tag
t _ _) | Tag -> Bool
tagSuppressed Tag
t = 1
    tagsImplicit evt :: Event
evt = TagRender -> CInt
toImplicitParam (TagRender -> CInt) -> TagRender -> CInt
forall a b. (a -> b) -> a -> b
$ FormatOptions -> Event -> TagRender
formatOptionsRenderTags FormatOptions
opts Event
evt

newtype ToEventRawException = ToEventRawException CInt
    deriving (Int -> ToEventRawException -> ShowS
[ToEventRawException] -> ShowS
ToEventRawException -> String
(Int -> ToEventRawException -> ShowS)
-> (ToEventRawException -> String)
-> ([ToEventRawException] -> ShowS)
-> Show ToEventRawException
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ToEventRawException] -> ShowS
$cshowList :: [ToEventRawException] -> ShowS
show :: ToEventRawException -> String
$cshow :: ToEventRawException -> String
showsPrec :: Int -> ToEventRawException -> ShowS
$cshowsPrec :: Int -> ToEventRawException -> ShowS
Show, Typeable)
instance Exception ToEventRawException

-- | Create a conduit that yields events from a bytestring.
decode :: MonadResource m => B.ByteString -> ConduitM i Event m ()
decode :: ByteString -> ConduitM i Event m ()
decode = (MarkedEvent -> Event)
-> ConduitT i MarkedEvent m () -> ConduitM i Event m ()
forall (m :: * -> *) o1 o2 i r.
Monad m =>
(o1 -> o2) -> ConduitT i o1 m r -> ConduitT i o2 m r
mapOutput MarkedEvent -> Event
yamlEvent (ConduitT i MarkedEvent m () -> ConduitM i Event m ())
-> (ByteString -> ConduitT i MarkedEvent m ())
-> ByteString
-> ConduitM i Event m ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> ConduitT i MarkedEvent m ()
forall (m :: * -> *) i.
MonadResource m =>
ByteString -> ConduitM i MarkedEvent m ()
decodeMarked

-- | Create a conduit that yields marked events from a bytestring.
--
-- This conduit will yield identical events to that of "decode", but also
-- includes start and end marks for each event.
--
-- @since 0.10.4.0
decodeMarked :: MonadResource m => B.ByteString -> ConduitM i MarkedEvent m ()
decodeMarked :: ByteString -> ConduitM i MarkedEvent m ()
decodeMarked bs :: ByteString
bs | ByteString -> Bool
B8.null ByteString
bs = () -> ConduitM i MarkedEvent m ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
decodeMarked bs :: ByteString
bs =
    IO (Ptr ParserStruct, ForeignPtr Word8)
-> ((Ptr ParserStruct, ForeignPtr Word8) -> IO ())
-> ((Ptr ParserStruct, ForeignPtr Word8)
    -> ConduitM i MarkedEvent m ())
-> ConduitM i MarkedEvent m ()
forall (m :: * -> *) a i o r.
MonadResource m =>
IO a -> (a -> IO ()) -> (a -> ConduitT i o m r) -> ConduitT i o m r
bracketP IO (Ptr ParserStruct, ForeignPtr Word8)
alloc (Ptr ParserStruct, ForeignPtr Word8) -> IO ()
forall a. (Ptr ParserStruct, ForeignPtr a) -> IO ()
cleanup (Ptr ParserStruct -> ConduitM i MarkedEvent m ()
forall (m :: * -> *) i.
MonadResource m =>
Ptr ParserStruct -> ConduitM i MarkedEvent m ()
runParser (Ptr ParserStruct -> ConduitM i MarkedEvent m ())
-> ((Ptr ParserStruct, ForeignPtr Word8) -> Ptr ParserStruct)
-> (Ptr ParserStruct, ForeignPtr Word8)
-> ConduitM i MarkedEvent m ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Ptr ParserStruct, ForeignPtr Word8) -> Ptr ParserStruct
forall a b. (a, b) -> a
fst)
  where
    alloc :: IO (Ptr ParserStruct, ForeignPtr Word8)
alloc = IO (Ptr ParserStruct, ForeignPtr Word8)
-> IO (Ptr ParserStruct, ForeignPtr Word8)
forall a. IO a -> IO a
mask_ (IO (Ptr ParserStruct, ForeignPtr Word8)
 -> IO (Ptr ParserStruct, ForeignPtr Word8))
-> IO (Ptr ParserStruct, ForeignPtr Word8)
-> IO (Ptr ParserStruct, ForeignPtr Word8)
forall a b. (a -> b) -> a -> b
$ do
        Ptr ParserStruct
ptr <- Int -> IO (Ptr ParserStruct)
forall a. Int -> IO (Ptr a)
mallocBytes Int
parserSize
        CInt
res <- Ptr ParserStruct -> IO CInt
c_yaml_parser_initialize Ptr ParserStruct
ptr
        if CInt
res CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
== 0
            then do
                Ptr ParserStruct -> IO ()
c_yaml_parser_delete Ptr ParserStruct
ptr
                Ptr ParserStruct -> IO ()
forall a. Ptr a -> IO ()
free Ptr ParserStruct
ptr
                YamlException -> IO (Ptr ParserStruct, ForeignPtr Word8)
forall e a. Exception e => e -> IO a
throwIO (YamlException -> IO (Ptr ParserStruct, ForeignPtr Word8))
-> YamlException -> IO (Ptr ParserStruct, ForeignPtr Word8)
forall a b. (a -> b) -> a -> b
$ String -> YamlException
YamlException "Yaml out of memory"
            else do
                let (bsfptr :: ForeignPtr Word8
bsfptr, offset :: Int
offset, len :: Int
len) = ByteString -> (ForeignPtr Word8, Int, Int)
B.toForeignPtr ByteString
bs
                let bsptrOrig :: Ptr Word8
bsptrOrig = ForeignPtr Word8 -> Ptr Word8
forall a. ForeignPtr a -> Ptr a
unsafeForeignPtrToPtr ForeignPtr Word8
bsfptr
                let bsptr :: Ptr CUChar
bsptr = Ptr Word8 -> Ptr Any
forall a b. Ptr a -> Ptr b
castPtr Ptr Word8
bsptrOrig Ptr Any -> Int -> Ptr CUChar
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
offset
                Ptr ParserStruct -> Ptr CUChar -> CULong -> IO ()
c_yaml_parser_set_input_string Ptr ParserStruct
ptr Ptr CUChar
bsptr (Int -> CULong
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
len)
                (Ptr ParserStruct, ForeignPtr Word8)
-> IO (Ptr ParserStruct, ForeignPtr Word8)
forall (m :: * -> *) a. Monad m => a -> m a
return (Ptr ParserStruct
ptr, ForeignPtr Word8
bsfptr)
    cleanup :: (Ptr ParserStruct, ForeignPtr a) -> IO ()
cleanup (ptr :: Ptr ParserStruct
ptr, bsfptr :: ForeignPtr a
bsfptr) = do
        ForeignPtr a -> IO ()
forall a. ForeignPtr a -> IO ()
touchForeignPtr ForeignPtr a
bsfptr
        Ptr ParserStruct -> IO ()
c_yaml_parser_delete Ptr ParserStruct
ptr
        Ptr ParserStruct -> IO ()
forall a. Ptr a -> IO ()
free Ptr ParserStruct
ptr

-- XXX copied from GHC.IO.FD
std_flags, read_flags, output_flags, write_flags :: CInt
std_flags :: CInt
std_flags    = CInt
Posix.o_NOCTTY
output_flags :: CInt
output_flags = CInt
std_flags    CInt -> CInt -> CInt
forall a. Bits a => a -> a -> a
.|. CInt
Posix.o_CREAT CInt -> CInt -> CInt
forall a. Bits a => a -> a -> a
.|. CInt
Posix.o_TRUNC
read_flags :: CInt
read_flags   = CInt
std_flags    CInt -> CInt -> CInt
forall a. Bits a => a -> a -> a
.|. CInt
Posix.o_RDONLY
write_flags :: CInt
write_flags  = CInt
output_flags CInt -> CInt -> CInt
forall a. Bits a => a -> a -> a
.|. CInt
Posix.o_WRONLY

-- | Open a C FILE* from a file path, using internal GHC API to work correctly
-- on all platforms, even on non-ASCII filenames. The opening mode must be
-- indicated via both 'rawOpenFlags' and 'openMode'.
openFile :: FilePath -> CInt -> String -> IO File
openFile :: String -> CInt -> String -> IO File
openFile file :: String
file rawOpenFlags :: CInt
rawOpenFlags openMode :: String
openMode = do
  CInt
fd <- IO CInt -> IO CInt
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO CInt -> IO CInt) -> IO CInt -> IO CInt
forall a b. (a -> b) -> a -> b
$ String -> (Ptr CChar -> IO CInt) -> IO CInt
forall a. String -> (Ptr CChar -> IO a) -> IO a
Posix.withFilePath String
file ((Ptr CChar -> IO CInt) -> IO CInt)
-> (Ptr CChar -> IO CInt) -> IO CInt
forall a b. (a -> b) -> a -> b
$ \file' :: Ptr CChar
file' ->
    Ptr CChar -> CInt -> CMode -> IO CInt
Posix.c_open Ptr CChar
file' CInt
rawOpenFlags 0o666
  if CInt
fd CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= (-1)
    then String -> (Ptr CChar -> IO File) -> IO File
forall a. String -> (Ptr CChar -> IO a) -> IO a
withCString String
openMode ((Ptr CChar -> IO File) -> IO File)
-> (Ptr CChar -> IO File) -> IO File
forall a b. (a -> b) -> a -> b
$ \openMode' :: Ptr CChar
openMode' -> CInt -> Ptr CChar -> IO File
c_fdopen CInt
fd Ptr CChar
openMode'
    else File -> IO File
forall (m :: * -> *) a. Monad m => a -> m a
return File
forall a. Ptr a
nullPtr

-- | Creata a conduit that yields events from a file.
decodeFile :: MonadResource m => FilePath -> ConduitM i Event m ()
decodeFile :: String -> ConduitM i Event m ()
decodeFile = (MarkedEvent -> Event)
-> ConduitT i MarkedEvent m () -> ConduitM i Event m ()
forall (m :: * -> *) o1 o2 i r.
Monad m =>
(o1 -> o2) -> ConduitT i o1 m r -> ConduitT i o2 m r
mapOutput MarkedEvent -> Event
yamlEvent (ConduitT i MarkedEvent m () -> ConduitM i Event m ())
-> (String -> ConduitT i MarkedEvent m ())
-> String
-> ConduitM i Event m ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> ConduitT i MarkedEvent m ()
forall (m :: * -> *) i.
MonadResource m =>
String -> ConduitM i MarkedEvent m ()
decodeFileMarked

-- | Create a conduit that yields marked events from a file.
--
-- This conduit will yield identical events to that of "decodeFile", but also
-- includes start and end marks for each event.
--
-- @since 0.10.4.0
decodeFileMarked :: MonadResource m => FilePath -> ConduitM i MarkedEvent m ()
decodeFileMarked :: String -> ConduitM i MarkedEvent m ()
decodeFileMarked file :: String
file =
    IO (Ptr ParserStruct, File)
-> ((Ptr ParserStruct, File) -> IO ())
-> ((Ptr ParserStruct, File) -> ConduitM i MarkedEvent m ())
-> ConduitM i MarkedEvent m ()
forall (m :: * -> *) a i o r.
MonadResource m =>
IO a -> (a -> IO ()) -> (a -> ConduitT i o m r) -> ConduitT i o m r
bracketP IO (Ptr ParserStruct, File)
alloc (Ptr ParserStruct, File) -> IO ()
cleanup (Ptr ParserStruct -> ConduitM i MarkedEvent m ()
forall (m :: * -> *) i.
MonadResource m =>
Ptr ParserStruct -> ConduitM i MarkedEvent m ()
runParser (Ptr ParserStruct -> ConduitM i MarkedEvent m ())
-> ((Ptr ParserStruct, File) -> Ptr ParserStruct)
-> (Ptr ParserStruct, File)
-> ConduitM i MarkedEvent m ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Ptr ParserStruct, File) -> Ptr ParserStruct
forall a b. (a, b) -> a
fst)
  where
    alloc :: IO (Ptr ParserStruct, File)
alloc = IO (Ptr ParserStruct, File) -> IO (Ptr ParserStruct, File)
forall a. IO a -> IO a
mask_ (IO (Ptr ParserStruct, File) -> IO (Ptr ParserStruct, File))
-> IO (Ptr ParserStruct, File) -> IO (Ptr ParserStruct, File)
forall a b. (a -> b) -> a -> b
$ do
        Ptr ParserStruct
ptr <- Int -> IO (Ptr ParserStruct)
forall a. Int -> IO (Ptr a)
mallocBytes Int
parserSize
        CInt
res <- Ptr ParserStruct -> IO CInt
c_yaml_parser_initialize Ptr ParserStruct
ptr
        if CInt
res CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
== 0
            then do
                Ptr ParserStruct -> IO ()
c_yaml_parser_delete Ptr ParserStruct
ptr
                Ptr ParserStruct -> IO ()
forall a. Ptr a -> IO ()
free Ptr ParserStruct
ptr
                YamlException -> IO (Ptr ParserStruct, File)
forall e a. Exception e => e -> IO a
throwIO (YamlException -> IO (Ptr ParserStruct, File))
-> YamlException -> IO (Ptr ParserStruct, File)
forall a b. (a -> b) -> a -> b
$ String -> YamlException
YamlException "Yaml out of memory"
            else do
                File
file' <- String -> CInt -> String -> IO File
openFile String
file CInt
read_flags "r"
                if File
file' File -> File -> Bool
forall a. Eq a => a -> a -> Bool
== File
forall a. Ptr a
nullPtr
                    then do
                        Ptr ParserStruct -> IO ()
c_yaml_parser_delete Ptr ParserStruct
ptr
                        Ptr ParserStruct -> IO ()
forall a. Ptr a -> IO ()
free Ptr ParserStruct
ptr
                        YamlException -> IO (Ptr ParserStruct, File)
forall e a. Exception e => e -> IO a
throwIO (YamlException -> IO (Ptr ParserStruct, File))
-> YamlException -> IO (Ptr ParserStruct, File)
forall a b. (a -> b) -> a -> b
$ String -> YamlException
YamlException
                                (String -> YamlException) -> String -> YamlException
forall a b. (a -> b) -> a -> b
$ "Yaml file not found: " String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
file
                    else do
                        Ptr ParserStruct -> File -> IO ()
c_yaml_parser_set_input_file Ptr ParserStruct
ptr File
file'
                        (Ptr ParserStruct, File) -> IO (Ptr ParserStruct, File)
forall (m :: * -> *) a. Monad m => a -> m a
return (Ptr ParserStruct
ptr, File
file')
    cleanup :: (Ptr ParserStruct, File) -> IO ()
cleanup (ptr :: Ptr ParserStruct
ptr, file' :: File
file') = do
        File -> IO ()
c_fclose_helper File
file'
        Ptr ParserStruct -> IO ()
c_yaml_parser_delete Ptr ParserStruct
ptr
        Ptr ParserStruct -> IO ()
forall a. Ptr a -> IO ()
free Ptr ParserStruct
ptr

runParser :: MonadResource m => Parser -> ConduitM i MarkedEvent m ()
runParser :: Ptr ParserStruct -> ConduitM i MarkedEvent m ()
runParser parser :: Ptr ParserStruct
parser = do
    Either YamlException (Maybe MarkedEvent)
e <- IO (Either YamlException (Maybe MarkedEvent))
-> ConduitT
     i MarkedEvent m (Either YamlException (Maybe MarkedEvent))
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Either YamlException (Maybe MarkedEvent))
 -> ConduitT
      i MarkedEvent m (Either YamlException (Maybe MarkedEvent)))
-> IO (Either YamlException (Maybe MarkedEvent))
-> ConduitT
     i MarkedEvent m (Either YamlException (Maybe MarkedEvent))
forall a b. (a -> b) -> a -> b
$ Ptr ParserStruct -> IO (Either YamlException (Maybe MarkedEvent))
parserParseOne' Ptr ParserStruct
parser
    case Either YamlException (Maybe MarkedEvent)
e of
        Left err :: YamlException
err -> IO () -> ConduitM i MarkedEvent m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> ConduitM i MarkedEvent m ())
-> IO () -> ConduitM i MarkedEvent m ()
forall a b. (a -> b) -> a -> b
$ YamlException -> IO ()
forall e a. Exception e => e -> IO a
throwIO YamlException
err
        Right Nothing -> () -> ConduitM i MarkedEvent m ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
        Right (Just ev :: MarkedEvent
ev) -> MarkedEvent -> ConduitM i MarkedEvent m ()
forall (m :: * -> *) o i. Monad m => o -> ConduitT i o m ()
yield MarkedEvent
ev ConduitM i MarkedEvent m ()
-> ConduitM i MarkedEvent m () -> ConduitM i MarkedEvent m ()
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Ptr ParserStruct -> ConduitM i MarkedEvent m ()
forall (m :: * -> *) i.
MonadResource m =>
Ptr ParserStruct -> ConduitM i MarkedEvent m ()
runParser Ptr ParserStruct
parser

parserParseOne' :: Parser
                -> IO (Either YamlException (Maybe MarkedEvent))
parserParseOne' :: Ptr ParserStruct -> IO (Either YamlException (Maybe MarkedEvent))
parserParseOne' parser :: Ptr ParserStruct
parser = Int
-> (EventRaw -> IO (Either YamlException (Maybe MarkedEvent)))
-> IO (Either YamlException (Maybe MarkedEvent))
forall a b. Int -> (Ptr a -> IO b) -> IO b
allocaBytes Int
eventSize ((EventRaw -> IO (Either YamlException (Maybe MarkedEvent)))
 -> IO (Either YamlException (Maybe MarkedEvent)))
-> (EventRaw -> IO (Either YamlException (Maybe MarkedEvent)))
-> IO (Either YamlException (Maybe MarkedEvent))
forall a b. (a -> b) -> a -> b
$ \er :: EventRaw
er -> do
    CInt
res <- IO CInt -> IO CInt
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO CInt -> IO CInt) -> IO CInt -> IO CInt
forall a b. (a -> b) -> a -> b
$ Ptr ParserStruct -> EventRaw -> IO CInt
c_yaml_parser_parse Ptr ParserStruct
parser EventRaw
er
    (IO (Either YamlException (Maybe MarkedEvent))
 -> IO () -> IO (Either YamlException (Maybe MarkedEvent)))
-> IO ()
-> IO (Either YamlException (Maybe MarkedEvent))
-> IO (Either YamlException (Maybe MarkedEvent))
forall a b c. (a -> b -> c) -> b -> a -> c
flip IO (Either YamlException (Maybe MarkedEvent))
-> IO () -> IO (Either YamlException (Maybe MarkedEvent))
forall a b. IO a -> IO b -> IO a
finally (EventRaw -> IO ()
c_yaml_event_delete EventRaw
er) (IO (Either YamlException (Maybe MarkedEvent))
 -> IO (Either YamlException (Maybe MarkedEvent)))
-> IO (Either YamlException (Maybe MarkedEvent))
-> IO (Either YamlException (Maybe MarkedEvent))
forall a b. (a -> b) -> a -> b
$
      if CInt
res CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
== 0
        then do
          String
problem <- (Ptr ParserStruct -> IO (Ptr CUChar))
-> Ptr ParserStruct -> IO String
forall (m :: * -> *) a.
MonadIO m =>
(a -> m (Ptr CUChar)) -> a -> m String
makeString Ptr ParserStruct -> IO (Ptr CUChar)
c_get_parser_error_problem Ptr ParserStruct
parser
          String
context <- (Ptr ParserStruct -> IO (Ptr CUChar))
-> Ptr ParserStruct -> IO String
forall (m :: * -> *) a.
MonadIO m =>
(a -> m (Ptr CUChar)) -> a -> m String
makeString Ptr ParserStruct -> IO (Ptr CUChar)
c_get_parser_error_context Ptr ParserStruct
parser
          YamlMark
problemMark <- Ptr ParserStruct -> IO MarkRaw
c_get_parser_error_mark Ptr ParserStruct
parser IO MarkRaw -> (MarkRaw -> IO YamlMark) -> IO YamlMark
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= MarkRaw -> IO YamlMark
getMark
          Either YamlException (Maybe MarkedEvent)
-> IO (Either YamlException (Maybe MarkedEvent))
forall (m :: * -> *) a. Monad m => a -> m a
return (Either YamlException (Maybe MarkedEvent)
 -> IO (Either YamlException (Maybe MarkedEvent)))
-> Either YamlException (Maybe MarkedEvent)
-> IO (Either YamlException (Maybe MarkedEvent))
forall a b. (a -> b) -> a -> b
$ YamlException -> Either YamlException (Maybe MarkedEvent)
forall a b. a -> Either a b
Left (YamlException -> Either YamlException (Maybe MarkedEvent))
-> YamlException -> Either YamlException (Maybe MarkedEvent)
forall a b. (a -> b) -> a -> b
$ String -> String -> YamlMark -> YamlException
YamlParseException String
problem String
context YamlMark
problemMark
        else Maybe MarkedEvent -> Either YamlException (Maybe MarkedEvent)
forall a b. b -> Either a b
Right (Maybe MarkedEvent -> Either YamlException (Maybe MarkedEvent))
-> IO (Maybe MarkedEvent)
-> IO (Either YamlException (Maybe MarkedEvent))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> EventRaw -> IO (Maybe MarkedEvent)
getEvent EventRaw
er

-- | Whether a tag should be rendered explicitly in the output or left
-- implicit.
--
-- @since 0.1.1.0
data TagRender = Explicit | Implicit
  deriving (Int -> TagRender
TagRender -> Int
TagRender -> [TagRender]
TagRender -> TagRender
TagRender -> TagRender -> [TagRender]
TagRender -> TagRender -> TagRender -> [TagRender]
(TagRender -> TagRender)
-> (TagRender -> TagRender)
-> (Int -> TagRender)
-> (TagRender -> Int)
-> (TagRender -> [TagRender])
-> (TagRender -> TagRender -> [TagRender])
-> (TagRender -> TagRender -> [TagRender])
-> (TagRender -> TagRender -> TagRender -> [TagRender])
-> Enum TagRender
forall a.
(a -> a)
-> (a -> a)
-> (Int -> a)
-> (a -> Int)
-> (a -> [a])
-> (a -> a -> [a])
-> (a -> a -> [a])
-> (a -> a -> a -> [a])
-> Enum a
enumFromThenTo :: TagRender -> TagRender -> TagRender -> [TagRender]
$cenumFromThenTo :: TagRender -> TagRender -> TagRender -> [TagRender]
enumFromTo :: TagRender -> TagRender -> [TagRender]
$cenumFromTo :: TagRender -> TagRender -> [TagRender]
enumFromThen :: TagRender -> TagRender -> [TagRender]
$cenumFromThen :: TagRender -> TagRender -> [TagRender]
enumFrom :: TagRender -> [TagRender]
$cenumFrom :: TagRender -> [TagRender]
fromEnum :: TagRender -> Int
$cfromEnum :: TagRender -> Int
toEnum :: Int -> TagRender
$ctoEnum :: Int -> TagRender
pred :: TagRender -> TagRender
$cpred :: TagRender -> TagRender
succ :: TagRender -> TagRender
$csucc :: TagRender -> TagRender
Enum)

toImplicitParam :: TagRender -> CInt
toImplicitParam :: TagRender -> CInt
toImplicitParam Explicit = 0
toImplicitParam Implicit = 1

-- | A value for 'formatOptionsRenderTags' that renders no
-- collection tags but all scalar tags (unless suppressed with styles
-- 'NoTag or 'PlainNoTag').
--
-- @since 0.1.1.0
renderScalarTags :: Event -> TagRender
renderScalarTags :: Event -> TagRender
renderScalarTags (EventScalar _ _ _ _) = TagRender
Explicit
renderScalarTags (EventSequenceStart _ _ _) = TagRender
Implicit
renderScalarTags (EventMappingStart _ _ _) = TagRender
Implicit
renderScalarTags _ = TagRender
Implicit

-- | A value for 'formatOptionsRenderTags' that renders all
-- tags (except 'NoTag' tag and 'PlainNoTag' style).
--
-- @since 0.1.1.0
renderAllTags :: Event -> TagRender
renderAllTags :: Event -> TagRender
renderAllTags _ = TagRender
Explicit

-- | A value for 'formatOptionsRenderTags' that renders no
-- tags.
--
-- @since 0.1.1.0
renderNoTags :: Event -> TagRender
renderNoTags :: Event -> TagRender
renderNoTags _ = TagRender
Implicit

-- | A value for 'formatOptionsRenderCollectionTags' that renders tags
-- which are instances of 'UriTag'
--
-- @since 0.1.1.0
renderUriTags :: Event -> TagRender
renderUriTags :: Event -> TagRender
renderUriTags (EventScalar _ UriTag{} _ _) = TagRender
Explicit
renderUriTags (EventSequenceStart UriTag{} _ _) = TagRender
Explicit
renderUriTags (EventMappingStart UriTag{} _ _) = TagRender
Explicit
renderUriTags _ = TagRender
Implicit

-- | Contains options relating to the formatting (indendation, width) of the YAML output.
--
-- @since 0.10.2.0
data FormatOptions = FormatOptions
    { FormatOptions -> Maybe Int
formatOptionsWidth :: Maybe Int
    , FormatOptions -> Event -> TagRender
formatOptionsRenderTags :: Event -> TagRender
    }

-- |
-- @since 0.10.2.0
defaultFormatOptions :: FormatOptions
defaultFormatOptions :: FormatOptions
defaultFormatOptions = FormatOptions :: Maybe Int -> (Event -> TagRender) -> FormatOptions
FormatOptions
    { formatOptionsWidth :: Maybe Int
formatOptionsWidth = Int -> Maybe Int
forall a. a -> Maybe a
Just 80 -- by default the width is set to 0 in the C code, which gets turned into 80 in yaml_emitter_emit_stream_start
    , formatOptionsRenderTags :: Event -> TagRender
formatOptionsRenderTags = Event -> TagRender
renderScalarTags
    }

-- | Set the maximum number of columns in the YAML output, or 'Nothing' for infinite. By default, the limit is 80 characters.
--
-- @since 0.10.2.0
setWidth :: Maybe Int -> FormatOptions -> FormatOptions
setWidth :: Maybe Int -> FormatOptions -> FormatOptions
setWidth w :: Maybe Int
w opts :: FormatOptions
opts = FormatOptions
opts { formatOptionsWidth :: Maybe Int
formatOptionsWidth = Maybe Int
w }

-- | Control when and whether tags are rendered to output.
--
-- @since 0.1.1.0
setTagRendering :: (Event -> TagRender) -> FormatOptions -> FormatOptions
setTagRendering :: (Event -> TagRender) -> FormatOptions -> FormatOptions
setTagRendering f :: Event -> TagRender
f opts :: FormatOptions
opts = FormatOptions
opts { formatOptionsRenderTags :: Event -> TagRender
formatOptionsRenderTags = Event -> TagRender
f }

encode :: MonadResource m => ConduitM Event o m ByteString
encode :: ConduitM Event o m ByteString
encode = FormatOptions -> ConduitM Event o m ByteString
forall (m :: * -> *) o.
MonadResource m =>
FormatOptions -> ConduitM Event o m ByteString
encodeWith FormatOptions
defaultFormatOptions

-- |
-- @since 0.10.2.0
encodeWith :: MonadResource m => FormatOptions -> ConduitM Event o m ByteString
encodeWith :: FormatOptions -> ConduitM Event o m ByteString
encodeWith opts :: FormatOptions
opts =
    FormatOptions
-> (Emitter -> IO (ForeignPtr BufferStruct))
-> (() -> ForeignPtr BufferStruct -> IO ByteString)
-> ConduitM Event o m ByteString
forall (m :: * -> *) a b o.
MonadResource m =>
FormatOptions
-> (Emitter -> IO a) -> (() -> a -> IO b) -> ConduitM Event o m b
runEmitter FormatOptions
opts Emitter -> IO (ForeignPtr BufferStruct)
alloc () -> ForeignPtr BufferStruct -> IO ByteString
forall p. p -> ForeignPtr BufferStruct -> IO ByteString
close
  where
    alloc :: Emitter -> IO (ForeignPtr BufferStruct)
alloc emitter :: Emitter
emitter = do
        ForeignPtr BufferStruct
fbuf <- Int -> IO (ForeignPtr BufferStruct)
forall a. Int -> IO (ForeignPtr a)
mallocForeignPtrBytes Int
bufferSize
        ForeignPtr BufferStruct -> (Ptr BufferStruct -> IO ()) -> IO ()
forall a b. ForeignPtr a -> (Ptr a -> IO b) -> IO b
withForeignPtr ForeignPtr BufferStruct
fbuf Ptr BufferStruct -> IO ()
c_buffer_init
        ForeignPtr BufferStruct -> (Ptr BufferStruct -> IO ()) -> IO ()
forall a b. ForeignPtr a -> (Ptr a -> IO b) -> IO b
withForeignPtr ForeignPtr BufferStruct
fbuf ((Ptr BufferStruct -> IO ()) -> IO ())
-> (Ptr BufferStruct -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ Emitter -> Ptr BufferStruct -> IO ()
c_my_emitter_set_output Emitter
emitter
        ForeignPtr BufferStruct -> IO (ForeignPtr BufferStruct)
forall (m :: * -> *) a. Monad m => a -> m a
return ForeignPtr BufferStruct
fbuf
    close :: p -> ForeignPtr BufferStruct -> IO ByteString
close _ fbuf :: ForeignPtr BufferStruct
fbuf = ForeignPtr BufferStruct
-> (Ptr BufferStruct -> IO ByteString) -> IO ByteString
forall a b. ForeignPtr a -> (Ptr a -> IO b) -> IO b
withForeignPtr ForeignPtr BufferStruct
fbuf ((Ptr BufferStruct -> IO ByteString) -> IO ByteString)
-> (Ptr BufferStruct -> IO ByteString) -> IO ByteString
forall a b. (a -> b) -> a -> b
$ \b :: Ptr BufferStruct
b -> do
        Ptr CUChar
ptr' <- Ptr BufferStruct -> IO (Ptr CUChar)
c_get_buffer_buff Ptr BufferStruct
b
        CULong
len <- Ptr BufferStruct -> IO CULong
c_get_buffer_used Ptr BufferStruct
b
        ForeignPtr Word8
fptr <- Ptr Word8 -> IO (ForeignPtr Word8)
forall a. Ptr a -> IO (ForeignPtr a)
newForeignPtr_ (Ptr Word8 -> IO (ForeignPtr Word8))
-> Ptr Word8 -> IO (ForeignPtr Word8)
forall a b. (a -> b) -> a -> b
$ Ptr CUChar -> Ptr Word8
forall a b. Ptr a -> Ptr b
castPtr Ptr CUChar
ptr'
        ByteString -> IO ByteString
forall (m :: * -> *) a. Monad m => a -> m a
return (ByteString -> IO ByteString) -> ByteString -> IO ByteString
forall a b. (a -> b) -> a -> b
$ ForeignPtr Word8 -> Int -> Int -> ByteString
B.fromForeignPtr ForeignPtr Word8
fptr 0 (Int -> ByteString) -> Int -> ByteString
forall a b. (a -> b) -> a -> b
$ CULong -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral CULong
len


encodeFile :: MonadResource m
           => FilePath
           -> ConduitM Event o m ()
encodeFile :: String -> ConduitM Event o m ()
encodeFile = FormatOptions -> String -> ConduitM Event o m ()
forall (m :: * -> *) o.
MonadResource m =>
FormatOptions -> String -> ConduitM Event o m ()
encodeFileWith FormatOptions
defaultFormatOptions

-- |
-- @since 0.10.2.0
encodeFileWith :: MonadResource m
           => FormatOptions
           -> FilePath
           -> ConduitM Event o m ()
encodeFileWith :: FormatOptions -> String -> ConduitM Event o m ()
encodeFileWith opts :: FormatOptions
opts filePath :: String
filePath =
    IO File
-> (File -> IO ())
-> (File -> ConduitM Event o m ())
-> ConduitM Event o m ()
forall (m :: * -> *) a i o r.
MonadResource m =>
IO a -> (a -> IO ()) -> (a -> ConduitT i o m r) -> ConduitT i o m r
bracketP IO File
getFile File -> IO ()
c_fclose ((File -> ConduitM Event o m ()) -> ConduitM Event o m ())
-> (File -> ConduitM Event o m ()) -> ConduitM Event o m ()
forall a b. (a -> b) -> a -> b
$ \file :: File
file -> FormatOptions
-> (Emitter -> IO ())
-> (() -> () -> IO ())
-> ConduitM Event o m ()
forall (m :: * -> *) a b o.
MonadResource m =>
FormatOptions
-> (Emitter -> IO a) -> (() -> a -> IO b) -> ConduitM Event o m b
runEmitter FormatOptions
opts (File -> Emitter -> IO ()
alloc File
file) (\u :: ()
u _ -> () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
u)
  where
    getFile :: IO File
getFile = do
#if WINDOWS && __GLASGOW_HASKELL__ >= 806
        -- See: https://github.com/snoyberg/yaml/issues/178#issuecomment-550180027
        removeFile filePath `Control.Exception.catch`
          (\(_ :: Control.Exception.IOException) -> pure ())
#endif
        File
file <- String -> CInt -> String -> IO File
openFile String
filePath CInt
write_flags "w"
        if File
file File -> File -> Bool
forall a. Eq a => a -> a -> Bool
== File
forall a. Ptr a
nullPtr
            then YamlException -> IO File
forall e a. Exception e => e -> IO a
throwIO (YamlException -> IO File) -> YamlException -> IO File
forall a b. (a -> b) -> a -> b
$ String -> YamlException
YamlException (String -> YamlException) -> String -> YamlException
forall a b. (a -> b) -> a -> b
$ "could not open file for write: " String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
filePath
            else File -> IO File
forall (m :: * -> *) a. Monad m => a -> m a
return File
file

    alloc :: File -> Emitter -> IO ()
alloc file :: File
file emitter :: Emitter
emitter = Emitter -> File -> IO ()
c_yaml_emitter_set_output_file Emitter
emitter File
file

runEmitter :: MonadResource m
           => FormatOptions
           -> (Emitter -> IO a) -- ^ alloc
           -> (() -> a -> IO b) -- ^ close
           -> ConduitM Event o m b
runEmitter :: FormatOptions
-> (Emitter -> IO a) -> (() -> a -> IO b) -> ConduitM Event o m b
runEmitter opts :: FormatOptions
opts allocI :: Emitter -> IO a
allocI closeI :: () -> a -> IO b
closeI =
    IO (Emitter, a)
-> ((Emitter, a) -> IO ())
-> ((Emitter, a) -> ConduitM Event o m b)
-> ConduitM Event o m b
forall (m :: * -> *) a i o r.
MonadResource m =>
IO a -> (a -> IO ()) -> (a -> ConduitT i o m r) -> ConduitT i o m r
bracketP IO (Emitter, a)
alloc (Emitter, a) -> IO ()
forall b. (Emitter, b) -> IO ()
cleanup (Emitter, a) -> ConduitM Event o m b
go
  where
    alloc :: IO (Emitter, a)
alloc = IO (Emitter, a) -> IO (Emitter, a)
forall a. IO a -> IO a
mask_ (IO (Emitter, a) -> IO (Emitter, a))
-> IO (Emitter, a) -> IO (Emitter, a)
forall a b. (a -> b) -> a -> b
$ do
        Emitter
emitter <- Int -> IO Emitter
forall a. Int -> IO (Ptr a)
mallocBytes Int
emitterSize
        CInt
res <- Emitter -> IO CInt
c_yaml_emitter_initialize Emitter
emitter
        Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (CInt
res CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
== 0) (IO () -> IO ()) -> IO () -> IO ()
forall a b. (a -> b) -> a -> b
$ YamlException -> IO ()
forall e a. Exception e => e -> IO a
throwIO (YamlException -> IO ()) -> YamlException -> IO ()
forall a b. (a -> b) -> a -> b
$ String -> YamlException
YamlException "c_yaml_emitter_initialize failed"
#ifndef __NO_UNICODE__
        Emitter -> CInt -> IO ()
c_yaml_emitter_set_unicode Emitter
emitter 1
#endif
        Emitter -> CInt -> IO ()
c_yaml_emitter_set_width Emitter
emitter (CInt -> IO ()) -> CInt -> IO ()
forall a b. (a -> b) -> a -> b
$ case FormatOptions -> Maybe Int
formatOptionsWidth FormatOptions
opts of
            Nothing -> -1 --infinite
            Just width :: Int
width -> Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
width
        a
a <- Emitter -> IO a
allocI Emitter
emitter
        (Emitter, a) -> IO (Emitter, a)
forall (m :: * -> *) a. Monad m => a -> m a
return (Emitter
emitter, a
a)
    cleanup :: (Emitter, b) -> IO ()
cleanup (emitter :: Emitter
emitter, _) = do
        Emitter -> IO ()
c_yaml_emitter_delete Emitter
emitter
        Emitter -> IO ()
forall a. Ptr a -> IO ()
free Emitter
emitter

    go :: (Emitter, a) -> ConduitM Event o m b
go (emitter :: Emitter
emitter, a :: a
a) =
        ConduitM Event o m b
loop
      where
        loop :: ConduitM Event o m b
loop = ConduitT Event o m (Maybe Event)
forall (m :: * -> *) i. Monad m => Consumer i m (Maybe i)
await ConduitT Event o m (Maybe Event)
-> (Maybe Event -> ConduitM Event o m b) -> ConduitM Event o m b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= ConduitM Event o m b
-> (Event -> ConduitM Event o m b)
-> Maybe Event
-> ConduitM Event o m b
forall b a. b -> (a -> b) -> Maybe a -> b
maybe (() -> ConduitM Event o m b
close ()) Event -> ConduitM Event o m b
push

        push :: Event -> ConduitM Event o m b
push e :: Event
e = do
            CInt
_ <- IO CInt -> ConduitT Event o m CInt
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO CInt -> ConduitT Event o m CInt)
-> IO CInt -> ConduitT Event o m CInt
forall a b. (a -> b) -> a -> b
$ FormatOptions -> Event -> (EventRaw -> IO CInt) -> IO CInt
forall a. FormatOptions -> Event -> (EventRaw -> IO a) -> IO a
toEventRaw FormatOptions
opts Event
e ((EventRaw -> IO CInt) -> IO CInt)
-> (EventRaw -> IO CInt) -> IO CInt
forall a b. (a -> b) -> a -> b
$ Emitter -> EventRaw -> IO CInt
c_yaml_emitter_emit Emitter
emitter
            ConduitM Event o m b
loop
        close :: () -> ConduitM Event o m b
close u :: ()
u = IO b -> ConduitM Event o m b
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO b -> ConduitM Event o m b) -> IO b -> ConduitM Event o m b
forall a b. (a -> b) -> a -> b
$ () -> a -> IO b
closeI ()
u a
a

-- | The pointer position
data YamlMark = YamlMark { YamlMark -> Int
yamlIndex :: Int, YamlMark -> Int
yamlLine :: Int, YamlMark -> Int
yamlColumn :: Int }
    deriving Int -> YamlMark -> ShowS
[YamlMark] -> ShowS
YamlMark -> String
(Int -> YamlMark -> ShowS)
-> (YamlMark -> String) -> ([YamlMark] -> ShowS) -> Show YamlMark
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [YamlMark] -> ShowS
$cshowList :: [YamlMark] -> ShowS
show :: YamlMark -> String
$cshow :: YamlMark -> String
showsPrec :: Int -> YamlMark -> ShowS
$cshowsPrec :: Int -> YamlMark -> ShowS
Show

data YamlException = YamlException String
                   -- | problem, context, index, position line, position column
                   | YamlParseException { YamlException -> String
yamlProblem :: String, YamlException -> String
yamlContext :: String, YamlException -> YamlMark
yamlProblemMark :: YamlMark }
    deriving (Int -> YamlException -> ShowS
[YamlException] -> ShowS
YamlException -> String
(Int -> YamlException -> ShowS)
-> (YamlException -> String)
-> ([YamlException] -> ShowS)
-> Show YamlException
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [YamlException] -> ShowS
$cshowList :: [YamlException] -> ShowS
show :: YamlException -> String
$cshow :: YamlException -> String
showsPrec :: Int -> YamlException -> ShowS
$cshowsPrec :: Int -> YamlException -> ShowS
Show, Typeable)
instance Exception YamlException