{-# LANGUAGE UnboxedTuples #-}

-- |
-- Module      : Streamly.Internal.System.IO
-- Copyright   : (c) 2020 Composewell Technologies
-- License     : BSD-3-Clause
-- Maintainer  : streamly@composewell.com
-- Stability   : experimental
-- Portability : GHC
--

module Streamly.Internal.System.IO
    ( defaultChunkSize
    , arrayPayloadSize
    , unsafeInlineIO
    )

where

-------------------------------------------------------------------------------
-- Imports
-------------------------------------------------------------------------------

import Foreign.Storable (Storable(sizeOf))
import GHC.Base (realWorld#)
import GHC.IO (IO(IO))

-------------------------------------------------------------------------------
-- API
-------------------------------------------------------------------------------

{-# INLINE unsafeInlineIO #-}
unsafeInlineIO :: IO a -> a
unsafeInlineIO :: IO a -> a
unsafeInlineIO (IO State# RealWorld -> (# State# RealWorld, a #)
m) = case State# RealWorld -> (# State# RealWorld, a #)
m State# RealWorld
realWorld# of (# State# RealWorld
_, a
r #) -> a
r

-- | Returns the heap allocation overhead for allocating a byte array. Each
-- heap object contains a one word header. Byte arrays contain the size of the
-- array after the header.
--
-- See https://gitlab.haskell.org/ghc/ghc/-/wikis/commentary/rts/storage/heap-objects#arrays
--
byteArrayOverhead :: Int
byteArrayOverhead :: Int
byteArrayOverhead = Int
2 Int -> Int -> Int
forall a. Num a => a -> a -> a
* Word -> Int
forall a. Storable a => a -> Int
sizeOf (Word
forall a. HasCallStack => a
undefined :: Word)

-- | When we allocate a byte array of size @k@ the allocator actually allocates
-- memory of size @k + byteArrayOverhead@. @arrayPayloadSize n@ returns the
-- size of the array in bytes that would result in an allocation of @n@ bytes.
--
arrayPayloadSize :: Int -> Int
arrayPayloadSize :: Int -> Int
arrayPayloadSize Int
n = let size :: Int
size = Int
n Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
byteArrayOverhead in Int -> Int -> Int
forall a. Ord a => a -> a -> a
max Int
size Int
0

-- | Default maximum buffer size in bytes, for reading from and writing to IO
-- devices, the value is 32KB minus GHC allocation overhead, which is a few
-- bytes, so that the actual allocation is 32KB.
defaultChunkSize :: Int
defaultChunkSize :: Int
defaultChunkSize = Int -> Int
arrayPayloadSize (Int
32 Int -> Int -> Int
forall a. Num a => a -> a -> a
* Int
1024)