[Haskell-cafe] runST $ unsafeIOToST $ ioWhatever
Folsk Pratima
folsk0pratima at cock.li
Sun Apr 14 19:47:04 UTC 2024
How wrong is it exactly? Did not get a reply on beginners at 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 <string.h>
int strerror_r (int, char *, size_t);
int
strerror_r_portable (int e, char *c, size_t s)
{
return strerror_r (e, c, s);
}
By default GHC picks up GNU version of strerror_r(), I want to pick up
the default portable version. I do not know how to make GHC understand
my desires.
More information about the Haskell-Cafe
mailing list