-- |
-- Module      : Basement.Runtime
-- License     : BSD-style
-- Maintainer  : foundation
--
-- Global configuration environment
module Basement.Runtime
    where

import           Basement.Compat.Base
import           Basement.Types.OffsetSize
import           System.Environment
import           System.IO.Unsafe (unsafePerformIO)
import           Text.Read        (readMaybe)

-- | Defines the maximum size in bytes of unpinned arrays.
--
-- You can change this value by setting the environment variable
-- @HS_FOUNDATION_UARRAY_UNPINNED_MAX@ to an unsigned integer number.
--
-- Note: We use 'unsafePerformIO' here. If the environment variable
-- changes during runtime and the runtime system decides to recompute
-- this value, referential transparency is violated (like the First
-- Order violated the Galactic Concordance!).
--
-- TODO The default value of 1024 bytes is arbitrarily chosen for now.
unsafeUArrayUnpinnedMaxSize :: CountOf Word8
unsafeUArrayUnpinnedMaxSize :: CountOf Word8
unsafeUArrayUnpinnedMaxSize = IO (CountOf Word8) -> CountOf Word8
forall a. IO a -> a
unsafePerformIO (IO (CountOf Word8) -> CountOf Word8)
-> IO (CountOf Word8) -> CountOf Word8
forall a b. (a -> b) -> a -> b
$ do
    Maybe Int
maxSize <- (Maybe String -> (String -> Maybe Int) -> Maybe Int
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= String -> Maybe Int
forall a. Read a => String -> Maybe a
readMaybe) (Maybe String -> Maybe Int) -> IO (Maybe String) -> IO (Maybe Int)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> IO (Maybe String)
lookupEnv String
"HS_FOUNDATION_UARRAY_UNPINNED_MAX"
    CountOf Word8 -> IO (CountOf Word8)
forall (f :: * -> *) a. Applicative f => a -> f a
pure (CountOf Word8 -> IO (CountOf Word8))
-> CountOf Word8 -> IO (CountOf Word8)
forall a b. (a -> b) -> a -> b
$ CountOf Word8
-> (Int -> CountOf Word8) -> Maybe Int -> CountOf Word8
forall b a. b -> (a -> b) -> Maybe a -> b
maybe (Int -> CountOf Word8
forall ty. Int -> CountOf ty
CountOf Int
1024) Int -> CountOf Word8
forall ty. Int -> CountOf ty
CountOf Maybe Int
maxSize
{-# NOINLINE unsafeUArrayUnpinnedMaxSize #-}