module System.IO.Streams.Csv.Encode
( encodeStream
, encodeStreamWith
, encodeStreamByName
, encodeStreamByNameWith
) where
import Control.Monad (when)
import Data.ByteString (ByteString)
import qualified Data.ByteString.Lazy as BL
import Data.Csv
import Data.IORef
import System.IO.Streams (OutputStream, makeOutputStream)
import qualified System.IO.Streams as Streams
encodeStream :: ToRecord a
=> OutputStream ByteString
-> IO (OutputStream a)
encodeStream :: OutputStream ByteString -> IO (OutputStream a)
encodeStream = EncodeOptions -> OutputStream ByteString -> IO (OutputStream a)
forall a.
ToRecord a =>
EncodeOptions -> OutputStream ByteString -> IO (OutputStream a)
encodeStreamWith EncodeOptions
defaultEncodeOptions
encodeStreamWith :: ToRecord a
=> EncodeOptions
-> OutputStream ByteString
-> IO (OutputStream a)
encodeStreamWith :: EncodeOptions -> OutputStream ByteString -> IO (OutputStream a)
encodeStreamWith EncodeOptions
opts OutputStream ByteString
output = do
IORef EncodeOptions
ref <- EncodeOptions -> IO (IORef EncodeOptions)
forall a. a -> IO (IORef a)
newIORef EncodeOptions
opts
(Maybe a -> IO ()) -> IO (OutputStream a)
forall a. (Maybe a -> IO ()) -> IO (OutputStream a)
makeOutputStream ((EncodeOptions -> [a] -> ByteString)
-> IORef EncodeOptions
-> OutputStream ByteString
-> Maybe a
-> IO ()
forall a.
(EncodeOptions -> [a] -> ByteString)
-> IORef EncodeOptions
-> OutputStream ByteString
-> Maybe a
-> IO ()
dispatch EncodeOptions -> [a] -> ByteString
forall a. ToRecord a => EncodeOptions -> [a] -> ByteString
encodeWith IORef EncodeOptions
ref OutputStream ByteString
output)
encodeStreamByName :: ToNamedRecord a
=> Header
-> OutputStream ByteString
-> IO (OutputStream a)
encodeStreamByName :: Header -> OutputStream ByteString -> IO (OutputStream a)
encodeStreamByName = EncodeOptions
-> Header -> OutputStream ByteString -> IO (OutputStream a)
forall a.
ToNamedRecord a =>
EncodeOptions
-> Header -> OutputStream ByteString -> IO (OutputStream a)
encodeStreamByNameWith EncodeOptions
defaultEncodeOptions
encodeStreamByNameWith :: ToNamedRecord a
=> EncodeOptions
-> Header
-> OutputStream ByteString
-> IO (OutputStream a)
encodeStreamByNameWith :: EncodeOptions
-> Header -> OutputStream ByteString -> IO (OutputStream a)
encodeStreamByNameWith EncodeOptions
opts Header
hdr OutputStream ByteString
output = do
IORef EncodeOptions
ref <- EncodeOptions -> IO (IORef EncodeOptions)
forall a. a -> IO (IORef a)
newIORef EncodeOptions
opts
(Maybe a -> IO ()) -> IO (OutputStream a)
forall a. (Maybe a -> IO ()) -> IO (OutputStream a)
makeOutputStream ((Maybe a -> IO ()) -> IO (OutputStream a))
-> (Maybe a -> IO ()) -> IO (OutputStream a)
forall a b. (a -> b) -> a -> b
$ (EncodeOptions -> [a] -> ByteString)
-> IORef EncodeOptions
-> OutputStream ByteString
-> Maybe a
-> IO ()
forall a.
(EncodeOptions -> [a] -> ByteString)
-> IORef EncodeOptions
-> OutputStream ByteString
-> Maybe a
-> IO ()
dispatch (EncodeOptions -> Header -> [a] -> ByteString
forall a.
ToNamedRecord a =>
EncodeOptions -> Header -> [a] -> ByteString
`encodeByNameWith` Header
hdr) IORef EncodeOptions
ref OutputStream ByteString
output
dispatch :: (EncodeOptions -> [a] -> BL.ByteString)
-> IORef EncodeOptions
-> OutputStream ByteString
-> Maybe a
-> IO ()
dispatch :: (EncodeOptions -> [a] -> ByteString)
-> IORef EncodeOptions
-> OutputStream ByteString
-> Maybe a
-> IO ()
dispatch EncodeOptions -> [a] -> ByteString
_ IORef EncodeOptions
_ OutputStream ByteString
output Maybe a
Nothing = Maybe ByteString -> OutputStream ByteString -> IO ()
forall a. Maybe a -> OutputStream a -> IO ()
Streams.write Maybe ByteString
forall a. Maybe a
Nothing OutputStream ByteString
output
dispatch EncodeOptions -> [a] -> ByteString
enc IORef EncodeOptions
ref OutputStream ByteString
output (Just a
x) = do
EncodeOptions
opts <- IORef EncodeOptions -> IO EncodeOptions
forall a. IORef a -> IO a
readIORef IORef EncodeOptions
ref
Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (EncodeOptions -> Bool
encIncludeHeader EncodeOptions
opts) (IO () -> IO ()) -> IO () -> IO ()
forall a b. (a -> b) -> a -> b
$ IORef EncodeOptions -> EncodeOptions -> IO ()
forall a. IORef a -> a -> IO ()
writeIORef IORef EncodeOptions
ref (EncodeOptions
opts {encIncludeHeader :: Bool
encIncludeHeader = Bool
False})
ByteString -> OutputStream ByteString -> IO ()
Streams.writeLazyByteString (EncodeOptions -> [a] -> ByteString
enc EncodeOptions
opts [a
x]) OutputStream ByteString
output