Simon Peyton-Jones wrote:
GHC does unwrap newtype result types, as in

foreign import foo :: Int -> IO Boogle
newtype Boogle = B Int

which is what the manual meant.  I'd never thought of newtyping the IO
monad itself.  Why are you doing that, incidentally?

I'm designing a simple API for interaction with a graphics window, where a render callback written in Haskell would set up some transforms and draw shapes and text. Using DirectX in C, my code would be something like:

       void Render(){
             Clear();
             BeginScene();
             DrawPrimitive();
             ...
             EndScene();
       }

       void Keypress(int c){
             // deal with user pressing c
       }

For Haskell, I could just make FFI declarations for Clear, BeginScene, etc as follows (modulo capitalization):

       foreign import ccall clear :: IO ()
       foreign import ccall scene :: IO () -> IO ()
       foreign import ccall drawPrimitive :: IO ()

      type RenderCallback :: IO ()
      type KeypressCallback :: IO ()

      render :: IO ()
      render = do
                        clear
                        scene $ do
                                        drawPrimitive

So Haskell has allowed the requirement for begin/end bracketing to be neatly abstracted by using a higher order function.

However, because everything is just in the IO monad, the following function, which misuses the API, is also well typed:

       keypress :: IO ()
       keypress = drawPrimitive -- not allowed at this point!!!

So the reason for wanting to wrap the IO monad is to make explicit the context in which the API functions can be correctly used as in:

      newtype RenderM a = RenderM (IO a) deriving (Monad, MonadIO, Functor)
      newtype DrawM a = DrawM (IO a) deriving (Monad, MonadIO, Functor)
      ...

      type RenderCallback :: RenderM ()

      foreign import ccall clear :: RenderM ()
      foreign import ccall scene :: DrawM () -> RenderM ()
      foreign import ccall drawPrimitive :: DrawM ()

      render :: RenderM ()
      render = ... -- as before

Now render is well typed but keypress is not, all things that, to use an API correctly in C or C++ you have to just guess from reading documentation but in Haskell with different monads is now explicit so that incorrect usage of the API can be detected by the compiler instead of resulting in weird runtime behaviour.

Regards, Brian.


_______________________________________________
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users

Reply via email to