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
_______________________________________________
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users

Reply via email to