{-# LANGUAGE CPP #-}

module Network.Wai.Handler.Warp.HTTP2.File where

import Network.HTTP2.Server

import Network.Wai.Handler.Warp.Types

#ifdef WINDOWS
pReadMaker :: InternalInfo -> PositionReadMaker
pReadMaker _ = defaultPositionReadMaker
#else
import Network.Wai.Handler.Warp.FdCache
import Network.Wai.Handler.Warp.SendFile (positionRead)

-- | 'PositionReadMaker' based on file descriptor cache.
--
-- Since 3.3.13
pReadMaker :: InternalInfo -> PositionReadMaker
pReadMaker :: InternalInfo -> PositionReadMaker
pReadMaker InternalInfo
ii FilePath
path = do
    (Maybe Fd
mfd, Refresh
refresh) <- InternalInfo -> FilePath -> IO (Maybe Fd, Refresh)
getFd InternalInfo
ii FilePath
path
    case Maybe Fd
mfd of
      Just Fd
fd -> (PositionRead, Sentinel) -> IO (PositionRead, Sentinel)
forall (m :: * -> *) a. Monad m => a -> m a
return (Fd -> PositionRead
pread Fd
fd, Refresh -> Sentinel
Refresher Refresh
refresh)
      Maybe Fd
Nothing -> do
          Fd
fd <- FilePath -> IO Fd
openFile FilePath
path
          (PositionRead, Sentinel) -> IO (PositionRead, Sentinel)
forall (m :: * -> *) a. Monad m => a -> m a
return (Fd -> PositionRead
pread Fd
fd, Refresh -> Sentinel
Closer (Refresh -> Sentinel) -> Refresh -> Sentinel
forall a b. (a -> b) -> a -> b
$ Fd -> Refresh
closeFile Fd
fd)
  where
    pread :: Fd -> PositionRead
    pread :: Fd -> PositionRead
pread Fd
fd FileOffset
off FileOffset
bytes Buffer
buf = Int -> FileOffset
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> FileOffset) -> IO Int -> IO FileOffset
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Fd -> Buffer -> Int -> Integer -> IO Int
positionRead Fd
fd Buffer
buf Int
bytes' Integer
off'
      where
        bytes' :: Int
bytes' = FileOffset -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral FileOffset
bytes
        off' :: Integer
off' = FileOffset -> Integer
forall a b. (Integral a, Num b) => a -> b
fromIntegral FileOffset
off
#endif