module Data.Svfactor.Print (
printSv
, printSvLazy
, printSv'
, printSvLazy'
, printSvText
, printSvTextLazy
, writeSvToFile
, writeSvToHandle
, writeSvToFile'
, writeSvToHandle'
, module Data.Svfactor.Print.Options
) where
import Data.ByteString (ByteString)
import qualified Data.ByteString.Lazy as LBS
import Data.ByteString.Builder as BSB
import Data.Foldable (Foldable (foldMap))
import Data.Semigroup ((<>))
import Data.Text (Text)
import System.IO (BufferMode (BlockBuffering), Handle, hClose, hSetBinaryMode, hSetBuffering, openFile, IOMode (WriteMode))
import Data.Svfactor.Print.Options
import Data.Svfactor.Print.Internal
import Data.Svfactor.Syntax.Sv (Sv (Sv))
svToBuilder :: PrintOptions s -> Sv s -> Builder
svToBuilder opts (Sv sep h rs e) =
foldMap (printHeader opts sep) h <> printRecords opts sep rs <> foldMap printNewline e
writeSvToHandle :: Handle -> Sv ByteString -> IO ()
writeSvToHandle = writeSvToHandle' defaultPrintOptions
writeSvToFile :: FilePath -> Sv ByteString -> IO ()
writeSvToFile = writeSvToFile' defaultPrintOptions
writeSvToHandle' :: PrintOptions s -> Handle -> Sv s -> IO ()
writeSvToHandle' opts h sv = hPutBuilder h (svToBuilder opts sv)
writeSvToFile' :: PrintOptions s -> FilePath -> Sv s -> IO ()
writeSvToFile' opts fp sv = do
h <- openFile fp WriteMode
hSetBuffering h (BlockBuffering Nothing)
hSetBinaryMode h True
writeSvToHandle' opts h sv
hClose h
printSv :: Sv ByteString -> ByteString
printSv = printSv' defaultPrintOptions
printSvLazy :: Sv ByteString -> LBS.ByteString
printSvLazy = printSvLazy' defaultPrintOptions
printSv' :: PrintOptions s -> Sv s -> ByteString
printSv' opts = LBS.toStrict . printSvLazy' opts
printSvLazy' :: PrintOptions s -> Sv s -> LBS.ByteString
printSvLazy' opts = toLazyByteString . svToBuilder opts
printSvText :: Sv Text -> ByteString
printSvText = printSv' textPrintOptions
printSvTextLazy :: Sv Text -> LBS.ByteString
printSvTextLazy = printSvLazy' textPrintOptions