Skip to content

Commit

Permalink
conduit 1.0
Browse files Browse the repository at this point in the history
  • Loading branch information
snoyberg committed Feb 10, 2013
1 parent f3436f3 commit dee4776
Show file tree
Hide file tree
Showing 2 changed files with 55 additions and 5 deletions.
58 changes: 54 additions & 4 deletions Text/Libyaml.hs
Original file line number Diff line number Diff line change
Expand Up @@ -8,6 +8,7 @@
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE CPP #-}
{-# LANGUAGE TypeFamilies #-}

-- | Low-level, streaming YAML interface. For a higher-level interface, see
-- "Data.Yaml".
Expand Down Expand Up @@ -464,7 +465,12 @@ newtype ToEventRawException = ToEventRawException CInt
deriving (Show, Typeable)
instance Exception ToEventRawException

decode :: MonadResource m => B.ByteString -> GSource m Event
decode :: MonadResource m => B.ByteString
#if MIN_VERSION_conduit(1, 0, 0)
-> MonadSource m Event
#else
-> GSource m Event
#endif
decode bs | B8.null bs = return ()
decode bs =
bracketP alloc cleanup (runParser . fst)
Expand All @@ -488,7 +494,12 @@ decode bs =
c_yaml_parser_delete ptr
free ptr

decodeFile :: MonadResource m => FilePath -> GSource m Event
decodeFile :: MonadResource m => FilePath
#if MIN_VERSION_conduit(1, 0, 0)
-> MonadSource m Event
#else
-> GSource m Event
#endif
decodeFile file =
bracketP alloc cleanup (runParser . fst)
where
Expand Down Expand Up @@ -519,11 +530,24 @@ decodeFile file =
c_yaml_parser_delete ptr
free ptr

runParser :: MonadResource m => Parser -> GSource m Event
runParser :: MonadResource m => Parser
#if MIN_VERSION_conduit(1, 0, 0)
-> MonadSource m Event
#else
-> GSource m Event
#endif
runParser parser = do
#if MIN_VERSION_conduit(1, 0, 0)
e <- liftStreamIO $ parserParseOne' parser
#else
e <- liftIO $ parserParseOne' parser
#endif
case e of
#if MIN_VERSION_conduit(1, 0, 0)
Left err -> liftStreamIO $ throwIO err
#else
Left err -> liftIO $ throwIO err
#endif
Right Nothing -> return ()
Right (Just ev) -> yield ev >> runParser parser

Expand All @@ -543,7 +567,12 @@ parserParseOne' parser = allocaBytes eventSize $ \er -> do
return $ Left $ YamlParseException problem context problemMark
else Right <$> getEvent er

encode :: MonadResource m => GSink Event m ByteString
encode :: MonadResource m
#if MIN_VERSION_conduit(1, 0, 0)
=> MonadSink Event m ByteString
#else
=> GSink Event m ByteString
#endif
encode =
runEmitter alloc close
where
Expand All @@ -560,7 +589,11 @@ encode =

encodeFile :: MonadResource m
=> FilePath
#if MIN_VERSION_conduit(1, 0, 0)
-> MonadSink Event m ()
#else
-> GInfSink Event m
#endif
encodeFile filePath =
bracketP getFile c_fclose $ \file -> runEmitter (alloc file) (\u _ -> return u)
where
Expand All @@ -576,8 +609,13 @@ encodeFile filePath =

runEmitter :: MonadResource m
=> (Emitter -> IO a) -- ^ alloc
#if MIN_VERSION_conduit(1, 0, 0)
-> (() -> a -> IO b) -- ^ close
-> MonadSink Event m b
#else
-> (u -> a -> IO b) -- ^ close
-> Pipe l Event o u m b
#endif
runEmitter allocI closeI =
bracketP alloc cleanup go
where
Expand All @@ -594,11 +632,23 @@ runEmitter allocI closeI =
go (emitter, a) =
loop
where
#if MIN_VERSION_conduit(1, 0, 0)
loop = await >>= maybe (close ()) push
#else
loop = awaitE >>= either close push
#endif

#if MIN_VERSION_conduit(1, 0, 0)
push e = do
_ <- liftStreamIO $ toEventRaw e $ c_yaml_emitter_emit emitter
loop
close u = liftStreamIO $ closeI u a
#else
push e = do
_ <- liftIO $ toEventRaw e $ c_yaml_emitter_emit emitter
loop
close u = liftIO $ closeI u a
#endif

-- | The pointer position
data YamlMark = YamlMark { yamlIndex :: Int, yamlLine :: Int, yamlColumn :: Int }
Expand Down
2 changes: 1 addition & 1 deletion yaml.cabal
Original file line number Diff line number Diff line change
Expand Up @@ -36,7 +36,7 @@ library
build-depends: base >= 4 && < 5
, transformers >= 0.1 && < 0.4
, bytestring >= 0.9.1.4
, conduit >= 0.5 && < 0.6
, conduit >= 0.5 && < 1.1
, resourcet >= 0.3 && < 0.5
, aeson >= 0.5
, containers
Expand Down

0 comments on commit dee4776

Please sign in to comment.