IO without exceptions?

About a year ago, I wrote a proposal for IOE, enabling checked exceptions in IO. It got fairly negative reactions, which is fine. This is a smaller change that I think might be less controversial than that.

Currently, we have IO that represents both impurity and the ability to throw exceptions. Here, I’m only talking about exceptions in the Haskell runtime; OOM and other catastrophic errors can also happen in pure code, so I’m not worried about those. What if we had some new type e.g. UIO that only represented impurity, and cannot throw any exceptions? That way, if you have a UIO, you don’t need to worry about catching exceptions.

One example motivation for this is ExceptT; ExceptT is notorious for being leaky. You might think ExceptT FooError IO () can only throw FooError, but any other error could be thrown in IO. ExceptT FooError UIO () would not have this problem. You can imagine other similar situations, where maybe you have a subsystem in IO, but you want the guarantee that it only throws FooError, so you want to make sure that any other IO function you call is UIO, so you don’t accidentally propagate some other exception.

Existing code like IORef could be UIO today, since none of those functions can throw exceptions. C FFI functions can also all be UIO, since C code can’t throw Haskell exceptions.

Thoughts? Is this sufficiently motivated? Is it sufficiently useful?

1 Like

You can throw user-defined exceptions from pure code. The meaning of a pure program that throws an exception is the same as one that gets stuck in an infinite loop. The special thing about I/O is that you can catch exceptions.

To make things even more complicated, there are also asynchronous exceptions which can be thrown from one thread to another.

So, I don’t think it is possible to ban user-defined exceptions from certain parts of your program. (Unless you go all-in, like by using Liquid Haskell.)

Ah yes I forgot about async and impure exceptions, thanks. I’m only talking about synchronous exceptions here, which I think is still worthwhile. Basically, I’m trying to get IO functions at the same level as pure functions, exception-wise. Impure exceptions and OS exceptions can happen in pure code, so they’d still happen in UIO. Presumably async exceptions can also interrupt pure code, so I’m not talking about that either.

The benefit of UIO is the same benefit as pure functions. Yes, technically, you can still break things, but the defined type implies certain properties that’s stronger than using IO everywhere

I think my added information has obscured my main message: you can throw user-defined exceptions from pure code. IO and pure code are already on the same level with respect to throwing exceptions.

I think it’s a great idea! It’s basically what effectful and Bluefin already provide through their Eff monads, which are essentially your UIO augmented with even more fine-grained type-level information.

1 Like

ah I see what you’re saying. My only counterpoint is that even though that’s the case, I don’t think I’ve ever seen impureThrow in the wild, and I’ve seen throwIO used fairly liberally. So UIO would be the middle ground where throwIO and catch are not defined, but you could still use impureThrow if you wish. But admittedly, this is less of a language issue and more of an ecosystem issue. You could do the same today with a newtype over IO and wrap every third-party IO call with

unsafeUIO = UIO
toUIO = UIO . try @SomeException

One side benefit having this in base would be all IO functions would be forced to be generalized to MonadUIO, so you wouldnt have to manually liftIO all base functions anymore

Here’s a question: what can you do in UIO? Almost all the interesting things we want to do in IO come down to primitives that can throw exceptions when things go wrong. Maybe we could recast a bunch of those as non-throwing functions that return Either or whatever, but it would be a lot of work!

3 Likes
1 Like

@taylorfausak ah yes, I forgot about that package! Yes, that’s basically my suggestion, except promoted to base.

@michaelpj Yes, this is mostly an ecosystem question that would require everyone to buy-in to providing an API that exports both IO and UIO Either versions. I recognize that might not be feasible, though.

However, you could still do a lot with UIO even without ecosystem buy-in. Like I mentioned in the original post, any C FFI code can always be UIO instead of IO, so if your application is mostly C bindings, you might be able to use UIO completely. base could also explicitly tag safe IO actions like IORef. But all the C bindings to the OS like getLine Or getArgs could be typed as UIO if changed to use ByteString (since decoding to String could fail with IOException).

Hrm - has everything listed here:

just been “totalled” ?

As you noted in your OP, Haskell code need not be I/O-based or require throw to raise exceptions. So for now, the chances of e.g. unexceptional going into base would seem rather low - a lot of work for limited benefit.


Some clarification needed here:

