
I revisited the typechecking of binding groups, partly to fix the shortcomings of SPECIALISE pragmas. On the way, I implemented the refined dependency analysis described by Mark Jones in "Typing Haskell in Haskell". As a result, this "Contexts differ in length" problem has gone away. Robert, would you like to give it a try? Your example below is now part of GHC's test suite. It'll be in the next major release, but not in 6.4. Simon | -----Original Message----- | From: Robert van Herk [mailto:rherk@cs.uu.nl] | Sent: 24 May 2005 13:31 | To: glasgow-haskell-users@haskell.org; Simon Peyton-Jones | Subject: Contexts differ in length | | Hi all, | | A while ago I sent an email to the glasgow haskell users maillinglist to | explain how the "Contexts differ in length" feature (or bug :-)) | restricted me in writing a haskell application. I was hoping for a | reply, however I didn't receive one (yet). | | Therefore, I will explain the problem again: | | I am writing (for my master's thesis project) a webdevelopment framework | in Haskell, with features somewhat comparable to Apple's WebObjects. | Amongst others, session state and database interaction is transparent, etc. | | In my framework, functions that generate HTML are called WFComponents. | These functions are monadic since they can generate IO (because they may | do database interaction etc). Also, components can generate links to | other components. However, since component a may generate a link to | component b (so that when the user clicks that link component b will be | evaluated) and component b may link to component a, there will occur | errors when I try to do this, since the contexts of component a and b | may not be the same. A minimal example of this will be something like: | | {-# OPTIONS -fglasgow-exts #-} | | module Main where | import Data.IORef | | class MyReader r v | r -> v where | myRead :: r -> IO v | | data R v = R (IORef v) | instance MyReader (R v) v where | myRead (R v) = | do v <- readIORef v | return v | | | a :: IO () | a = | do r <- createReader | b r | | b :: MyReader r Int => r -> IO () | b r = | do i <- myRead r | if i > 10 | then a | else putStrLn (show i) | | createReader :: IO (R Int) | createReader = | do ref <- newIORef 0 | return (R ref) | | | | A real example will be a bit more complicated, but this is basically | what I need to do and currently am not able to. Of course, when needed, | I can show you the real example. Somewhere in the history of this | mailling list I read that people have had this program before, but only | in toy programs. However, I am experincing this problem currently in | something that is not a toy program. Therefore, my question is if it | would be possible to lift this constraint on the language, and also, if | the developers of GHC are currently planning to do this... | | Thanks, | | Robert