{-# LANGUAGE CPP #-}
{-# LANGUAGE ExistentialQuantification #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE FlexibleContexts #-}
#include "inline.hs"
module Streamly.Memory.Malloc
(
mallocForeignPtrAlignedBytes
, mallocForeignPtrAlignedUnmanagedBytes
)
where
#define USE_GHC_MALLOC
import Foreign.ForeignPtr (ForeignPtr, newForeignPtr_)
import Foreign.Marshal.Alloc (mallocBytes)
#ifndef USE_GHC_MALLOC
import Foreign.ForeignPtr (newForeignPtr)
import Foreign.Marshal.Alloc (finalizerFree)
#endif
import qualified GHC.ForeignPtr as GHC
{-# INLINE mallocForeignPtrAlignedBytes #-}
mallocForeignPtrAlignedBytes :: Int -> Int -> IO (GHC.ForeignPtr a)
#ifdef USE_GHC_MALLOC
mallocForeignPtrAlignedBytes :: Int -> Int -> IO (ForeignPtr a)
mallocForeignPtrAlignedBytes =
Int -> Int -> IO (ForeignPtr a)
forall a. Int -> Int -> IO (ForeignPtr a)
GHC.mallocPlainForeignPtrAlignedBytes
#else
mallocForeignPtrAlignedBytes size _alignment = do
p <- mallocBytes size
newForeignPtr finalizerFree p
#endif
mallocForeignPtrAlignedUnmanagedBytes :: Int -> Int -> IO (ForeignPtr a)
mallocForeignPtrAlignedUnmanagedBytes :: Int -> Int -> IO (ForeignPtr a)
mallocForeignPtrAlignedUnmanagedBytes Int
size Int
_alignment = do
Ptr a
p <- Int -> IO (Ptr a)
forall a. Int -> IO (Ptr a)
mallocBytes Int
size
Ptr a -> IO (ForeignPtr a)
forall a. Ptr a -> IO (ForeignPtr a)
newForeignPtr_ Ptr a
p