module Network.HTTP2.Arch.File where

import System.IO

import Imports
import Network.HPACK

-- | Offset for file.
type FileOffset = Int64
-- | How many bytes to read
type ByteCount = Int64

-- | Position read for files.
type PositionRead = FileOffset -> ByteCount -> Buffer -> IO ByteCount

-- | Manipulating a file resource.
data Sentinel =
    -- | Closing a file resource. Its refresher is automatiaclly generated by
    --   the internal timer.
    Closer (IO ())
    -- | Refreshing a file resource while reading.
    --   Closing the file must be done by its own timer or something.
  | Refresher (IO ())

-- | Making a position read and its closer.
type PositionReadMaker = FilePath -> IO (PositionRead, Sentinel)
-- | Position read based on 'Handle'.
defaultPositionReadMaker :: PositionReadMaker
defaultPositionReadMaker :: PositionReadMaker
defaultPositionReadMaker FilePath
file = do
    Handle
hdl <- FilePath -> IOMode -> IO Handle
openBinaryFile FilePath
file IOMode
ReadMode
    forall (m :: * -> *) a. Monad m => a -> m a
return (Handle -> PositionRead
pread Handle
hdl, IO () -> Sentinel
Closer forall a b. (a -> b) -> a -> b
$ Handle -> IO ()
hClose Handle
hdl)
  where
    pread :: Handle -> PositionRead
    pread :: Handle -> PositionRead
pread Handle
hdl FileOffset
off FileOffset
bytes Buffer
buf = do
        Handle -> SeekMode -> Integer -> IO ()
hSeek Handle
hdl SeekMode
AbsoluteSeek forall a b. (a -> b) -> a -> b
$ forall a b. (Integral a, Num b) => a -> b
fromIntegral FileOffset
off
        forall a b. (Integral a, Num b) => a -> b
fromIntegral forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall a. Handle -> Ptr a -> Int -> IO Int
hGetBufSome Handle
hdl Buffer
buf (forall a b. (Integral a, Num b) => a -> b
fromIntegral FileOffset
bytes)