What if we had some new type e.g. UIO that only represented purity, and cannot throw any exceptions?

…I/O in Haskell isn’t pure:

http://conal.net/blog/posts/the-c-language-is-purely-functional

and “hiding” exceptions with some new type seems to be about as useful as VB6’s On Error Resume Next. Moreover, if that type is monadic the potential for the monadic interface to invade most of your codebase:

https://lexi-lambda.github.io/blog/2016/06/12/four-months-with-haskell

is still there. Hence the request for clarification - I’m just not seeing how anything is gained by what is being contemplated here.

Sorry, I meant “impurity”; I updated the OP.

Yes, I’ve conceded the fact that exceptions can still crop up anywhere. However, IMO impure exceptions are the equivalent of panics in Rust, and I think as a community, we’ve generally all aligned with that notion and not throw impure exceptions, as a general rule. At least not without loud warnings in the documentation. I’ll also handwave async exceptions for a second.

But as a community, we’ve accepted that going into some random library and calling some IO function will probably throw errors. IMO we aren’t really loud about what exceptions can be thrown when exposing an interface in IO.

One benefit of UIO is people can actually document their IO actions more precisely. If I write a library today and return IO (Either LibError Foo), I can’t express my guarantee that I’m not calling some third party IO function that will throw a different error that you’re in charge of handling. With UIO, I could document that, and short of forcing unexceptional on all my users, I can’t do that today.

Now, perhaps this is all hopes and dreams, and shouldve-wouldve-couldve. Maybe the ecosystem has solidified to an extent where introducing this concept wouldnt make much headway. But I do think having UIO in base would bring a lot of benefit, if it were sufficiently saturated through the ecosystem. Aside from the probability of this actually happening, the point of this post is to ask “If we had this in base already, and everyone in the ecosystem has bought into using it properly, would that be a better Haskell world than today’s?”

…featuring an all-new monadic I/O type:

primitive data OI
primitive partOI :: OI -> (OI, OI)

primitive seq :: a -> b -> b  -- "seq", as in "SEQUENTIAL"

primitive getChar :: OI -> Char
primitive putChar :: Char -> OI -> ()
            ⋮

type IO a = OI -> a

instance {-# OVERLAPPING #-} Monad ((->) OI) where
    return x = \ u -> partOI u `seq` x
    m >>= k  = \ u -> case partOI u of (u1, u2) -> (\ x -> x `seq` k x u2) (m u1)
    m >> w   = \ u -> case partOI u of (u1, u2) -> m u1 `seq` w u2

with maybe some more concise (or less) syntax:

1 Like

In the case of Java, checked exceptions proliferated, then people were put off by them, and moved to either unchecked exceptions or throwing the base Exception everywhere. All (IO a) is (UIO (Either IOError a)) because IO can explode for any reason, there’s no guarantees. You probably want a solid effects handling system before tainting everything with either and exception, besides IO.

You could introduce a new notion of purity that excludes exceptions. For example: purity level 2, or divine :grinning_face_with_smiling_eyes:

I’m not sure how the notation would work, but you could use the masking mechanism to disable async exceptions for a divine expression.
Then make any call to non-divine functions within a divine expression a compile error (but vice versa would be allowed).

Then you could use your fancy notation (which I neglected to provide), to tag IO with divinity, excluding exceptions.

ghc -XDivine ... YourDivineModule.hs ?

Alternatively: imagine if -XStrict didn’t exist, and having to use notation everywhere to exclude laziness? Your code would now be thoroughly “banged”.

It could be an interesting challenge for -XDivine to add all the async-masking without altering the types of exported entities. Using (or generating) a second “wrapper” module for the original one is another option, but that would require some way to prevent the original from being used directly…

I defined an exception-free IO monad in my explicit-exception package decades ago, but did not make it public, so far:
https://hackage.haskell.org/package/explicit-exception-0.2/src/src/System/IO/Straight.hs

The value of an UIO is that you have to use an explicit way to handle exceptions, may it be an Either result type or an exception monad transformer.

The explicit approach was originally considered for Haskell, and ultimately dismissed:

  • Handling Exceptions in Haskell (1999)

  • A semantics for imprecise exceptions (1999)

So having a type like UIO a would be of limited benefit - useful in some circumstances - and cause more confusion (and time-wasting discussions about when and where to use it).

1 Like