[Haskell-cafe] Teach me to cooperate with IOException

Folsk Pratima folsk0pratima at cock.li
Tue Apr 16 10:49:00 UTC 2024


Consider following C code.

```
int
syscall_that_fails (int *errno_here)
{
    *errno_here = 2;
    return -1;
}
```

Now I write the haskell wrapper, first without any error checking.

```
module Complex where

import Foreign
import Foreign.C
import Foreign.C.Types
import Foreign.Storable

foreign import ccall unsafe "complex.c syscall_that_fails" c_syscall_that_fails :: Ptr CInt -> IO CInt

sysCall :: Int -> IO ()
sysCall i =
    allocaBytes (sizeOf (0 :: CInt)) $ \ptr ->
        c_syscall_that_fails ptr >> return ()
```

Now I want to introduce some actual error checking, so at first I
simply do

```
module Complex where

import Control.Exception
import Foreign
import Foreign.C
import Foreign.C.Types
import Foreign.Storable

foreign import ccall unsafe "complex.c syscall_that_fails" c_syscall_that_fails
    :: Ptr CInt -> IO CInt

sysCall :: Int -> IO ()
sysCall i =
    allocaBytes (sizeOf (0 :: CInt)) $ \ptr -> do
        st <- c_syscall_that_fails ptr
        errno <- peekElemOff ptr 0
        case st of
            (-1) -> throwIO $ userError $ "syscall: " ++ show errno
            _ -> return ()

```

Now, I do not think it is a "user error", it is a real system call
error that might or might not be already covered by System.IO.Error. In
my case errno is 2, it is "No such file or directory", so it is covered
by System.IO.Error and I may just use the library. But my C code may
call whatever! What if System.IO does not cover that range of `errno`s?
What if I want to distinguish between *my* errors and system errors? In
such case I have to introduce my own way to do it.

How do I do it? My first wild guess is to introduce my own exception,
like this.

```
module Complex where

import Control.Exception
import Foreign
import Foreign.C
import Foreign.C.Types
import Foreign.Storable

data CException =
    LocalCallFailed
        { cexeption_errno :: Int
        , cexception_caller :: String
        }

instance Show CException where
    show (LocalCallFailed errno caller) = caller ++ ": " ++ show errno

instance Exception CException

foreign import ccall unsafe "complex.c syscall_that_fails" c_syscall_that_fails
    :: Ptr CInt -> IO CInt

sysCall :: Int -> IO ()
sysCall i =
    allocaBytes (sizeOf (0 :: CInt)) $ \ptr -> do
        st <- c_syscall_that_fails ptr
        errno <- peekElemOff ptr 0
        case st of
            (-1) -> throwIO . LocalCallFailed (fromIntegral errno) $ "syscall"
            _ -> return ()

```

And now I ask myself, what if allocaBytes fails? I looked on its code
and it does ioError, thus, it will throwIO. If then I need to invoke
sysCall, I can not use `try` anymore, because it is not determined what
I will catch, LocalCallFailed or IOException.

Next, what if I extend the `case of` clause to include some other
errors, that are not related to system calls, but are my own?

I try to recover, but can not come up with anything better than this...

```
module Complex where

import Control.Exception
import Foreign
import Foreign.C
import Foreign.C.Types
import Foreign.Storable

data CException
    = LocalCallFailed
          { cexeption_errno :: Int
          , cexception_caller :: String
          }
    | GenericIOException
          { genericioexception :: IOException
          }

instance Show CException where
    show (LocalCallFailed errno caller) = caller ++ ": " ++ show errno
    show (GenericIOException e) = displayException e

instance Exception CException

ioExceptionToMe :: IO (Either IOException a) -> IO a
ioExceptionToMe action = do
    e0 <- action
    case e0 of
        Left e -> throwIO . GenericIOException $ e
        Right a -> return a

tryIO :: IO a -> IO a
tryIO action = ioExceptionToMe $ try action

foreign import ccall unsafe "complex.c syscall_that_fails" c_syscall_that_fails
    :: Ptr CInt -> IO CInt

sysCall :: Int -> IO ()
sysCall i =
    tryIO $
    allocaBytes (sizeOf (0 :: CInt)) $ \ptr -> do
        st <- c_syscall_that_fails ptr
        errno <- tryIO $ peekElemOff ptr 0
        case st of
            (-1) -> throwIO . LocalCallFailed (fromIntegral errno) $ "syscall"
            _ -> return ()
```

Now, this seems to be easily extendable. I can change LocalCallFailed
to LocalSyscallFailed and then add something like LocalOwnFailed, which
would account for some C error that is not attributed to system calls,
and so on.

But still, it seems very dumb, because of how I use tryIO. I have to
use it on literally every haskell provided IO and... It just does not
seem right.


More information about the Haskell-Cafe mailing list