Created
September 29, 2021 15:53
-
-
Save ShrykeWindgrace/126e7f5e26b0ead9dbf19da510363e49 to your computer and use it in GitHub Desktop.
Lazy or not lazy?
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
{-# LANGUAGE AllowAmbiguousTypes #-} | |
{-# LANGUAGE FlexibleInstances #-} | |
{-# LANGUAGE ImportQualifiedPost #-} | |
{-# LANGUAGE OverloadedStrings #-} | |
module Main where | |
import Control.Monad.Trans.Class (MonadTrans (lift)) | |
import Control.Monad.Trans.Reader (ReaderT (runReaderT), asks) | |
import Data.Binary (Get, Word64, Word8, getWord8) | |
import Data.Binary.Get (Get, getWord8, runGet) | |
import Data.ByteString qualified as BS | |
import Data.ByteString.Lazy qualified as BL | |
import System.IO ( | |
Handle, | |
IOMode (ReadMode), | |
SeekMode (AbsoluteSeek), | |
hFileSize, | |
hSeek, | |
withFile, | |
) | |
contents :: BL.ByteString | |
contents = "123" | |
main :: IO () | |
main = do | |
putStrLn "create file input.bin" | |
BL.writeFile "input.bin" contents | |
runWithSeeker "input.bin" seeker >>= print . conv | |
seeker :: Impl Word8 | |
seeker = do | |
seek AbsoluteSeek (Offset 1) | |
embed getWord8 | |
newtype Offset = Offset Word64 | |
conv :: Word8 -> Char | |
conv = toEnum . fromIntegral | |
class MonadSeeker m where | |
seek :: SeekMode -> Offset -> m () | |
embed :: Get a -> m a | |
size :: m Int | |
type Impl a = ReaderT (Handle, Int) IO a | |
instance MonadSeeker (ReaderT (Handle, Int) IO) where | |
size = asks snd | |
seek mode (Offset offset) = do | |
h <- asks fst | |
lift $ hSeek h mode (fromIntegral offset) | |
embed act = do | |
h <- asks fst | |
bs <- lift $ BS.hGetContents h | |
let val = runGet act $ BL.fromStrict bs | |
pure val | |
runWithSeeker :: FilePath -> Impl a -> IO a | |
runWithSeeker path impl = withFile path ReadMode runner | |
where | |
runner h = do | |
l <- (fromIntegral <$> hFileSize h) :: IO Int | |
runReaderT impl (h, l) |
Sign up for free
to join this conversation on GitHub.
Already have an account?
Sign in to comment