runST $ unsafeIOToST $ ioWhatever

How wrong is it exactly? Did not get a reply on beginners@haskell.org
import Control.Exception
import Control.Monad.ST
import Control.Monad.ST.Unsafe
import Data.Word
import Foreign.C.String
import Foreign.C.String
import Foreign.C.Types
import Foreign.Marshal
import Foreign.Ptr
import Foreign.Storable
foreign import ccall unsafe "strerror_r_portalbe.c strerror_r_portable" c_strerror_r
:: CInt -> Ptr CChar -> CSize -> IO CInt
memSet :: Ptr a -> Word8 -> Word32 -> IO (Ptr a)
memSet ptr _ 0 = return ptr
memSet ptr byte size = do
let voidptr = castPtr ptr :: Ptr Word8
acts =
map
(\i -> pokeByteOff voidptr i byte)
[0 .. fromIntegral (size - 1)]
mapM_ id acts
return ptr
strError :: Int -> String
strError errnum = runST $ unsafeIOToST ioString
where
baseSize :: CSize
baseSize = 50
ioString = run baseSize
run :: CSize -> IO String
run size
| size > 100000 =
throwIO $
userError $
"!!! INTERNAL strError memory leak detected, " ++
"you can not recover !!!"
| otherwise = do
may <- tryIOString size
case may of
Just str -> return str
Nothing -> run (size + baseSize)
tryIOString :: CSize -> IO (Maybe String)
tryIOString size =
allocaBytes (fromIntegral size) $ \ptr -> do
zeroptr <- memSet ptr 0 (fromIntegral size)
st <- c_strerror_r (fromIntegral errnum) ptr size
-- heuristic
case st of
22 -> return . return $ "Unknown error " ++ show errnum
34 -> return Nothing
_ -> peekCAString ptr >>= return . return
main = mapM_ (putStrLn) $ map strError [1 .. 1000]
The C file is
#define _POSIX_C_SOURCE 200112L
#include

On Sun, 14 Apr 2024, Folsk Pratima wrote:
strError :: Int -> String strError errnum = runST $ unsafeIOToST ioString
Instead of (runST $ unsafeIOToST ioString) you could just call (unsafePerformIO ioString). However, ioString must not have observable side effects. throwIO does not look right and should be 'error'.

On Sun, 14 Apr 2024, Folsk Pratima wrote:
memSet :: Ptr a -> Word8 -> Word32 -> IO (Ptr a) memSet ptr _ 0 = return ptr memSet ptr byte size = do let voidptr = castPtr ptr :: Ptr Word8 acts = map (\i -> pokeByteOff voidptr i byte) [0 .. fromIntegral (size - 1)] mapM_ id acts return ptr
I think you just want pokeArray ptr $ replicate (fromIntegral size) byte

On Sun, 14 Apr 2024, Folsk Pratima wrote:
tryIOString :: CSize -> IO (Maybe String) tryIOString size = allocaBytes (fromIntegral size) $ \ptr -> do zeroptr <- memSet ptr 0 (fromIntegral size)
You may instead do withArray (replicate (fromIntegral size) 0) $ \ptr -> do st <- c_strerror_r (fromIntegral errnum) ptr size ...
participants (2)
-
Folsk Pratima
-
Henning Thielemann