{-# LANGUAGE EmptyDataDecls #-}
{-# LANGUAGE ForeignFunctionInterface #-}
{-# LANGUAGE DeriveDataTypeable #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE CPP #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE StrictData #-}
{-# LANGUAGE BangPatterns #-}
{-# LANGUAGE DeriveGeneric, DeriveAnyClass #-}
module Text.Libyaml
(
MarkedEvent(..)
, Event (..)
, Style (..)
, SequenceStyle (..)
, MappingStyle (..)
, Tag (..)
, AnchorName
, Anchor
, encode
, encodeWith
, decode
, decodeMarked
, encodeFile
, decodeFile
, decodeFileMarked
, encodeFileWith
, FormatOptions
, defaultFormatOptions
, setWidth
, setTagRendering
, renderScalarTags
, renderAllTags
, renderNoTags
, renderUriTags
, 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.Monad
import Control.Monad.IO.Class
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)
#endif
import GHC.Generics (Generic)
import Control.DeepSeq
import Control.Exception.Safe
import qualified Streamly.Internal.Data.Stream.StreamD.Type as D
import qualified Streamly.Internal.Data.Unfold as SIU
import Streamly.Prelude hiding (yield, finally, bracket)
import qualified Streamly.Prelude as S
import Streamly.Internal.Data.Unfold.Type
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
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
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, forall x. Rep Event x -> Event
forall x. Event -> Rep Event x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Event x -> Event
$cfrom :: forall x. Event -> Rep Event x
Generic, Event -> ()
forall a. (a -> ()) -> NFData a
rnf :: Event -> ()
$crnf :: Event -> ()
NFData)
data MarkedEvent = MarkedEvent
{ MarkedEvent -> Event
yamlEvent :: Event
, MarkedEvent -> YamlMark
yamlStartMark :: YamlMark
, MarkedEvent -> YamlMark
yamlEndMark :: YamlMark
}
data Style = Any
| Plain
| SingleQuoted
| DoubleQuoted
| Literal
| Folded
| PlainNoTag
deriving (Int -> Style -> ShowS
[Style] -> ShowS
Style -> String
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]
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
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]
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
forall a. a -> a -> Bounded a
maxBound :: Style
$cmaxBound :: Style
minBound :: Style
$cminBound :: Style
Bounded, Eq 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
Ord, Typeable Style
Style -> DataType
Style -> Constr
(forall b. Data b => b -> b) -> Style -> 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)
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(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 (m :: * -> *).
MonadPlus m =>
(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 (m :: * -> *).
Monad m =>
(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 :: forall u. Int -> (forall d. Data d => d -> u) -> Style -> u
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Style -> u
gmapQ :: forall u. (forall d. Data d => d -> u) -> Style -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> Style -> [u]
gmapQr :: forall r r'.
(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 :: forall r r'.
(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 (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(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 (t :: * -> *) (c :: * -> *).
Typeable t =>
(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 (c :: * -> *).
(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 (c :: * -> *).
(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
Data, Typeable, forall x. Rep Style x -> Style
forall x. Style -> Rep Style x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Style x -> Style
$cfrom :: forall x. Style -> Rep Style x
Generic, Style -> ()
forall a. (a -> ()) -> NFData a
rnf :: Style -> ()
$crnf :: Style -> ()
NFData)
data SequenceStyle = AnySequence | BlockSequence | FlowSequence
deriving (Int -> SequenceStyle -> ShowS
[SequenceStyle] -> ShowS
SequenceStyle -> String
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
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]
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
forall a. a -> a -> Bounded a
maxBound :: SequenceStyle
$cmaxBound :: SequenceStyle
minBound :: SequenceStyle
$cminBound :: SequenceStyle
Bounded, Eq 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
Ord, Typeable SequenceStyle
SequenceStyle -> DataType
SequenceStyle -> Constr
(forall b. Data b => b -> b) -> SequenceStyle -> 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)
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(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 (m :: * -> *).
MonadPlus m =>
(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 (m :: * -> *).
Monad m =>
(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 :: forall u. Int -> (forall d. Data d => d -> u) -> SequenceStyle -> u
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> SequenceStyle -> u
gmapQ :: forall u. (forall d. Data d => d -> u) -> SequenceStyle -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> SequenceStyle -> [u]
gmapQr :: forall r r'.
(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 :: forall r r'.
(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 (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(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 (t :: * -> *) (c :: * -> *).
Typeable t =>
(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 (c :: * -> *).
(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 (c :: * -> *).
(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
Data, Typeable, forall x. Rep SequenceStyle x -> SequenceStyle
forall x. SequenceStyle -> Rep SequenceStyle x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep SequenceStyle x -> SequenceStyle
$cfrom :: forall x. SequenceStyle -> Rep SequenceStyle x
Generic, SequenceStyle -> ()
forall a. (a -> ()) -> NFData a
rnf :: SequenceStyle -> ()
$crnf :: SequenceStyle -> ()
NFData)
data MappingStyle = AnyMapping | BlockMapping | FlowMapping
deriving (Int -> MappingStyle -> ShowS
[MappingStyle] -> ShowS
MappingStyle -> String
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
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]
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
forall a. a -> a -> Bounded a
maxBound :: MappingStyle
$cmaxBound :: MappingStyle
minBound :: MappingStyle
$cminBound :: MappingStyle
Bounded, Eq 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
Ord, Typeable MappingStyle
MappingStyle -> DataType
MappingStyle -> Constr
(forall b. Data b => b -> b) -> MappingStyle -> 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)
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(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 (m :: * -> *).
MonadPlus m =>
(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 (m :: * -> *).
Monad m =>
(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 :: forall u. Int -> (forall d. Data d => d -> u) -> MappingStyle -> u
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> MappingStyle -> u
gmapQ :: forall u. (forall d. Data d => d -> u) -> MappingStyle -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> MappingStyle -> [u]
gmapQr :: forall r r'.
(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 :: forall r r'.
(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 (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(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 (t :: * -> *) (c :: * -> *).
Typeable t =>
(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 (c :: * -> *).
(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 (c :: * -> *).
(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
Data, Typeable, forall x. Rep MappingStyle x -> MappingStyle
forall x. MappingStyle -> Rep MappingStyle x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep MappingStyle x -> MappingStyle
$cfrom :: forall x. MappingStyle -> Rep MappingStyle x
Generic, MappingStyle -> ()
forall a. (a -> ()) -> NFData a
rnf :: MappingStyle -> ()
$crnf :: MappingStyle -> ()
NFData)
data Tag = StrTag
| FloatTag
| NullTag
| BoolTag
| SetTag
| IntTag
| SeqTag
| MapTag
| UriTag String
| NoTag
deriving (Int -> Tag -> ShowS
[Tag] -> ShowS
Tag -> String
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
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]
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
Tag -> DataType
Tag -> Constr
(forall b. Data b => b -> b) -> Tag -> 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)
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(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 (m :: * -> *).
MonadPlus m =>
(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 (m :: * -> *).
Monad m =>
(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 :: forall u. Int -> (forall d. Data d => d -> u) -> Tag -> u
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Tag -> u
gmapQ :: forall u. (forall d. Data d => d -> u) -> Tag -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> Tag -> [u]
gmapQr :: forall r r'.
(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 :: forall r r'.
(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 (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(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 (t :: * -> *) (c :: * -> *).
Typeable t =>
(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 (c :: * -> *).
(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 (c :: * -> *).
(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
Data, Typeable, forall x. Rep Tag x -> Tag
forall x. Tag -> Rep Tag x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Tag x -> Tag
$cfrom :: forall x. Tag -> Rep Tag x
Generic, Tag -> ()
forall a. (a -> ()) -> NFData a
rnf :: Tag -> ()
$crnf :: Tag -> ()
NFData)
tagSuppressed :: Tag -> Bool
tagSuppressed :: Tag -> Bool
tagSuppressed (Tag
NoTag) = Bool
True
tagSuppressed (UriTag String
"") = Bool
True
tagSuppressed Tag
_ = Bool
False
type AnchorName = String
type Anchor = Maybe AnchorName
tagToString :: Tag -> String
tagToString :: Tag -> String
tagToString Tag
StrTag = String
"tag:yaml.org,2002:str"
tagToString Tag
FloatTag = String
"tag:yaml.org,2002:float"
tagToString Tag
NullTag = String
"tag:yaml.org,2002:null"
tagToString Tag
BoolTag = String
"tag:yaml.org,2002:bool"
tagToString Tag
SetTag = String
"tag:yaml.org,2002:set"
tagToString Tag
IntTag = String
"tag:yaml.org,2002:int"
tagToString Tag
SeqTag = String
"tag:yaml.org,2002:seq"
tagToString Tag
MapTag = String
"tag:yaml.org,2002:map"
tagToString (UriTag String
s) = String
s
tagToString Tag
NoTag = String
""
bsToTag :: ByteString -> Tag
bsToTag :: ByteString -> Tag
bsToTag = String -> Tag
stringToTag forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> String
B8.unpack
stringToTag :: String -> Tag
stringToTag :: String -> Tag
stringToTag String
"tag:yaml.org,2002:str" = Tag
StrTag
stringToTag String
"tag:yaml.org,2002:float" = Tag
FloatTag
stringToTag String
"tag:yaml.org,2002:null" = Tag
NullTag
stringToTag String
"tag:yaml.org,2002:bool" = Tag
BoolTag
stringToTag String
"tag:yaml.org,2002:set" = Tag
SetTag
stringToTag String
"tag:yaml.org,2002:int" = Tag
IntTag
stringToTag String
"tag:yaml.org,2002:seq" = Tag
SeqTag
stringToTag String
"tag:yaml.org,2002:map" = Tag
MapTag
stringToTag String
"" = Tag
NoTag
stringToTag String
s = String -> Tag
UriTag String
s
data ParserStruct
type Parser = Ptr ParserStruct
parserSize :: Int
parserSize :: Int
parserSize = Int
480
data EventRawStruct
type EventRaw = Ptr EventRawStruct
eventSize :: Int
eventSize :: Int
eventSize = Int
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 MarkRaw
m = Int -> Int -> Int -> YamlMark
YamlMark
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (forall a b. (Integral a, Num b) => a -> b
fromIntegral forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> MarkRaw -> IO CULong
c_get_mark_index MarkRaw
m)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (forall a b. (Integral a, Num b) => a -> b
fromIntegral forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> MarkRaw -> IO CULong
c_get_mark_line MarkRaw
m)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (forall a b. (Integral a, Num b) => a -> b
fromIntegral 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 :: forall (m :: * -> *) a.
MonadIO m =>
(a -> m (Ptr CUChar)) -> a -> m String
makeString a -> m (Ptr CUChar)
f a
a = do
CString
cchar <- forall a b. Ptr a -> Ptr b
castPtr forall (m :: * -> *) a1 r. Monad m => (a1 -> r) -> m a1 -> m r
`liftM` a -> m (Ptr CUChar)
f a
a
if CString
cchar forall a. Eq a => a -> a -> Bool
== forall a. Ptr a
nullPtr
then forall (m :: * -> *) a. Monad m => a -> m a
return String
""
else forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO forall a b. (a -> b) -> a -> b
$ CString -> IO String
peekCString CString
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]
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
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 CString) -> EventRaw -> IO Anchor
readAnchor EventRaw -> IO CString
getAnchor EventRaw
er = do
CString
yanchor <- EventRaw -> IO CString
getAnchor EventRaw
er
if CString
yanchor forall a. Eq a => a -> a -> Bool
== forall a. Ptr a
nullPtr
then forall (m :: * -> *) a. Monad m => a -> m a
return forall a. Maybe a
Nothing
else forall a. a -> Maybe a
Just forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> CString -> IO String
peekCString CString
yanchor
readStyle :: (Enum a) => (EventRaw -> IO CInt) -> EventRaw -> IO a
readStyle :: forall a. Enum a => (EventRaw -> IO CInt) -> EventRaw -> IO a
readStyle EventRaw -> IO CInt
getStyle EventRaw
er = forall a. Enum a => Int -> a
toEnum forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Enum a => a -> Int
fromEnum 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 EventRaw -> IO (Ptr CUChar)
getTag EventRaw
er = ByteString -> Tag
bsToTag forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (EventRaw -> IO (Ptr CUChar)
getTag EventRaw
er forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= CString -> IO ByteString
packCString forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b. Ptr a -> Ptr b
castPtr)
{-# INLINE getEvent #-}
getEvent :: EventRaw -> IO (Maybe MarkedEvent)
getEvent :: EventRaw -> IO (Maybe MarkedEvent)
getEvent 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 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 forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= MarkRaw -> IO YamlMark
getMark
Maybe Event
event <- case forall a. Enum a => Int -> a
toEnum forall a b. (a -> b) -> a -> b
$ forall a. Enum a => a -> Int
fromEnum CInt
et of
EventType
YamlNoEvent -> forall (m :: * -> *) a. Monad m => a -> m a
return forall a. Maybe a
Nothing
EventType
YamlStreamStartEvent -> forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ forall a. a -> Maybe a
Just Event
EventStreamStart
EventType
YamlStreamEndEvent -> forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ forall a. a -> Maybe a
Just Event
EventStreamEnd
EventType
YamlDocumentStartEvent -> forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ forall a. a -> Maybe a
Just Event
EventDocumentStart
EventType
YamlDocumentEndEvent -> forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ forall a. a -> Maybe a
Just Event
EventDocumentEnd
EventType
YamlAliasEvent -> do
CString
yanchor <- EventRaw -> IO CString
c_get_alias_anchor EventRaw
er
String
anchor <- if CString
yanchor forall a. Eq a => a -> a -> Bool
== forall a. Ptr a
nullPtr
then forall a. HasCallStack => String -> a
error String
"got YamlAliasEvent with empty anchor"
else CString -> IO String
peekCString CString
yanchor
forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ forall a. a -> Maybe a
Just forall a b. (a -> b) -> a -> b
$ String -> Event
EventAlias String
anchor
EventType
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' :: CString
yvalue' = forall a b. Ptr a -> Ptr b
castPtr Ptr CUChar
yvalue
let ylen' :: Int
ylen' = forall a. Enum a => a -> Int
fromEnum CULong
ylen
ByteString
bs <- CStringLen -> IO ByteString
packCStringLen (CString
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 <- forall a. Enum a => (EventRaw -> IO CInt) -> EventRaw -> IO a
readStyle EventRaw -> IO CInt
c_get_scalar_style EventRaw
er
Anchor
anchor <- (EventRaw -> IO CString) -> EventRaw -> IO Anchor
readAnchor EventRaw -> IO CString
c_get_scalar_anchor EventRaw
er
forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ forall a. a -> Maybe a
Just forall a b. (a -> b) -> a -> b
$ ByteString -> Tag -> Style -> Anchor -> Event
EventScalar ByteString
bs Tag
tag Style
style Anchor
anchor
EventType
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 <- 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 CString) -> EventRaw -> IO Anchor
readAnchor EventRaw -> IO CString
c_get_sequence_start_anchor EventRaw
er
forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ forall a. a -> Maybe a
Just forall a b. (a -> b) -> a -> b
$ Tag -> SequenceStyle -> Anchor -> Event
EventSequenceStart Tag
tag SequenceStyle
style Anchor
anchor
EventType
YamlSequenceEndEvent -> forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ forall a. a -> Maybe a
Just Event
EventSequenceEnd
EventType
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 <- 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 CString) -> EventRaw -> IO Anchor
readAnchor EventRaw -> IO CString
c_get_mapping_start_anchor EventRaw
er
forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ forall a. a -> Maybe a
Just forall a b. (a -> b) -> a -> b
$ Tag -> MappingStyle -> Anchor -> Event
EventMappingStart Tag
tag MappingStyle
style Anchor
anchor
EventType
YamlMappingEndEvent -> forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ forall a. a -> Maybe a
Just Event
EventMappingEnd
forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ (\Event
e -> Event -> YamlMark -> YamlMark -> MarkedEvent
MarkedEvent Event
e YamlMark
startMark YamlMark
endMark) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Maybe Event
event
data EmitterStruct
type Emitter = Ptr EmitterStruct
emitterSize :: Int
emitterSize :: Int
emitterSize = Int
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 = Int
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
-> Ptr CUChar
-> Ptr CUChar
-> CInt
-> CInt
-> CInt
-> CInt
-> 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 :: forall a. FormatOptions -> Event -> (EventRaw -> IO a) -> IO a
toEventRaw FormatOptions
opts Event
e EventRaw -> IO a
f = forall a b. Int -> (Ptr a -> IO b) -> IO b
allocaBytes Int
eventSize forall a b. (a -> b) -> a -> b
$ \EventRaw
er -> do
CInt
ret <- case Event
e of
Event
EventStreamStart ->
EventRaw -> CInt -> IO CInt
c_yaml_stream_start_event_initialize
EventRaw
er
CInt
0
Event
EventStreamEnd ->
EventRaw -> IO CInt
c_yaml_stream_end_event_initialize EventRaw
er
Event
EventDocumentStart ->
EventRaw -> IO CInt
c_simple_document_start EventRaw
er
Event
EventDocumentEnd ->
EventRaw -> CInt -> IO CInt
c_yaml_document_end_event_initialize EventRaw
er CInt
1
EventScalar ByteString
bs Tag
thetag Style
style0 Anchor
anchor -> do
forall a. ByteString -> (CStringLen -> IO a) -> IO a
BU.unsafeUseAsCStringLen ByteString
bs forall a b. (a -> b) -> a -> b
$ \(CString
value, Int
len) -> do
let value' :: Ptr CUChar
value' = forall a b. Ptr a -> Ptr b
castPtr CString
value :: Ptr CUChar
len' :: CInt
len' = forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
len :: CInt
let thetag' :: String
thetag' = Tag -> String
tagToString Tag
thetag
forall a. String -> (CString -> IO a) -> IO a
withCString String
thetag' forall a b. (a -> b) -> a -> b
$ \CString
tag' -> do
let pi0 :: CInt
pi0 = Event -> CInt
tagsImplicit Event
e
(CInt
pi, Style
style) =
case Style
style0 of
Style
PlainNoTag -> (CInt
1, Style
Plain)
Style
x -> (CInt
pi0, Style
x)
style' :: CInt
style' = forall a. Enum a => Int -> a
toEnum forall a b. (a -> b) -> a -> b
$ forall a. Enum a => a -> Int
fromEnum Style
style
tagP :: Ptr CUChar
tagP = forall a b. Ptr a -> Ptr b
castPtr CString
tag'
case Anchor
anchor of
Anchor
Nothing ->
EventRaw
-> Ptr CUChar
-> Ptr CUChar
-> Ptr CUChar
-> CInt
-> CInt
-> CInt
-> CInt
-> IO CInt
c_yaml_scalar_event_initialize
EventRaw
er
forall a. Ptr a
nullPtr
Ptr CUChar
tagP
Ptr CUChar
value'
CInt
len'
CInt
pi
CInt
pi
CInt
style'
Just String
anchor' ->
forall a. String -> (CString -> IO a) -> IO a
withCString String
anchor' forall a b. (a -> b) -> a -> b
$ \CString
anchorP' -> do
let anchorP :: Ptr CUChar
anchorP = forall a b. Ptr a -> Ptr b
castPtr CString
anchorP'
EventRaw
-> Ptr CUChar
-> Ptr CUChar
-> Ptr CUChar
-> CInt
-> CInt
-> CInt
-> CInt
-> IO CInt
c_yaml_scalar_event_initialize
EventRaw
er
Ptr CUChar
anchorP
Ptr CUChar
tagP
Ptr CUChar
value'
CInt
len'
CInt
0
CInt
pi
CInt
style'
EventSequenceStart Tag
tag SequenceStyle
style Anchor
Nothing ->
forall a. String -> (CString -> IO a) -> IO a
withCString (Tag -> String
tagToString Tag
tag) forall a b. (a -> b) -> a -> b
$ \CString
tag' -> do
let tagP :: Ptr CUChar
tagP = forall a b. Ptr a -> Ptr b
castPtr CString
tag'
EventRaw -> Ptr CUChar -> Ptr CUChar -> CInt -> CInt -> IO CInt
c_yaml_sequence_start_event_initialize
EventRaw
er
forall a. Ptr a
nullPtr
Ptr CUChar
tagP
(Event -> CInt
tagsImplicit Event
e)
(forall a. Enum a => Int -> a
toEnum forall a b. (a -> b) -> a -> b
$ forall a. Enum a => a -> Int
fromEnum SequenceStyle
style)
EventSequenceStart Tag
tag SequenceStyle
style (Just String
anchor) ->
forall a. String -> (CString -> IO a) -> IO a
withCString (Tag -> String
tagToString Tag
tag) forall a b. (a -> b) -> a -> b
$ \CString
tag' -> do
let tagP :: Ptr CUChar
tagP = forall a b. Ptr a -> Ptr b
castPtr CString
tag'
forall a. String -> (CString -> IO a) -> IO a
withCString String
anchor forall a b. (a -> b) -> a -> b
$ \CString
anchor' -> do
let anchorP :: Ptr CUChar
anchorP = forall a b. Ptr a -> Ptr b
castPtr CString
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)
(forall a. Enum a => Int -> a
toEnum forall a b. (a -> b) -> a -> b
$ forall a. Enum a => a -> Int
fromEnum SequenceStyle
style)
Event
EventSequenceEnd ->
EventRaw -> IO CInt
c_yaml_sequence_end_event_initialize EventRaw
er
EventMappingStart Tag
tag MappingStyle
style Anchor
Nothing ->
forall a. String -> (CString -> IO a) -> IO a
withCString (Tag -> String
tagToString Tag
tag) forall a b. (a -> b) -> a -> b
$ \CString
tag' -> do
let tagP :: Ptr CUChar
tagP = forall a b. Ptr a -> Ptr b
castPtr CString
tag'
EventRaw -> Ptr CUChar -> Ptr CUChar -> CInt -> CInt -> IO CInt
c_yaml_mapping_start_event_initialize
EventRaw
er
forall a. Ptr a
nullPtr
Ptr CUChar
tagP
(Event -> CInt
tagsImplicit Event
e)
(forall a. Enum a => Int -> a
toEnum forall a b. (a -> b) -> a -> b
$ forall a. Enum a => a -> Int
fromEnum MappingStyle
style)
EventMappingStart Tag
tag MappingStyle
style (Just String
anchor) ->
forall a. String -> (CString -> IO a) -> IO a
withCString (Tag -> String
tagToString Tag
tag) forall a b. (a -> b) -> a -> b
$ \CString
tag' -> do
forall a. String -> (CString -> IO a) -> IO a
withCString String
anchor forall a b. (a -> b) -> a -> b
$ \CString
anchor' -> do
let tagP :: Ptr CUChar
tagP = forall a b. Ptr a -> Ptr b
castPtr CString
tag'
let anchorP :: Ptr CUChar
anchorP = forall a b. Ptr a -> Ptr b
castPtr CString
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)
(forall a. Enum a => Int -> a
toEnum forall a b. (a -> b) -> a -> b
$ forall a. Enum a => a -> Int
fromEnum MappingStyle
style)
Event
EventMappingEnd ->
EventRaw -> IO CInt
c_yaml_mapping_end_event_initialize EventRaw
er
EventAlias String
anchor ->
forall a. String -> (CString -> IO a) -> IO a
withCString String
anchor forall a b. (a -> b) -> a -> b
$ \CString
anchorP' -> do
let anchorP :: Ptr CUChar
anchorP = forall a b. Ptr a -> Ptr b
castPtr CString
anchorP'
EventRaw -> Ptr CUChar -> IO CInt
c_yaml_alias_event_initialize
EventRaw
er
Ptr CUChar
anchorP
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless (CInt
ret forall a. Eq a => a -> a -> Bool
== CInt
1) forall a b. (a -> b) -> a -> b
$ forall (m :: * -> *) e a. (MonadThrow m, Exception e) => e -> m a
throwIO forall a b. (a -> b) -> a -> b
$ CInt -> ToEventRawException
ToEventRawException CInt
ret
EventRaw -> IO a
f EventRaw
er
where
tagsImplicit :: Event -> CInt
tagsImplicit (EventScalar ByteString
_ Tag
t Style
_ Anchor
_) | Tag -> Bool
tagSuppressed Tag
t = CInt
1
tagsImplicit (EventMappingStart Tag
t MappingStyle
_ Anchor
_) | Tag -> Bool
tagSuppressed Tag
t = CInt
1
tagsImplicit (EventSequenceStart Tag
t SequenceStyle
_ Anchor
_) | Tag -> Bool
tagSuppressed Tag
t = CInt
1
tagsImplicit Event
evt = TagRender -> CInt
toImplicitParam 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
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
{-# INLINE decode #-}
decode :: (MonadCatch m, MonadAsync m, MonadMask m) => B.ByteString -> SerialT m Event
decode :: forall (m :: * -> *).
(MonadCatch m, MonadAsync m, MonadMask m) =>
ByteString -> SerialT m Event
decode = forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap MarkedEvent -> Event
yamlEvent forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (m :: * -> *).
(MonadCatch m, MonadAsync m, MonadMask m) =>
ByteString -> SerialT m MarkedEvent
decodeMarked
{-# INLINE decodeMarked #-}
decodeMarked :: (MonadCatch m, MonadAsync m, MonadMask m) => B.ByteString -> SerialT m MarkedEvent
decodeMarked :: forall (m :: * -> *).
(MonadCatch m, MonadAsync m, MonadMask m) =>
ByteString -> SerialT m MarkedEvent
decodeMarked ByteString
bs'
| ByteString -> Bool
B8.null ByteString
bs' = forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
IsStream t =>
t m a
nil
| Bool
otherwise = forall (t :: (* -> *) -> * -> *) (m :: * -> *) a b.
(IsStream t, Monad m) =>
Unfold m a b -> a -> t m b
unfold (forall (m :: * -> *) a c d b.
(MonadAsync m, MonadCatch m) =>
(a -> m c) -> (c -> m d) -> Unfold m c b -> Unfold m a b
SIU.bracket (forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> IO (Ptr ParserStruct, ForeignPtr Word8)
alloc) (forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall {a}. (Ptr ParserStruct, ForeignPtr a) -> IO ()
cleanup) (forall a c (m :: * -> *) b.
(a -> c) -> Unfold m c b -> Unfold m a b
lmap forall a b. (a, b) -> a
fst forall (m :: * -> *).
MonadIO m =>
Unfold m (Ptr ParserStruct) MarkedEvent
unfoldParser)) ByteString
bs'
where
alloc :: ByteString -> IO (Ptr ParserStruct, ForeignPtr Word8)
alloc ByteString
bs = forall (m :: * -> *) a. MonadMask m => m a -> m a
mask_ forall a b. (a -> b) -> a -> b
$ do
Ptr ParserStruct
ptr <- 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 forall a. Eq a => a -> a -> Bool
== CInt
0
then do
Ptr ParserStruct -> IO ()
c_yaml_parser_delete Ptr ParserStruct
ptr
forall a. Ptr a -> IO ()
free Ptr ParserStruct
ptr
forall (m :: * -> *) e a. (MonadThrow m, Exception e) => e -> m a
throwIO forall a b. (a -> b) -> a -> b
$ String -> YamlException
YamlException String
"Yaml out of memory"
else do
let (ForeignPtr Word8
bsfptr, Int
offset, Int
len) = ByteString -> (ForeignPtr Word8, Int, Int)
B.toForeignPtr ByteString
bs
let bsptrOrig :: Ptr Word8
bsptrOrig = forall a. ForeignPtr a -> Ptr a
unsafeForeignPtrToPtr ForeignPtr Word8
bsfptr
let bsptr :: Ptr CUChar
bsptr = forall a b. Ptr a -> Ptr b
castPtr Ptr Word8
bsptrOrig 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 (forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
len)
forall (m :: * -> *) a. Monad m => a -> m a
return (Ptr ParserStruct
ptr, ForeignPtr Word8
bsfptr)
cleanup :: (Ptr ParserStruct, ForeignPtr a) -> IO ()
cleanup (Ptr ParserStruct
ptr, ForeignPtr a
bsfptr) = do
forall a. ForeignPtr a -> IO ()
touchForeignPtr ForeignPtr a
bsfptr
Ptr ParserStruct -> IO ()
c_yaml_parser_delete Ptr ParserStruct
ptr
forall a. Ptr a -> IO ()
free Ptr ParserStruct
ptr
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 forall a. Bits a => a -> a -> a
.|. CInt
Posix.o_CREAT forall a. Bits a => a -> a -> a
.|. CInt
Posix.o_TRUNC
read_flags :: CInt
read_flags = CInt
std_flags forall a. Bits a => a -> a -> a
.|. CInt
Posix.o_RDONLY
write_flags :: CInt
write_flags = CInt
output_flags forall a. Bits a => a -> a -> a
.|. CInt
Posix.o_WRONLY
openFile :: FilePath -> CInt -> String -> IO File
openFile :: String -> CInt -> String -> IO File
openFile String
file CInt
rawOpenFlags String
openMode = do
CInt
fd <- forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO forall a b. (a -> b) -> a -> b
$ forall a. String -> (CString -> IO a) -> IO a
Posix.withFilePath String
file forall a b. (a -> b) -> a -> b
$ \CString
file' ->
CString -> CInt -> CMode -> IO CInt
Posix.c_open CString
file' CInt
rawOpenFlags CMode
0o666
if CInt
fd forall a. Eq a => a -> a -> Bool
/= (-CInt
1)
then forall a. String -> (CString -> IO a) -> IO a
withCString String
openMode forall a b. (a -> b) -> a -> b
$ \CString
openMode' -> CInt -> CString -> IO File
c_fdopen CInt
fd CString
openMode'
else forall (m :: * -> *) a. Monad m => a -> m a
return forall a. Ptr a
nullPtr
{-# INLINE decodeFile #-}
decodeFile :: (MonadCatch m, MonadAsync m, MonadMask m) => FilePath -> SerialT m Event
decodeFile :: forall (m :: * -> *).
(MonadCatch m, MonadAsync m, MonadMask m) =>
String -> SerialT m Event
decodeFile = forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap MarkedEvent -> Event
yamlEvent forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (m :: * -> *).
(MonadCatch m, MonadAsync m, MonadMask m) =>
String -> SerialT m MarkedEvent
decodeFileMarked
{-# INLINE decodeFileMarked #-}
decodeFileMarked :: (MonadCatch m, MonadAsync m, MonadMask m) => FilePath -> SerialT m MarkedEvent
decodeFileMarked :: forall (m :: * -> *).
(MonadCatch m, MonadAsync m, MonadMask m) =>
String -> SerialT m MarkedEvent
decodeFileMarked = forall (t :: (* -> *) -> * -> *) (m :: * -> *) a b.
(IsStream t, Monad m) =>
Unfold m a b -> a -> t m b
unfold (forall (m :: * -> *) a c d b.
(MonadAsync m, MonadCatch m) =>
(a -> m c) -> (c -> m d) -> Unfold m c b -> Unfold m a b
SIU.bracket (forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> IO (Ptr ParserStruct, File)
alloc) (forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Ptr ParserStruct, File) -> IO ()
cleanup) (forall a c (m :: * -> *) b.
(a -> c) -> Unfold m c b -> Unfold m a b
lmap forall a b. (a, b) -> a
fst forall (m :: * -> *).
MonadIO m =>
Unfold m (Ptr ParserStruct) MarkedEvent
unfoldParser))
where
alloc :: String -> IO (Ptr ParserStruct, File)
alloc String
file = forall (m :: * -> *) a. MonadMask m => m a -> m a
mask_ forall a b. (a -> b) -> a -> b
$ do
Ptr ParserStruct
ptr <- 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 forall a. Eq a => a -> a -> Bool
== CInt
0
then do
Ptr ParserStruct -> IO ()
c_yaml_parser_delete Ptr ParserStruct
ptr
forall a. Ptr a -> IO ()
free Ptr ParserStruct
ptr
forall (m :: * -> *) e a. (MonadThrow m, Exception e) => e -> m a
throwIO forall a b. (a -> b) -> a -> b
$ String -> YamlException
YamlException String
"Yaml out of memory"
else do
File
file' <- String -> CInt -> String -> IO File
openFile String
file CInt
read_flags String
"r"
if File
file' forall a. Eq a => a -> a -> Bool
== forall a. Ptr a
nullPtr
then do
Ptr ParserStruct -> IO ()
c_yaml_parser_delete Ptr ParserStruct
ptr
forall a. Ptr a -> IO ()
free Ptr ParserStruct
ptr
forall (m :: * -> *) e a. (MonadThrow m, Exception e) => e -> m a
throwIO forall a b. (a -> b) -> a -> b
$ String -> YamlException
YamlException
forall a b. (a -> b) -> a -> b
$ String
"Yaml file not found: " forall a. [a] -> [a] -> [a]
++ String
file
else do
Ptr ParserStruct -> File -> IO ()
c_yaml_parser_set_input_file Ptr ParserStruct
ptr File
file'
forall (m :: * -> *) a. Monad m => a -> m a
return (Ptr ParserStruct
ptr, File
file')
cleanup :: (Ptr ParserStruct, File) -> IO ()
cleanup (Ptr ParserStruct
ptr, File
file') = do
File -> IO ()
c_fclose_helper File
file'
Ptr ParserStruct -> IO ()
c_yaml_parser_delete Ptr ParserStruct
ptr
forall a. Ptr a -> IO ()
free Ptr ParserStruct
ptr
{-# INLINE unfoldParser #-}
unfoldParser :: MonadIO m => Unfold m Parser MarkedEvent
unfoldParser :: forall (m :: * -> *).
MonadIO m =>
Unfold m (Ptr ParserStruct) MarkedEvent
unfoldParser = forall (m :: * -> *) a b s.
(s -> m (Step s b)) -> (a -> m s) -> Unfold m a b
Unfold forall {m :: * -> *}.
MonadIO m =>
Ptr ParserStruct -> m (Step (Ptr ParserStruct) MarkedEvent)
step forall (m :: * -> *) a. Monad m => a -> m a
return
where
{-# INLINE [0] step #-}
step :: Ptr ParserStruct -> m (Step (Ptr ParserStruct) MarkedEvent)
step Ptr ParserStruct
parser = do
Either YamlException (Maybe MarkedEvent)
e <- forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO 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 YamlException
err -> forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO forall a b. (a -> b) -> a -> b
$ forall (m :: * -> *) e a. (MonadThrow m, Exception e) => e -> m a
throwIO YamlException
err
Right Maybe MarkedEvent
Nothing -> forall (f :: * -> *) a. Applicative f => a -> f a
pure forall s a. Step s a
D.Stop
Right (Just MarkedEvent
ev) -> forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ forall s a. a -> s -> Step s a
D.Yield MarkedEvent
ev Ptr ParserStruct
parser
parserParseOne' :: Parser
-> IO (Either YamlException (Maybe MarkedEvent))
parserParseOne' :: Ptr ParserStruct -> IO (Either YamlException (Maybe MarkedEvent))
parserParseOne' Ptr ParserStruct
parser = forall a b. Int -> (Ptr a -> IO b) -> IO b
allocaBytes Int
eventSize forall a b. (a -> b) -> a -> b
$ \EventRaw
er -> do
CInt
res <- forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO forall a b. (a -> b) -> a -> b
$ Ptr ParserStruct -> EventRaw -> IO CInt
c_yaml_parser_parse Ptr ParserStruct
parser EventRaw
er
forall a b c. (a -> b -> c) -> b -> a -> c
flip forall (m :: * -> *) a b. MonadMask m => m a -> m b -> m a
finally (EventRaw -> IO ()
c_yaml_event_delete EventRaw
er) forall a b. (a -> b) -> a -> b
$
if CInt
res forall a. Eq a => a -> a -> Bool
== CInt
0
then do
String
problem <- 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 <- 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 forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= MarkRaw -> IO YamlMark
getMark
forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ forall a b. a -> Either a b
Left forall a b. (a -> b) -> a -> b
$ String -> String -> YamlMark -> YamlException
YamlParseException String
problem String
context YamlMark
problemMark
else forall a b. b -> Either a b
Right forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> EventRaw -> IO (Maybe MarkedEvent)
getEvent EventRaw
er
data TagRender = Explicit | Implicit
deriving (Int -> TagRender
TagRender -> Int
TagRender -> [TagRender]
TagRender -> TagRender
TagRender -> TagRender -> [TagRender]
TagRender -> TagRender -> TagRender -> [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 TagRender
Explicit = CInt
0
toImplicitParam TagRender
Implicit = CInt
1
renderScalarTags :: Event -> TagRender
renderScalarTags :: Event -> TagRender
renderScalarTags (EventScalar ByteString
_ Tag
_ Style
_ Anchor
_) = TagRender
Explicit
renderScalarTags (EventSequenceStart Tag
_ SequenceStyle
_ Anchor
_) = TagRender
Implicit
renderScalarTags (EventMappingStart Tag
_ MappingStyle
_ Anchor
_) = TagRender
Implicit
renderScalarTags Event
_ = TagRender
Implicit
renderAllTags :: Event -> TagRender
renderAllTags :: Event -> TagRender
renderAllTags Event
_ = TagRender
Explicit
renderNoTags :: Event -> TagRender
renderNoTags :: Event -> TagRender
renderNoTags Event
_ = TagRender
Implicit
renderUriTags :: Event -> TagRender
renderUriTags :: Event -> TagRender
renderUriTags (EventScalar ByteString
_ UriTag{} Style
_ Anchor
_) = TagRender
Explicit
renderUriTags (EventSequenceStart UriTag{} SequenceStyle
_ Anchor
_) = TagRender
Explicit
renderUriTags (EventMappingStart UriTag{} MappingStyle
_ Anchor
_) = TagRender
Explicit
renderUriTags Event
_ = TagRender
Implicit
data FormatOptions = FormatOptions
{ FormatOptions -> Maybe Int
formatOptionsWidth :: Maybe Int
, FormatOptions -> Event -> TagRender
formatOptionsRenderTags :: Event -> TagRender
}
defaultFormatOptions :: FormatOptions
defaultFormatOptions :: FormatOptions
defaultFormatOptions = FormatOptions
{ formatOptionsWidth :: Maybe Int
formatOptionsWidth = forall a. a -> Maybe a
Just Int
80
, formatOptionsRenderTags :: Event -> TagRender
formatOptionsRenderTags = Event -> TagRender
renderScalarTags
}
setWidth :: Maybe Int -> FormatOptions -> FormatOptions
setWidth :: Maybe Int -> FormatOptions -> FormatOptions
setWidth Maybe Int
w FormatOptions
opts = FormatOptions
opts { formatOptionsWidth :: Maybe Int
formatOptionsWidth = Maybe Int
w }
setTagRendering :: (Event -> TagRender) -> FormatOptions -> FormatOptions
setTagRendering :: (Event -> TagRender) -> FormatOptions -> FormatOptions
setTagRendering Event -> TagRender
f FormatOptions
opts = FormatOptions
opts { formatOptionsRenderTags :: Event -> TagRender
formatOptionsRenderTags = Event -> TagRender
f }
{-# INLINE encode #-}
encode :: (MonadCatch m, MonadAsync m, MonadMask m)
=> SerialT m Event
-> m ByteString
encode :: forall (m :: * -> *).
(MonadCatch m, MonadAsync m, MonadMask m) =>
SerialT m Event -> m ByteString
encode = forall (m :: * -> *).
(MonadCatch m, MonadAsync m, MonadMask m) =>
FormatOptions -> SerialT m Event -> m ByteString
encodeWith FormatOptions
defaultFormatOptions
{-# INLINE encodeWith #-}
encodeWith :: (MonadCatch m, MonadAsync m, MonadMask m)
=> FormatOptions
-> SerialT m Event
-> m ByteString
encodeWith :: forall (m :: * -> *).
(MonadCatch m, MonadAsync m, MonadMask m) =>
FormatOptions -> SerialT m Event -> m ByteString
encodeWith FormatOptions
opts =
forall (m :: * -> *) a b.
(MonadCatch m, MonadAsync m, MonadMask m) =>
FormatOptions
-> (Emitter -> IO a) -> (() -> a -> IO b) -> SerialT m Event -> m b
runEmitter FormatOptions
opts Emitter -> IO (ForeignPtr BufferStruct)
alloc forall {p}. p -> ForeignPtr BufferStruct -> IO ByteString
close
where
alloc :: Emitter -> IO (ForeignPtr BufferStruct)
alloc Emitter
emitter = do
ForeignPtr BufferStruct
fbuf <- forall a. Int -> IO (ForeignPtr a)
mallocForeignPtrBytes Int
bufferSize
forall a b. ForeignPtr a -> (Ptr a -> IO b) -> IO b
withForeignPtr ForeignPtr BufferStruct
fbuf Buffer -> IO ()
c_buffer_init
forall a b. ForeignPtr a -> (Ptr a -> IO b) -> IO b
withForeignPtr ForeignPtr BufferStruct
fbuf forall a b. (a -> b) -> a -> b
$ Emitter -> Buffer -> IO ()
c_my_emitter_set_output Emitter
emitter
forall (m :: * -> *) a. Monad m => a -> m a
return ForeignPtr BufferStruct
fbuf
close :: p -> ForeignPtr BufferStruct -> IO ByteString
close p
_ ForeignPtr BufferStruct
fbuf = forall a b. ForeignPtr a -> (Ptr a -> IO b) -> IO b
withForeignPtr ForeignPtr BufferStruct
fbuf forall a b. (a -> b) -> a -> b
$ \Buffer
b -> do
Ptr CUChar
ptr' <- Buffer -> IO (Ptr CUChar)
c_get_buffer_buff Buffer
b
CULong
len <- Buffer -> IO CULong
c_get_buffer_used Buffer
b
ForeignPtr Word8
fptr <- forall a. Ptr a -> IO (ForeignPtr a)
newForeignPtr_ forall a b. (a -> b) -> a -> b
$ forall a b. Ptr a -> Ptr b
castPtr Ptr CUChar
ptr'
forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ ForeignPtr Word8 -> Int -> Int -> ByteString
B.fromForeignPtr ForeignPtr Word8
fptr Int
0 forall a b. (a -> b) -> a -> b
$ forall a b. (Integral a, Num b) => a -> b
fromIntegral CULong
len
{-# INLINE encodeFile #-}
encodeFile :: (MonadCatch m, MonadAsync m, MonadMask m)
=> FilePath
-> SerialT m Event
-> m ()
encodeFile :: forall (m :: * -> *).
(MonadCatch m, MonadAsync m, MonadMask m) =>
String -> SerialT m Event -> m ()
encodeFile = forall (m :: * -> *).
(MonadCatch m, MonadAsync m, MonadMask m) =>
FormatOptions -> String -> SerialT m Event -> m ()
encodeFileWith FormatOptions
defaultFormatOptions
{-# INLINE encodeFileWith #-}
encodeFileWith :: (MonadCatch m, MonadAsync m, MonadMask m)
=> FormatOptions
-> FilePath
-> SerialT m Event
-> m ()
encodeFileWith :: forall (m :: * -> *).
(MonadCatch m, MonadAsync m, MonadMask m) =>
FormatOptions -> String -> SerialT m Event -> m ()
encodeFileWith FormatOptions
opts String
filePath SerialT m Event
inputStream =
forall (m :: * -> *) a b c.
MonadMask m =>
m a -> (a -> m b) -> (a -> m c) -> m c
bracket (forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO IO File
getFile) (forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO forall b c a. (b -> c) -> (a -> b) -> a -> c
. File -> IO ()
c_fclose) forall a b. (a -> b) -> a -> b
$ \File
file -> forall (m :: * -> *) a b.
(MonadCatch m, MonadAsync m, MonadMask m) =>
FormatOptions
-> (Emitter -> IO a) -> (() -> a -> IO b) -> SerialT m Event -> m b
runEmitter FormatOptions
opts (File -> Emitter -> IO ()
alloc File
file) (\()
u ()
_ -> forall (m :: * -> *) a. Monad m => a -> m a
return ()
u) SerialT m Event
inputStream
where
getFile :: IO File
getFile = do
#if WINDOWS && __GLASGOW_HASKELL__ >= 806
removeFile filePath `Control.Exception.Safe.catch`
(\(_ :: Control.Exception.Safe.IOException) -> pure ())
#endif
File
file <- String -> CInt -> String -> IO File
openFile String
filePath CInt
write_flags String
"w"
if File
file forall a. Eq a => a -> a -> Bool
== forall a. Ptr a
nullPtr
then forall (m :: * -> *) e a. (MonadThrow m, Exception e) => e -> m a
throwIO forall a b. (a -> b) -> a -> b
$ String -> YamlException
YamlException forall a b. (a -> b) -> a -> b
$ String
"could not open file for write: " forall a. [a] -> [a] -> [a]
++ String
filePath
else forall (m :: * -> *) a. Monad m => a -> m a
return File
file
alloc :: File -> Emitter -> IO ()
alloc File
file Emitter
emitter = Emitter -> File -> IO ()
c_yaml_emitter_set_output_file Emitter
emitter File
file
{-# INLINE runEmitter #-}
runEmitter :: (MonadCatch m, MonadAsync m, MonadMask m)
=> FormatOptions
-> (Emitter -> IO a)
-> (() -> a -> IO b)
-> SerialT m Event
-> m b
runEmitter :: forall (m :: * -> *) a b.
(MonadCatch m, MonadAsync m, MonadMask m) =>
FormatOptions
-> (Emitter -> IO a) -> (() -> a -> IO b) -> SerialT m Event -> m b
runEmitter FormatOptions
opts Emitter -> IO a
allocI () -> a -> IO b
closeI SerialT m Event
inputStream =
forall (m :: * -> *) a b c.
MonadMask m =>
m a -> (a -> m b) -> (a -> m c) -> m c
bracket (forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO IO (Emitter, a)
alloc) (forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall {b}. (Emitter, b) -> IO ()
cleanup) (Emitter, a) -> m b
go
where
alloc :: IO (Emitter, a)
alloc = forall (m :: * -> *) a. MonadMask m => m a -> m a
mask_ forall a b. (a -> b) -> a -> b
$ do
Emitter
emitter <- forall a. Int -> IO (Ptr a)
mallocBytes Int
emitterSize
CInt
res <- Emitter -> IO CInt
c_yaml_emitter_initialize Emitter
emitter
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (CInt
res forall a. Eq a => a -> a -> Bool
== CInt
0) forall a b. (a -> b) -> a -> b
$ forall (m :: * -> *) e a. (MonadThrow m, Exception e) => e -> m a
throwIO forall a b. (a -> b) -> a -> b
$ String -> YamlException
YamlException String
"c_yaml_emitter_initialize failed"
#ifndef __NO_UNICODE__
Emitter -> CInt -> IO ()
c_yaml_emitter_set_unicode Emitter
emitter CInt
1
#endif
Emitter -> CInt -> IO ()
c_yaml_emitter_set_width Emitter
emitter forall a b. (a -> b) -> a -> b
$ case FormatOptions -> Maybe Int
formatOptionsWidth FormatOptions
opts of
Maybe Int
Nothing -> -CInt
1
Just Int
width -> forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
width
a
a <- Emitter -> IO a
allocI Emitter
emitter
forall (m :: * -> *) a. Monad m => a -> m a
return (Emitter
emitter, a
a)
cleanup :: (Emitter, b) -> IO ()
cleanup (Emitter
emitter, b
_) = do
Emitter -> IO ()
c_yaml_emitter_delete Emitter
emitter
forall a. Ptr a -> IO ()
free Emitter
emitter
go :: (Emitter, a) -> m b
go (Emitter
emitter, a
a) = do
forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> SerialT m a -> m ()
S.mapM_ Event -> m ()
push SerialT m Event
inputStream
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO forall a b. (a -> b) -> a -> b
$ () -> a -> IO b
closeI () a
a
where
push :: Event -> m ()
push Event
e = forall (f :: * -> *) a. Functor f => f a -> f ()
void forall a b. (a -> b) -> a -> b
$ forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO forall a b. (a -> b) -> a -> b
$ forall a. FormatOptions -> Event -> (EventRaw -> IO a) -> IO a
toEventRaw FormatOptions
opts Event
e forall a b. (a -> b) -> a -> b
$ Emitter -> EventRaw -> IO CInt
c_yaml_emitter_emit Emitter
emitter
data YamlMark = YamlMark { YamlMark -> Int
yamlIndex :: Int, YamlMark -> Int
yamlLine :: Int, YamlMark -> Int
yamlColumn :: Int }
deriving (Int -> YamlMark -> ShowS
[YamlMark] -> ShowS
YamlMark -> String
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, forall x. Rep YamlMark x -> YamlMark
forall x. YamlMark -> Rep YamlMark x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep YamlMark x -> YamlMark
$cfrom :: forall x. YamlMark -> Rep YamlMark x
Generic, YamlMark -> ()
forall a. (a -> ()) -> NFData a
rnf :: YamlMark -> ()
$crnf :: YamlMark -> ()
NFData)
data YamlException = YamlException String
| YamlParseException { YamlException -> String
yamlProblem :: String, YamlException -> String
yamlContext :: String, YamlException -> YamlMark
yamlProblemMark :: YamlMark }
deriving (Int -> YamlException -> ShowS
[YamlException] -> ShowS
YamlException -> String
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, forall x. Rep YamlException x -> YamlException
forall x. YamlException -> Rep YamlException x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep YamlException x -> YamlException
$cfrom :: forall x. YamlException -> Rep YamlException x
Generic, YamlException -> ()
forall a. (a -> ()) -> NFData a
rnf :: YamlException -> ()
$crnf :: YamlException -> ()
NFData)
instance Exception YamlException