module Z.IO.Environment
  ( 
    getArgs
    
  , getAllEnv
  , getEnv, getEnv'
  , setEnv, unsetEnv
    
  , getCWD, chDir, getHomeDir, getTempDir
  , getRandom, getRandomT
  , getResUsage, ResUsage(..), TimeVal(..)
  , getResidentSetMemory
  , getUpTime
  , getHighResolutionTime
  , PID(..)
  , getPID, getPPID
  , getHostname
  , getOSName, OSName(..)
  , getPassWD, PassWD(..), UID, GID
  , getCPUInfo, CPUInfo(..)
  , getLoadAvg
  , getFreeMem, getTotalMem, getConstrainedMem
  ) where
import Control.Monad
import Data.Word
import Z.Data.Vector.Base as V
import Z.Data.CBytes
import Z.Foreign
import Z.IO.Exception
import Z.IO.UV.Manager
import Foreign.Storable
import Z.IO.UV.FFI
import Z.IO.UV.FFI_Env
getArgs :: IO [CBytes]
getArgs :: IO [CBytes]
getArgs = do
    (CInt
argc :: CInt, (Ptr CString
p_argv :: Ptr CString, ()
_)) <- (MBA# CInt -> IO (Ptr CString, ())) -> IO (CInt, (Ptr CString, ()))
forall a b. Prim a => (MBA# CInt -> IO b) -> IO (a, b)
allocPrimUnsafe ((MBA# CInt -> IO (Ptr CString, ()))
 -> IO (CInt, (Ptr CString, ())))
-> (MBA# CInt -> IO (Ptr CString, ()))
-> IO (CInt, (Ptr CString, ()))
forall a b. (a -> b) -> a -> b
$ \ MBA# CInt
p_argc -> do
        (MBA# CInt -> IO ()) -> IO (Ptr CString, ())
forall a b. Prim a => (MBA# CInt -> IO b) -> IO (a, b)
allocPrimUnsafe ((MBA# CInt -> IO ()) -> IO (Ptr CString, ()))
-> (MBA# CInt -> IO ()) -> IO (Ptr CString, ())
forall a b. (a -> b) -> a -> b
$ \ MBA# CInt
p_p_argv -> do
            MBA# CInt -> MBA# CInt -> IO ()
getProgArgv MBA# CInt
p_argc MBA# CInt
p_p_argv
    [Int] -> (Int -> IO CBytes) -> IO [CBytes]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
t a -> (a -> m b) -> m (t b)
forM [Int
0..CInt -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral (CInt
argcCInt -> CInt -> CInt
forall a. Num a => a -> a -> a
-CInt
1)] ((Int -> IO CBytes) -> IO [CBytes])
-> (Int -> IO CBytes) -> IO [CBytes]
forall a b. (a -> b) -> a -> b
$ \ Int
i -> do
        CString -> IO CBytes
fromCString (CString -> IO CBytes) -> IO CString -> IO CBytes
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< Ptr CString -> Int -> IO CString
forall a. Storable a => Ptr a -> Int -> IO a
peekElemOff Ptr CString
p_argv Int
i
getAllEnv :: HasCallStack => IO [(CBytes, CBytes)]
getAllEnv :: IO [(CBytes, CBytes)]
getAllEnv = IO (Ptr CString, CInt)
-> ((Ptr CString, CInt) -> IO ())
-> ((Ptr CString, CInt) -> IO [(CBytes, CBytes)])
-> IO [(CBytes, CBytes)]
forall a b c. IO a -> (a -> IO b) -> (a -> IO c) -> IO c
bracket
    (do (Ptr CString
p_env :: Ptr CString, (CInt
envc :: CInt, ()
_)) <- (MBA# CInt -> IO (CInt, ())) -> IO (Ptr CString, (CInt, ()))
forall a b. Prim a => (MBA# CInt -> IO b) -> IO (a, b)
allocPrimUnsafe ((MBA# CInt -> IO (CInt, ())) -> IO (Ptr CString, (CInt, ())))
-> (MBA# CInt -> IO (CInt, ())) -> IO (Ptr CString, (CInt, ()))
forall a b. (a -> b) -> a -> b
$ \ MBA# CInt
p_p_env -> do
            (MBA# CInt -> IO ()) -> IO (CInt, ())
forall a b. Prim a => (MBA# CInt -> IO b) -> IO (a, b)
allocPrimUnsafe ((MBA# CInt -> IO ()) -> IO (CInt, ()))
-> (MBA# CInt -> IO ()) -> IO (CInt, ())
forall a b. (a -> b) -> a -> b
$ \ MBA# CInt
p_envc ->
                IO CInt -> IO ()
forall a. (HasCallStack, Integral a) => IO a -> IO ()
throwUVIfMinus_ (MBA# CInt -> MBA# CInt -> IO CInt
forall a. MBA# CInt -> MBA# CInt -> IO CInt
uv_os_environ MBA# CInt
p_p_env MBA# CInt
p_envc)
        (Ptr CString, CInt) -> IO (Ptr CString, CInt)
forall (m :: * -> *) a. Monad m => a -> m a
return (Ptr CString
p_env, CInt
envc))
    (\ (Ptr CString
p_env, CInt
envc) -> Ptr CString -> CInt -> IO ()
forall a. Ptr a -> CInt -> IO ()
uv_os_free_environ Ptr CString
p_env CInt
envc)
    (\ (Ptr CString
p_env, CInt
envc) -> do
        [Int] -> (Int -> IO (CBytes, CBytes)) -> IO [(CBytes, CBytes)]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
t a -> (a -> m b) -> m (t b)
forM [Int
0..CInt -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral (CInt
envcCInt -> CInt -> CInt
forall a. Num a => a -> a -> a
-CInt
1)] ((Int -> IO (CBytes, CBytes)) -> IO [(CBytes, CBytes)])
-> (Int -> IO (CBytes, CBytes)) -> IO [(CBytes, CBytes)]
forall a b. (a -> b) -> a -> b
$ \ Int
i -> do
            CBytes
k <- CString -> IO CBytes
fromCString (CString -> IO CBytes) -> IO CString -> IO CBytes
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< Ptr CString -> Int -> IO CString
forall a. Storable a => Ptr a -> Int -> IO a
peekElemOff Ptr CString
p_env (Int
iInt -> Int -> Int
forall a. Num a => a -> a -> a
*Int
2)
            CBytes
v <- CString -> IO CBytes
fromCString (CString -> IO CBytes) -> IO CString -> IO CBytes
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< Ptr CString -> Int -> IO CString
forall a. Storable a => Ptr a -> Int -> IO a
peekElemOff Ptr CString
p_env (Int
iInt -> Int -> Int
forall a. Num a => a -> a -> a
*Int
2Int -> Int -> Int
forall a. Num a => a -> a -> a
+Int
1)
            (CBytes, CBytes) -> IO (CBytes, CBytes)
forall (m :: * -> *) a. Monad m => a -> m a
return (CBytes
k, CBytes
v))
getEnv :: HasCallStack => CBytes -> IO (Maybe CBytes)
getEnv :: CBytes -> IO (Maybe CBytes)
getEnv CBytes
k = Int -> IO (Maybe CBytes)
go Int
512
  where
    go :: Int -> IO (Maybe CBytes)
go Int
siz = do
        (Int
siz', (CBytes
v, CInt
r))<- Int -> (MBA# CInt -> IO (CBytes, CInt)) -> IO (Int, (CBytes, CInt))
forall a b. Prim a => a -> (MBA# CInt -> IO b) -> IO (a, b)
withPrimUnsafe Int
siz ((MBA# CInt -> IO (CBytes, CInt)) -> IO (Int, (CBytes, CInt)))
-> (MBA# CInt -> IO (CBytes, CInt)) -> IO (Int, (CBytes, CInt))
forall a b. (a -> b) -> a -> b
$ \ MBA# CInt
p_siz ->
            CBytes -> (BA# Word8 -> IO (CBytes, CInt)) -> IO (CBytes, CInt)
forall a. CBytes -> (BA# Word8 -> IO a) -> IO a
withCBytesUnsafe CBytes
k ((BA# Word8 -> IO (CBytes, CInt)) -> IO (CBytes, CInt))
-> (BA# Word8 -> IO (CBytes, CInt)) -> IO (CBytes, CInt)
forall a b. (a -> b) -> a -> b
$ \ BA# Word8
p_k ->
                Int -> (MBA# CInt -> IO CInt) -> IO (CBytes, CInt)
forall a.
HasCallStack =>
Int -> (MBA# CInt -> IO a) -> IO (CBytes, a)
allocCBytesUnsafe Int
siz ((MBA# CInt -> IO CInt) -> IO (CBytes, CInt))
-> (MBA# CInt -> IO CInt) -> IO (CBytes, CInt)
forall a b. (a -> b) -> a -> b
$ \ MBA# CInt
p_v ->
                    BA# Word8 -> MBA# CInt -> MBA# CInt -> IO CInt
uv_os_getenv BA# Word8
p_k MBA# CInt
p_v MBA# CInt
p_siz
        case CInt
r of
            CInt
UV_ENOBUFS -> Int -> IO (Maybe CBytes)
go Int
siz'
            CInt
UV_ENOENT -> Maybe CBytes -> IO (Maybe CBytes)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe CBytes
forall a. Maybe a
Nothing
            CInt
_ -> do
                IO CInt -> IO ()
forall a. (HasCallStack, Integral a) => IO a -> IO ()
throwUVIfMinus_ (CInt -> IO CInt
forall (m :: * -> *) a. Monad m => a -> m a
return CInt
r)
                Maybe CBytes -> IO (Maybe CBytes)
forall (m :: * -> *) a. Monad m => a -> m a
return (CBytes -> Maybe CBytes
forall a. a -> Maybe a
Just CBytes
v)
getEnv' :: HasCallStack => CBytes -> IO CBytes
getEnv' :: CBytes -> IO CBytes
getEnv' CBytes
k = HasCallStack => CBytes -> IO (Maybe CBytes)
CBytes -> IO (Maybe CBytes)
getEnv CBytes
k IO (Maybe CBytes) -> (Maybe CBytes -> IO CBytes) -> IO CBytes
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \ Maybe CBytes
mv -> case Maybe CBytes
mv of
    Just CBytes
v -> CBytes -> IO CBytes
forall (m :: * -> *) a. Monad m => a -> m a
return CBytes
v
    Maybe CBytes
_ -> CInt -> IOEInfo -> IO CBytes
forall a. CInt -> IOEInfo -> IO a
throwUVError CInt
UV_ENOENT (Text -> Text -> CallStack -> IOEInfo
IOEInfo Text
"ENOENT" Text
"no such environment variable" CallStack
HasCallStack => CallStack
callStack)
setEnv :: HasCallStack => CBytes -> CBytes -> IO ()
setEnv :: CBytes -> CBytes -> IO ()
setEnv CBytes
k CBytes
v = CBytes -> (BA# Word8 -> IO ()) -> IO ()
forall a. CBytes -> (BA# Word8 -> IO a) -> IO a
withCBytesUnsafe CBytes
k ((BA# Word8 -> IO ()) -> IO ()) -> (BA# Word8 -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \ BA# Word8
p_k ->
    CBytes -> (BA# Word8 -> IO ()) -> IO ()
forall a. CBytes -> (BA# Word8 -> IO a) -> IO a
withCBytesUnsafe CBytes
v ((BA# Word8 -> IO ()) -> IO ()) -> (BA# Word8 -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \ BA# Word8
p_v ->
        IO CInt -> IO ()
forall a. (HasCallStack, Integral a) => IO a -> IO ()
throwUVIfMinus_ (BA# Word8 -> BA# Word8 -> IO CInt
uv_os_setenv BA# Word8
p_k BA# Word8
p_v)
unsetEnv :: HasCallStack => CBytes -> IO ()
unsetEnv :: CBytes -> IO ()
unsetEnv CBytes
k = IO () -> IO ()
forall (f :: * -> *) a. Functor f => f a -> f ()
void (IO () -> IO ())
-> ((BA# Word8 -> IO ()) -> IO ()) -> (BA# Word8 -> IO ()) -> IO ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. CBytes -> (BA# Word8 -> IO ()) -> IO ()
forall a. CBytes -> (BA# Word8 -> IO a) -> IO a
withCBytesUnsafe CBytes
k ((BA# Word8 -> IO ()) -> IO ()) -> (BA# Word8 -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \ BA# Word8
p -> IO CInt -> IO ()
forall a. (HasCallStack, Integral a) => IO a -> IO ()
throwUVIfMinus_ (BA# Word8 -> IO CInt
uv_os_unsetenv BA# Word8
p)
getResidentSetMemory :: HasCallStack => IO CSize
getResidentSetMemory :: IO CSize
getResidentSetMemory = do
    (CSize
size, CInt
r) <- (MBA# CInt -> IO CInt) -> IO (CSize, CInt)
forall a b. Prim a => (MBA# CInt -> IO b) -> IO (a, b)
allocPrimUnsafe MBA# CInt -> IO CInt
uv_resident_set_memory
    IO CInt -> IO ()
forall a. (HasCallStack, Integral a) => IO a -> IO ()
throwUVIfMinus_ (CInt -> IO CInt
forall (m :: * -> *) a. Monad m => a -> m a
return CInt
r)
    CSize -> IO CSize
forall (m :: * -> *) a. Monad m => a -> m a
return CSize
size
getUpTime :: HasCallStack => IO Double
getUpTime :: IO Double
getUpTime = do
    (Double
size, CInt
r) <- (MBA# CInt -> IO CInt) -> IO (Double, CInt)
forall a b. Prim a => (MBA# CInt -> IO b) -> IO (a, b)
allocPrimUnsafe MBA# CInt -> IO CInt
uv_uptime
    IO CInt -> IO ()
forall a. (HasCallStack, Integral a) => IO a -> IO ()
throwUVIfMinus_ (CInt -> IO CInt
forall (m :: * -> *) a. Monad m => a -> m a
return CInt
r)
    Double -> IO Double
forall (m :: * -> *) a. Monad m => a -> m a
return Double
size
getHighResolutionTime :: IO Word64
getHighResolutionTime :: IO Word64
getHighResolutionTime = IO Word64
uv_hrtime
getResUsage :: HasCallStack => IO ResUsage
getResUsage :: IO ResUsage
getResUsage = do
    (MutableByteArray MBA# CInt
mba#) <- Int -> IO (MutableByteArray (PrimState IO))
forall (m :: * -> *).
PrimMonad m =>
Int -> m (MutableByteArray (PrimState m))
newByteArray Int
sizeOfResUsage
    IO CInt -> IO ()
forall a. (HasCallStack, Integral a) => IO a -> IO ()
throwUVIfMinus_ (MBA# CInt -> IO CInt
forall k (a :: k). MBA# CInt -> IO CInt
uv_getrusage MBA# CInt
mba#)
    MBA# CInt -> IO ResUsage
forall k (a :: k). MBA# CInt -> IO ResUsage
peekResUsage MBA# CInt
mba#
getPID :: IO PID
getPID :: IO PID
getPID = IO PID
uv_os_getpid
getPPID :: IO PID
getPPID :: IO PID
getPPID = IO PID
uv_os_getppid
getHostname :: HasCallStack => IO CBytes
getHostname :: IO CBytes
getHostname = do
    (CBytes
n, (CSize, ())
_) <- Int -> (MBA# CInt -> IO (CSize, ())) -> IO (CBytes, (CSize, ()))
forall a.
HasCallStack =>
Int -> (MBA# CInt -> IO a) -> IO (CBytes, a)
allocCBytesUnsafe (CSize -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral CSize
UV_MAXHOSTNAMESIZE) ((MBA# CInt -> IO (CSize, ())) -> IO (CBytes, (CSize, ())))
-> (MBA# CInt -> IO (CSize, ())) -> IO (CBytes, (CSize, ()))
forall a b. (a -> b) -> a -> b
$ \ MBA# CInt
p_n ->
        CSize -> (MBA# CInt -> IO ()) -> IO (CSize, ())
forall a b. Prim a => a -> (MBA# CInt -> IO b) -> IO (a, b)
withPrimUnsafe CSize
UV_MAXHOSTNAMESIZE ((MBA# CInt -> IO ()) -> IO (CSize, ()))
-> (MBA# CInt -> IO ()) -> IO (CSize, ())
forall a b. (a -> b) -> a -> b
$ \ MBA# CInt
p_siz ->
            IO CInt -> IO ()
forall a. (HasCallStack, Integral a) => IO a -> IO ()
throwUVIfMinus_ (MBA# CInt -> MBA# CInt -> IO CInt
uv_os_gethostname MBA# CInt
p_n MBA# CInt
p_siz)
    CBytes -> IO CBytes
forall (m :: * -> *) a. Monad m => a -> m a
return CBytes
n
getRandom :: Int -> IO V.Bytes
getRandom :: Int -> IO Bytes
getRandom Int
siz = do
    (Bytes
v, ()
_) <- Int -> (MBA# CInt -> IO ()) -> IO (Bytes, ())
forall a b.
Prim a =>
Int -> (MBA# CInt -> IO b) -> IO (PrimVector a, b)
allocPrimVectorUnsafe Int
siz ((MBA# CInt -> IO ()) -> IO (Bytes, ()))
-> (MBA# CInt -> IO ()) -> IO (Bytes, ())
forall a b. (a -> b) -> a -> b
$ \ MBA# CInt
mba# ->
        IO CInt -> IO ()
forall a. (HasCallStack, Integral a) => IO a -> IO ()
throwUVIfMinus_ (MBA# CInt -> CSize -> CInt -> IO CInt
hs_uv_random MBA# CInt
mba# (Int -> CSize
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
siz) CInt
0)
    Bytes -> IO Bytes
forall (m :: * -> *) a. Monad m => a -> m a
return Bytes
v
getRandomT :: Int -> IO V.Bytes
getRandomT :: Int -> IO Bytes
getRandomT Int
siz = do
    (Bytes
v, ()
_) <- Int -> (Ptr Word8 -> IO ()) -> IO (Bytes, ())
forall a b.
Prim a =>
Int -> (Ptr a -> IO b) -> IO (PrimVector a, b)
allocPrimVectorSafe Int
siz ((Ptr Word8 -> IO ()) -> IO (Bytes, ()))
-> (Ptr Word8 -> IO ()) -> IO (Bytes, ())
forall a b. (a -> b) -> a -> b
$ \ Ptr Word8
p -> do
        UVManager
uvm <- IO UVManager
getUVManager
        HasCallStack =>
UVManager -> (Ptr UVLoop -> IO UVSlotUnsafe) -> IO ()
UVManager -> (Ptr UVLoop -> IO UVSlotUnsafe) -> IO ()
withUVRequest_ UVManager
uvm (Ptr Word8 -> CSize -> CInt -> Ptr UVLoop -> IO UVSlotUnsafe
hs_uv_random_threaded Ptr Word8
p (Int -> CSize
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
siz) CInt
0)
    Bytes -> IO Bytes
forall (m :: * -> *) a. Monad m => a -> m a
return Bytes
v
getCWD :: HasCallStack => IO CBytes
getCWD :: IO CBytes
getCWD = Int -> IO CBytes
go Int
512
  where
    go :: Int -> IO CBytes
go Int
siz = do
        (Int
siz', (CBytes
v, CInt
r))<- Int -> (MBA# CInt -> IO (CBytes, CInt)) -> IO (Int, (CBytes, CInt))
forall a b. Prim a => a -> (MBA# CInt -> IO b) -> IO (a, b)
withPrimUnsafe Int
siz ((MBA# CInt -> IO (CBytes, CInt)) -> IO (Int, (CBytes, CInt)))
-> (MBA# CInt -> IO (CBytes, CInt)) -> IO (Int, (CBytes, CInt))
forall a b. (a -> b) -> a -> b
$ \ MBA# CInt
p_siz ->
            Int -> (MBA# CInt -> IO CInt) -> IO (CBytes, CInt)
forall a.
HasCallStack =>
Int -> (MBA# CInt -> IO a) -> IO (CBytes, a)
allocCBytesUnsafe Int
siz ((MBA# CInt -> IO CInt) -> IO (CBytes, CInt))
-> (MBA# CInt -> IO CInt) -> IO (CBytes, CInt)
forall a b. (a -> b) -> a -> b
$ \ MBA# CInt
p_v ->
                MBA# CInt -> MBA# CInt -> IO CInt
uv_cwd MBA# CInt
p_v MBA# CInt
p_siz
        case CInt
r of
            CInt
UV_ENOBUFS -> Int -> IO CBytes
go Int
siz'
            CInt
_ -> do
                IO CInt -> IO ()
forall a. (HasCallStack, Integral a) => IO a -> IO ()
throwUVIfMinus_ (CInt -> IO CInt
forall (m :: * -> *) a. Monad m => a -> m a
return CInt
r)
                CBytes -> IO CBytes
forall (m :: * -> *) a. Monad m => a -> m a
return CBytes
v
chDir :: HasCallStack => CBytes -> IO ()
chDir :: CBytes -> IO ()
chDir CBytes
p = IO CInt -> IO ()
forall a. (HasCallStack, Integral a) => IO a -> IO ()
throwUVIfMinus_ (CBytes -> (BA# Word8 -> IO CInt) -> IO CInt
forall a. CBytes -> (BA# Word8 -> IO a) -> IO a
withCBytesUnsafe CBytes
p ((BA# Word8 -> IO CInt) -> IO CInt)
-> (BA# Word8 -> IO CInt) -> IO CInt
forall a b. (a -> b) -> a -> b
$ \ BA# Word8
pp -> BA# Word8 -> IO CInt
uv_chdir BA# Word8
pp)
getHomeDir :: HasCallStack => IO CBytes
getHomeDir :: IO CBytes
getHomeDir = Int -> IO CBytes
go Int
512
  where
    go :: Int -> IO CBytes
go Int
siz = do
        (Int
siz', (CBytes
v, CInt
r))<- Int -> (MBA# CInt -> IO (CBytes, CInt)) -> IO (Int, (CBytes, CInt))
forall a b. Prim a => a -> (MBA# CInt -> IO b) -> IO (a, b)
withPrimUnsafe Int
siz ((MBA# CInt -> IO (CBytes, CInt)) -> IO (Int, (CBytes, CInt)))
-> (MBA# CInt -> IO (CBytes, CInt)) -> IO (Int, (CBytes, CInt))
forall a b. (a -> b) -> a -> b
$ \ MBA# CInt
p_siz ->
            Int -> (MBA# CInt -> IO CInt) -> IO (CBytes, CInt)
forall a.
HasCallStack =>
Int -> (MBA# CInt -> IO a) -> IO (CBytes, a)
allocCBytesUnsafe Int
siz ((MBA# CInt -> IO CInt) -> IO (CBytes, CInt))
-> (MBA# CInt -> IO CInt) -> IO (CBytes, CInt)
forall a b. (a -> b) -> a -> b
$ \ MBA# CInt
p_v ->
                MBA# CInt -> MBA# CInt -> IO CInt
uv_os_homedir MBA# CInt
p_v MBA# CInt
p_siz
        case CInt
r of
            CInt
UV_ENOBUFS -> Int -> IO CBytes
go Int
siz'
            CInt
_ -> do
                IO CInt -> IO ()
forall a. (HasCallStack, Integral a) => IO a -> IO ()
throwUVIfMinus_ (CInt -> IO CInt
forall (m :: * -> *) a. Monad m => a -> m a
return CInt
r)
                CBytes -> IO CBytes
forall (m :: * -> *) a. Monad m => a -> m a
return CBytes
v
getTempDir :: HasCallStack => IO CBytes
getTempDir :: IO CBytes
getTempDir = Int -> IO CBytes
go Int
512
  where
    go :: Int -> IO CBytes
go Int
siz = do
        (Int
siz', (CBytes
v, CInt
r))<- Int -> (MBA# CInt -> IO (CBytes, CInt)) -> IO (Int, (CBytes, CInt))
forall a b. Prim a => a -> (MBA# CInt -> IO b) -> IO (a, b)
withPrimUnsafe Int
siz ((MBA# CInt -> IO (CBytes, CInt)) -> IO (Int, (CBytes, CInt)))
-> (MBA# CInt -> IO (CBytes, CInt)) -> IO (Int, (CBytes, CInt))
forall a b. (a -> b) -> a -> b
$ \ MBA# CInt
p_siz ->
            Int -> (MBA# CInt -> IO CInt) -> IO (CBytes, CInt)
forall a.
HasCallStack =>
Int -> (MBA# CInt -> IO a) -> IO (CBytes, a)
allocCBytesUnsafe Int
siz ((MBA# CInt -> IO CInt) -> IO (CBytes, CInt))
-> (MBA# CInt -> IO CInt) -> IO (CBytes, CInt)
forall a b. (a -> b) -> a -> b
$ \ MBA# CInt
p_v ->
                MBA# CInt -> MBA# CInt -> IO CInt
uv_os_tmpdir MBA# CInt
p_v MBA# CInt
p_siz
        case CInt
r of
            CInt
UV_ENOBUFS -> Int -> IO CBytes
go Int
siz'
            CInt
_ -> do
                IO CInt -> IO ()
forall a. (HasCallStack, Integral a) => IO a -> IO ()
throwUVIfMinus_ (CInt -> IO CInt
forall (m :: * -> *) a. Monad m => a -> m a
return CInt
r)
                CBytes -> IO CBytes
forall (m :: * -> *) a. Monad m => a -> m a
return CBytes
v
getFreeMem :: IO Word64
getFreeMem :: IO Word64
getFreeMem = IO Word64
uv_get_free_memory
getTotalMem :: IO Word64
getTotalMem :: IO Word64
getTotalMem = IO Word64
uv_get_total_memory
getConstrainedMem :: IO Word64
getConstrainedMem :: IO Word64
getConstrainedMem = IO Word64
uv_get_constrained_memory
foreign import ccall unsafe getProgArgv :: MBA# CInt -> MBA# (Ptr CString) -> IO ()