module Text.PageIO.Run where import Data.Maybe import Text.PageIO.Types import System.IO import Data.ByteString.Unsafe import Data.ByteString.Lazy.Internal (defaultChunkSize) import qualified Data.ByteString.Char8 as S import qualified Data.ByteString.Lazy.Char8 as L readPages :: FilePath -> IO [Page] readPages fn = openBinaryFile fn ReadMode >>= hReadPages hReadPages :: Handle -> IO [Page] hReadPages fh = do hSetBinaryMode fh True sz <- hFileSize fh -- Cutoff is 64MB; we map the data directly to memory if it's less than that amount if sz > 64 * 1024 * 1024 then hReadPagesLazy fh else hReadPagesStrict fh (fromEnum sz) hReadPagesLazy :: Handle -> IO [Page] hReadPagesLazy fh = do hSetBuffering fh (BlockBuffering (Just defaultChunkSize)) content <- L.hGetContents fh return $ case map (S.concat . L.toChunks) (L.split '\x0C' content) of [] -> [] (hd:tl) -> map (MkPage . map dropCR . S.lines) (hd:map (S.tail . S.dropWhile (/= '\n')) tl) where dropCR x | S.null x = S.copy x | S.last x == '\r' = S.copy (S.init x) | otherwise = S.copy x hReadPagesStrict :: Handle -> Int -> IO [Page] hReadPagesStrict fh sz = do hSetBuffering fh (BlockBuffering (Just sz)) content <- S.hGet fh sz case S.split '\x0C' content of [] -> return [] (hd:tl) -> do let pages = map (MkPage . map dropCR . S.lines) $ filter ((>0) . S.length) (hd:map (S.tail . S.dropWhile (/= '\n')) tl) length (pageLines $ last pages) `seq` unsafeFinalize content return pages where dropCR x | S.null x = S.copy x | S.last x == '\r' = S.copy (S.init x) | otherwise = S.copy x putPage :: Page -> IO () putPage = mapM_ S.putStrLn . pageLines