module Network.HTTP2.Arch.Config where

import Data.ByteString (ByteString)
import Data.IORef
import Foreign.Marshal.Alloc (mallocBytes, free)
import Network.Socket
import Network.Socket.ByteString (sendAll)
import qualified System.TimeManager as T

import Network.HPACK
import Network.HTTP2.Arch.File
import Network.HTTP2.Arch.ReadN

-- | HTTP/2 configuration.
data Config = Config {
    -- | This is used only by frameSender.
    -- This MUST be freed after frameSender is terminated.
      Config -> Buffer
confWriteBuffer :: Buffer
    -- | The size of the write buffer.
    --   We assume that the read buffer is the same size.
    --   So, this value is announced via SETTINGS_MAX_FRAME_SIZE
    --   to the peer.
    , Config -> Int
confBufferSize  :: BufferSize
    , Config -> ByteString -> IO ()
confSendAll     :: ByteString -> IO ()
    , Config -> Int -> IO ByteString
confReadN       :: Int -> IO ByteString
    , Config -> PositionReadMaker
confPositionReadMaker :: PositionReadMaker
    , Config -> Manager
confTimeoutManager :: T.Manager
    }

-- | Making simple configuration whose IO is not efficient.
--   A write buffer is allocated internally.
allocSimpleConfig :: Socket -> BufferSize -> IO Config
allocSimpleConfig :: Socket -> Int -> IO Config
allocSimpleConfig Socket
s Int
bufsiz = do
    Buffer
buf <- forall a. Int -> IO (Ptr a)
mallocBytes Int
bufsiz
    IORef (Maybe ByteString)
ref <- forall a. a -> IO (IORef a)
newIORef forall a. Maybe a
Nothing
    Manager
timmgr <- Int -> IO Manager
T.initialize forall a b. (a -> b) -> a -> b
$ Int
30 forall a. Num a => a -> a -> a
* Int
1000000
    let config :: Config
config = Config {
            confWriteBuffer :: Buffer
confWriteBuffer = Buffer
buf
          , confBufferSize :: Int
confBufferSize = Int
bufsiz
          , confSendAll :: ByteString -> IO ()
confSendAll = Socket -> ByteString -> IO ()
sendAll Socket
s
          , confReadN :: Int -> IO ByteString
confReadN = Socket -> IORef (Maybe ByteString) -> Int -> IO ByteString
defaultReadN Socket
s IORef (Maybe ByteString)
ref
          , confPositionReadMaker :: PositionReadMaker
confPositionReadMaker = PositionReadMaker
defaultPositionReadMaker
          , confTimeoutManager :: Manager
confTimeoutManager = Manager
timmgr
          }
    forall (m :: * -> *) a. Monad m => a -> m a
return Config
config

-- | Deallocating the resource of the simple configuration.
freeSimpleConfig :: Config -> IO ()
freeSimpleConfig :: Config -> IO ()
freeSimpleConfig Config
conf = do
    forall a. Ptr a -> IO ()
free forall a b. (a -> b) -> a -> b
$ Config -> Buffer
confWriteBuffer Config
conf
    Manager -> IO ()
T.killManager forall a b. (a -> b) -> a -> b
$ Config -> Manager
confTimeoutManager Config
conf