
Hello fellow haskellers, I am wondering if anyone has an idea whether I'd run into trouble if I rebound >>= in order to provide a more restricted monad. My idea is to define a class: class WitnessMonad wm where (>>=) :: wm w w' a -> (a -> wm w' w'' b) -> wm w w'' b (>>) :: wm w w' a -> wm w' w'' b -> wm w w'' b return :: a -> wm w w' a fail :: String -> wm w w' a which obviously just adds a couple of phantom types indicating the monad state prior to and after each operation. I actually rather like this redefined monad, as it seems like it'd be useful in lots of places (e.g. a restricted IO monad that disallows use of a file handle after it's closed). It seems to me like this would be a pretty cool kind of monad. It'd allow us to encode typechecked "properties" in a monad, and there'd be very little restriction on how tricky those properties could be. And we'd get this all using the same do syntax we all love (and the new properties are by definition sequential, so a monad is precisely what we want, only at the type level). One trouble I see is how to move an ordinary monad into the WitnessMonad class. Of course, they differ in kind, so we need to do something, but I'm not sure what, and suspect that folks with experience using monad transformers will immediately see the answer. Of course, I want to be able to use both my fancy witnessed monad and IO in the same module, and I want to be able to use do notation for both of them. I suppose we could easily define data M m w w' c = M (m c) lift = M lower (M m) = m instance WitnessMonad (M m) where f >>= g = lift $ Prelude.(>>=) (lower f) (lower . g) ... but then we'd have to lift all our operations, so an ordinary IO function in a module that used my fancy rebound do notation would look like f :: IO Char f = lower $ do lift $ putStr "Hello world" lift $ getChar which seems rather heavy. Can anyone think of syntax-light way to allow my hypothesized rebound do-notation to also work with ordinary monads? -- David Roundy Department of Physics Oregon State University

David Roundy
class WitnessMonad wm where (>>=) :: wm w w' a -> (a -> wm w' w'' b) -> wm w w'' b (>>) :: wm w w' a -> wm w' w'' b -> wm w w'' b return :: a -> wm w w' a fail :: String -> wm w w' a
I suspect that you want "w" and "w'" to be the same type in the types of "return" and "fail". Previous work: Atkey, Robert. 2006. Parameterised notions of computation. In MSFP 2006: Workshop on mathematically structured functional programming, ed. Conor McBride and Tarmo Uustalu. Electronic Workshops in Computing, British Computer Society. http://homepages.inf.ed.ac.uk/ratkey/param-notions.pdf http://haskell.org/pipermail/haskell-cafe/2004-July/006448.html -- Edit this signature at http://www.digitas.harvard.edu/cgi-bin/ken/sig FORTH is a program that interfaces keyboards with computer. Charles H.Moore, Geoffrey C. Leach, 1970. http://www.ultratechnology.com/4th_1970.html

On Sun, Dec 17, 2006 at 01:35:49PM -0500, Chung-chieh Shan wrote:
David Roundy
wrote: class WitnessMonad wm where (>>=) :: wm w w' a -> (a -> wm w' w'' b) -> wm w w'' b (>>) :: wm w w' a -> wm w' w'' b -> wm w w'' b return :: a -> wm w w' a fail :: String -> wm w w' a
I suspect that you want "w" and "w'" to be the same type in the types of "return" and "fail".
You're right. That was silly of me.
Previous work:
Atkey, Robert. 2006. Parameterised notions of computation. In MSFP 2006: Workshop on mathematically structured functional programming, ed. Conor McBride and Tarmo Uustalu. Electronic Workshops in Computing, British Computer Society. http://homepages.inf.ed.ac.uk/ratkey/param-notions.pdf
http://haskell.org/pipermail/haskell-cafe/2004-July/006448.html
Hmmm. Those look interesting, but don't seem to address the question of trying this in actual Haskell. I don't see any reason why this overloading wouldn't work, except for the inconvenience of having to lift and unlift everything that's not in a fun monad. Do you? Mightn't there be a way around that issue? -- David Roundy Department of Physics Oregon State University

On 12/17/06, David Roundy
Hello fellow haskellers,
I am wondering if anyone has an idea whether I'd run into trouble if I rebound >>= in order to provide a more restricted monad. My idea is to define a class:
. . .
which seems rather heavy. Can anyone think of syntax-light way to allow my hypothesized rebound do-notation to also work with ordinary monads?
You could try something like this:
import Prelude hiding (Monad (..)) import qualified Prelude (Monad (..)) as P
class WitnessMonad wm where ...
data M m w w' c = M (m c)
instance P.Monad m => WitnessMonad (M m) where ...
Then if everything works out, you should end up with M IO and such as WitnessMonads.

Here's a sketch of an idea as a solution to my dilemma, which unfortunately requires associated types. Any suggestions how it might be translatable into functional dependencies? (I should say, I've not got a HEAD ghc, and am just going by memory on my indexed types syntax.) class Witness w where type M w a b (>>=) :: M w a b x -> (x -> M w b c y) -> M w a c y (>>) :: M w a b x -> M w b c y -> M w a c y f >> g = f >>= const g return :: x -> M w a a x fail :: String -> M w a b x instance Monad m => Witness m where M m a b = m (>>=) = Prelude.(>>=) (>>) = Prelude.(>>) return = Prelude.return fail = Prelude.fail with these definitions it seems that any existing monad will continue to work as it always had, but I can now add new special sorts of monadish objects, such as data RepositoryMonad a b x = RM ... instance Witness RepositoryMonad where M RepositoryMonad x y = RepositoryMonad x y ... which would allow me to create a monad in which the actions are limited according to witness types, such as applyPatchToWorking :: Patch a b -> RepositoryMonad (rec,a) (rec,b) () -- David Roundy http://www.darcs.net

I've now almost got a FD solution to this problem, except that it won't work, and I don't know why. Of course, it's possible that the AT solution won't work either (I'm still compiling ghc, should have it in the morning...), but at least it seems far simpler. My FD solution is below. My trouble is that I really don't understand the limitations on FDs, which as I understand it is why Simon P.J. opposes adding them to Haskell': they're hard to understand. This all seems to work (although you'll see that I was reduced to using unsafeCoerce# in the IO instance, which is embarrassing--to say the least--but not unsafe), until I hit the RealWitness instance at the bottom, at which point ghc bombs out with: Witness.hs:33:0: Couldn't match expected type `m'' (a rigid variable) against inferred type `RealWitness a a'' `m'' is bound by the type signature for `>>' at Witness.hs:11:29 When using functional dependencies to combine Witness WitnessReally a b (RealWitness a b), (and a screenful more) Any suggestions? {-# OPTIONS -fno-implicit-prelude -fglasgow-exts #-} module Witness ( Witness ) where import GHC.Exts (unsafeCoerce#) import Prelude hiding ( (>>), (>>=), return, fail ) import qualified Prelude as P ( (>>), (>>=), return, fail ) class Witness w a b m | w a b -> m, m -> w a b where (>>=) :: (Witness w a a' m', Witness w a' b m'') => m' x -> (x -> m'' y) -> m y (>>) :: (Witness w a a' m', Witness w a' b m'') => m' x -> m'' y -> m y f >> g = f >>= const g private_return :: x -> m x fail :: String -> m x return :: Witness w a a m => x -> m x return = private_return data WitnessIO instance Witness WitnessIO () () IO where private_return = P.return fail = P.fail f >>= g = x2io f P.>>= y2io g where x2io :: Witness WitnessIO a b m => m x -> IO x x2io = unsafeCoerce# y2io :: Witness WitnessIO a b m => (y -> m x) -> (y -> IO x) y2io = unsafeCoerce# data RealWitness a b c -- this would be concrete data WitnessReally instance Witness WitnessReally a b (RealWitness a b) where {- The following monad is what I'd like to define if I could use associated type synonyms: class Witness w where type W w a b (>>=) :: W w a b x -> (x -> W w b c y) -> W w a c y (>>) :: W w a b x -> W w b c y -> W w a c y f >> g = f >>= const g return :: x -> W w a a x fail :: String -> W w a b x instance Monad m => Witness m where W m a b = m (>>=) = Prelude.(>>=) (>>) = Prelude.(>>) return = Prelude.return fail = Prelude.fail -}

Hello David, Monday, December 18, 2006, 6:00:29 AM, you wrote:
My trouble is that I really don't understand the limitations on FDs, which as I understand it is why Simon P.J. opposes adding them to Haskell': they're hard to understand.
ghc 6.6 user manual contains great introduction into FD -- Best regards, Bulat mailto:Bulat.Ziganshin@gmail.com

On the FD impasse:
Witness.hs:33:0: Couldn't match expected type `m'' (a rigid variable) against inferred type `RealWitness a a'' `m'' is bound by the type signature for `>>' at Witness.hs:11:29 When using functional dependencies to combine Witness WitnessReally a b (RealWitness a b), (and a screenful more)
Any suggestions?
What follows isn't so much a suggestion, but I think it's a description of this error's origins. Note that >>='s signature from the class declaration
class Witness w a b m | w a b -> m, m -> w a b where (>>=) :: (Witness w a a' m', Witness w a' b m'') => m' x -> (x -> m'' y) -> m y (>>) :: (Witness w a a' m', Witness w a' b m'') => m' x -> m'' y -> m y f >> g = f >>= const g private_return :: x -> m x fail :: String -> m x
is "copied" to this instance declaration,
instance Witness WitnessReally a b (RealWitness a b) where
so we have: (>>=) :: ( Witness WitnessReally a a' m' , Witness WitnessReally a' b m'' ) => m' x -> (x -> m'' y) -> (RealWitness a b) y Now consider what the signature of >>= for this instance would be if this "copy from the class to the instance" operation were savvy to our plans: (>>=) :: ( Witness WitnessReally a a' (RealWitness a a') , Witness WitnessReally a' b (RealWitness a' b) ) => (RealWitness a a') x -> (x -> (RealWitness a' b) y) -> (RealWitness a b) y This signature is what the FD analyzer determines. Our above error arises because the actual signature of >>= has m' where the FDs indicate we'll always have (RealWitness a a'). Does that seem accurate? (I've put off actually looking at the GHC source for ages now...) In my opinion, this is reminiscent of some of the scoped-type variable issues and notions (e.g. wobbly types). By the functional dependency |w a b -> m|, we know that the m' and m'' in the signature of >>= will be determined as some particular types (i.e. the class is a type function from w a b to m), and we'd just like to refer to whatever those types actually are as m' and m''. It seems the FD analyzer determines for us what those particular types are, but then the type-checker is unhappy that we're naming them m' and m'' when we should know more about them (e.g. that they have a RealWitness tycon). Unfortunately, we have no choice about the signature of >>= at the instance declaration, since it's copied straight from the class declaration. If m' and m'' were recognized as partially wobbly variables, then maybe this wouldn't be a problem. Or maybe wobbly types could be framed in terms of functional dependencies on a non-method's signature? (The rest might be off-topic.) This situation also conjures up some of my own confusion about FDs, the open world assumption, and "finalizing" a typeclass. One of my main confusions with FDs is how they play with the open world assumption. Another confusion is that just because your instance declarations satisfy the FDs of a class, they won't necessisarily allow the type inference engine to act in accord to those FDs. Sometimes you have to break a class's definition into ancillary classes, each with one of the FDs you want and appropriate instance declarations to drive the inference along those particular FDs. If you try to cram all of the FDs into one set of instance declarations, they tend to choke the FD analyzer. (I read FDs as "a b and c" determine "x y and z"; this is a description of the class's membership, but the FD analysis takes place on the instance declarations themselves and not necessarily the types admitted to the class.) Nick

Hi David, I don't think you need functional dependencies or associated type synonyms to get your example to work. In the past, I have used the abstraction that you are describing (I call it an "indexed monad" and it has a nice categorical definition). Here is how you can define it:
class IxMonad m where (>>>=) :: m i j a -> (a -> m j k b) -> m i k b ret :: a -> m i i a
Next, you wanted to define an instances that captured the fact that any monad is trivially an indexed monad. Here is how you can do this:
newtype FromMonad m i j a = M { unM :: m a }
instance Monad m => IxMonad (FromMonad m) where ret x = M (return x) M m >>>= f = M (m >>= (unM . f))
We use a newtype to prevent this instance overlapping with other instances. And just for fun we can define another indexed monad: state that supports "strong updates" (i.e., the type of the state can change as you compute):
newtype State i j a = S { unS :: i -> (a,j) }
instance IxMonad State where ret x = S (\s -> (x,s)) S m >>>= f = S (\s1 -> let (a,s2) = m s1 in unS (f a) s2)
Here are some operations to access and modify the state:
get :: State s s s get = S (\s -> (s,s))
set :: s1 -> State s2 s1 s2 set s1 = S (\s2 -> (s2,s1))
Notice that swapping "s1" and "s2" results in a type error. Nice. Also by choosing different operations one can enforce other properties. Now lets try it out:
test = set True >>>= \x -> set 'a' >>>= \y -> ret (x,y)
And it is all Haskell 98! Another interesting example of
an indexed monad is the continuation monad (I noticed that
from Wadler's "Composable Continuations" paper).
I hope this helps!
-Iavor
On 12/17/06, David Roundy
Here's a sketch of an idea as a solution to my dilemma, which unfortunately requires associated types. Any suggestions how it might be translatable into functional dependencies? (I should say, I've not got a HEAD ghc, and am just going by memory on my indexed types syntax.)
class Witness w where type M w a b (>>=) :: M w a b x -> (x -> M w b c y) -> M w a c y (>>) :: M w a b x -> M w b c y -> M w a c y f >> g = f >>= const g return :: x -> M w a a x fail :: String -> M w a b x
instance Monad m => Witness m where M m a b = m (>>=) = Prelude.(>>=) (>>) = Prelude.(>>) return = Prelude.return fail = Prelude.fail
with these definitions it seems that any existing monad will continue to work as it always had, but I can now add new special sorts of monadish objects, such as
data RepositoryMonad a b x = RM ... instance Witness RepositoryMonad where M RepositoryMonad x y = RepositoryMonad x y ...
which would allow me to create a monad in which the actions are limited according to witness types, such as
applyPatchToWorking :: Patch a b -> RepositoryMonad (rec,a) (rec,b) () -- David Roundy http://www.darcs.net _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

"Iavor Diatchki"
class IxMonad m where (>>>=) :: m i j a -> (a -> m j k b) -> m i k b ret :: a -> m i i a
And just for fun we can define another indexed monad: state that supports "strong updates" (i.e., the type of the state can change as you compute):
newtype State i j a = S { unS :: i -> (a,j) }
This reminded me very much of the state monad (actually more general than a monad) used internally in the nhc98/yhc compiler. Attached below. Niklas Rojemo came up with this formulation in 1993. Regards, Malcolm ---- module State where -- Use >>> and >>>= instead of >> and >>= to avoid problems with 1.3 prelude infixl 5 >>>,>>>=,=>>> infixr 4 >=> type State0 d s s' = d -> s -> s' type State d s u s' = d -> s -> (u,s') -- 'unit' is what is now known as 'return' in monad-speak unitS :: u -> State d s u s unitS u = (\d s -> (u,s)) unitS0 :: State0 d s s unitS0 = (\d s -> s) -- There are four 'bind'-like operators, >>>, >>>=, =>>>, and >=> (>>>) :: State0 d a b -> State0 d b c -> State0 d a c f >>> g = \d s -> g d (f d s) (=>>>) :: State d s (a->b) s' -> State d s' a s'' -> State d s b s'' f =>>> g = \d s -> case f d s of (h,s) -> case g d s of (x,s) -> let hx = h x in seq hx (hx,s) -- f =>>> g = \d s -> case f d s of (h,s) -> case g d s of (x,s) -> (h x,s) (>>>=) :: State d s a s' -> (a -> State0 d s' s'') -> State0 d s s'' f >>>= g = \d s -> case f d s of (x,s) -> g x d s (>=>) :: State d s d' s' -> State0 d' s' s'' -> State0 d s s'' f >=> g = \d s -> case f d s of (d,s) -> (g d s) mapS :: (a->State d s b s) -> [a] -> State d s [b] s mapS f [] = unitS [] mapS f (x:xs) = unitS (:) =>>> f x =>>> mapS f xs mapS0 :: (a->State0 d s s) -> [a] -> State0 d s s mapS0 f [] = unitS0 mapS0 f (x:xs) = f x >>> mapS0 f xs zipWithS :: (a -> b -> State d s c s) -> [a] -> [b] -> State d s [c] s zipWithS f [] [] = unitS [] zipWithS f (x:xs) (y:ys) = unitS (:) =>>> f x y =>>> zipWithS f xs ys zipWithS _ _ _ = error "zipWithS: lists of different lengths" ----

On Mon, Dec 18, 2006 at 06:52:41PM -0800, Iavor Diatchki wrote:
Hi David,
I don't think you need functional dependencies or associated type synonyms to get your example to work. In the past, I have used the abstraction that you are describing (I call it an "indexed monad" and it has a nice categorical definition).
The trouble is that your solution doesn't allow you to use do-notation with the IxMonad. And if you did allow yourself to use do-notation by rebinding (>>=), etc, then you wouldn't be able to use ordinary monads with do-notation in the same module. That's what makes things tricky, since an IxMonad is different-kinded from Monad, so you can't make a monad an instance of IxMonad. David

David Roundy wrote:
The trouble is that your solution doesn't allow you to use do-notation with the IxMonad. And if you did allow yourself to use do-notation by rebinding (>>=), etc, then you wouldn't be able to use ordinary monads with do-notation in the same module. That's what makes things tricky, since an IxMonad is different-kinded from Monad, so you can't make a monad an instance of IxMonad.
Seems to me that this screams for camlp4. Oops, wrong language ;-) But seriously, this kind of thing seems to arise often enough that having a standard method for doing "syntax extensions" for Haskell seems like a good idea. And as far as making Monad instances for IxMonad, this is where partial application at the class level would come in rather handy. Seems to be that (at least) IxMonad m () () should be a Monad. Jacques

On Tue, Dec 19, 2006 at 10:08:12AM -0500, Jacques Carette wrote:
David Roundy wrote:
The trouble is that your solution doesn't allow you to use do-notation with the IxMonad. And if you did allow yourself to use do-notation by rebinding (>>=), etc, then you wouldn't be able to use ordinary monads with do-notation in the same module. That's what makes things tricky, since an IxMonad is different-kinded from Monad, so you can't make a monad an instance of IxMonad.
Seems to me that this screams for camlp4. Oops, wrong language ;-)
But seriously, this kind of thing seems to arise often enough that having a standard method for doing "syntax extensions" for Haskell seems like a good idea.
Rebinding the do notation is at least reasonably clean, it's just that we don't want to lose the ability to mix with ordinary monads. I'm not sure that syntax extensions are very often a good idea...
And as far as making Monad instances for IxMonad, this is where partial application at the class level would come in rather handy. Seems to be that (at least) IxMonad m () () should be a Monad.
Indeed, that's true, but it's hard to go the other way around, but it is possible (I believe) to go the other way around with associated types. My latest attemp (which won't compile with the HEAD ghc that I just compiled, probably because I haven't figured out the synatax for guards with indexed types is: class WitnessMonad m where type W m :: * -> * -> * (>>=) :: (WitnessMonad m', WitnessMonad m'', w a b = W m', w b c = W m'', w a c = W m) => m' x -> (x -> m'' y) -> m y (>>) :: (WitnessMonad m', WitnessMonad m'', w a b = W m', w b c = W m'', w a c = W m) => m' x -> m'' y -> m y f >> g = f >>= const g return :: w a a = W m x => -> m x fail :: String -> m x data Witness a b instance Monad m => WitnessMonad m where W m = Witness () () (>>=) = Prelude.(>>=) (>>) = Prelude.(>>) return = Prelude.return fail = Prelude.fail which I think is quite pretty. It allows the Monadlike object to have kind * -> *, while still allowing us to hide extra witness types inside and pull them out using the W function. -- David Roundy http://www.darcs.net

First, I believe that this paper http://homepages.inf.ed.ac.uk/ratkey/param-notions.pdf is intimately related to WitnessMonad. David Roundy wrote:
Rebinding the do notation is at least reasonably clean, it's just that we don't want to lose the ability to mix with ordinary monads. This inability is what made me suggest an experimental syntax extension rather than rebinding.
I'm not sure that syntax extensions are very often a good idea...
I view syntax extensions as a proof-of-concept mechanism: you show that your new idea, if it had proper syntactic support, can make some kinds of programming a lot easier and clearer. Then hopefully the extension gets incorporated into official syntax. If not, then the extension should in time disappear. The main advantage is to make experiments (for new syntax) possible. Right now, the barriers to surmount for syntactic matters is quite high. I agree that it is rare that a syntax extension is really a "good" idea.
data Witness a b
instance Monad m => WitnessMonad m where W m = Witness () () (>>=) = Prelude.(>>=) (>>) = Prelude.(>>) return = Prelude.return fail = Prelude.fail
which I think is quite pretty. It allows the Monadlike object to have kind * -> *, while still allowing us to hide extra witness types inside and pull them out using the W function.
Yes, if you can make that work, that is quite pretty. Jacques

Hi,
On 12/19/06, Jacques Carette
First, I believe that this paper http://homepages.inf.ed.ac.uk/ratkey/param-notions.pdf is intimately related to WitnessMonad.
This paper definitely seems to be related. Thanks for the link! -Iavor

David Roundy
My latest attemp (which won't compile with the HEAD ghc that I just compiled, probably because I haven't figured out the synatax for guards with indexed types is:
class WitnessMonad m where type W m :: * -> * -> * (>>=) :: (WitnessMonad m', WitnessMonad m'', w a b = W m', w b c = W m'', w a c = W m) => m' x -> (x -> m'' y) -> m y (>>) :: (WitnessMonad m', WitnessMonad m'', w a b = W m', w b c = W m'', w a c = W m) => m' x -> m'' y -> m y f >> g = f >>= const g return :: w a a = W m x => -> m x fail :: String -> m x
data Witness a b
instance Monad m => WitnessMonad m where W m = Witness () () (>>=) = Prelude.(>>=) (>>) = Prelude.(>>) return = Prelude.return fail = Prelude.fail
which I think is quite pretty. It allows the Monadlike object to have kind * -> *, while still allowing us to hide extra witness types inside and pull them out using the W function.
Did anyone with knowledge of Associated Types pursue this solution? It doesn't work with GHC head, and I can't really do anything about that. Mostly curiosity. Thanks pepe ---------------------------------------------------------------- Everything from here on is to convince GMane that, even if my message contains more quoted text than fresh text, it is a legitimate message and it should be ok to post it.

Pepe Iborra:
David Roundy
writes: My latest attemp (which won't compile with the HEAD ghc that I just compiled, probably because I haven't figured out the synatax for guards with indexed types is:
class WitnessMonad m where type W m :: * -> * -> * (>>=) :: (WitnessMonad m', WitnessMonad m'', w a b = W m', w b c = W m'', w a c = W m) => m' x -> (x -> m'' y) -> m y (>>) :: (WitnessMonad m', WitnessMonad m'', w a b = W m', w b c = W m'', w a c = W m) => m' x -> m'' y -> m y f >> g = f >>= const g return :: w a a = W m x => -> m x fail :: String -> m x
data Witness a b
instance Monad m => WitnessMonad m where W m = Witness () () (>>=) = Prelude.(>>=) (>>) = Prelude.(>>) return = Prelude.return fail = Prelude.fail
which I think is quite pretty. It allows the Monadlike object to have kind * -> *, while still allowing us to hide extra witness types inside and pull them out using the W function.
Did anyone with knowledge of Associated Types pursue this solution?
Where did you get this from. My haskell-cafe mail folder doesn't seem to have the thread you are replying to.
It doesn't work with GHC head, and I can't really do anything about that. Mostly curiosity.
The main reason this doesn't work with the head is because the implementation of associated type *synonyms* (as opposed to associated data types) is still incomplete. (See also http://haskell.org/haskellwiki/GHC/Indexed_types.) We are working at the implementation, but I just relocated from New York to Sydney, which is why not much happened in the last two months. But I also don't quite understand the intention of this code: * What exactly is the kind of the type function W supposed to be? Is it "(* -> *) -> *"? If so, then the declaration needs to be class WitnessMonad m where type W m :: * .... That is, assuming (m :: * -> *), we have (W m :: *) with (W :: (* -> *) -> *). * In the signature (>>=) :: (WitnessMonad m', WitnessMonad m'', w a b = W m', w b c = W m'', w a c = W m) what is the purpose of "w" (and hence the purpose of the equality constraints)? What you really want is to impose a kind of state transition relationship on the monads involved in monad binds, right? * In the instance, using Prelude.>>= for the witness monad won't work. After all, Prelude.>>= can only combine two actions in the same monad, but the WitnessMonad signature promises to combine two different WitnessMonads (under certain constraints). * Another problem with the instance is that it requires undecidable instances. As I am not quite sure about the intention of the code it is hard to propose a fix. In particular, I have no idea how you want to combine two different witness monads in (>>=). Manuel

Did anyone with knowledge of Associated Types pursue this solution?
Where did you get this from. My haskell-cafe mail folder doesn't seem to have the thread you are replying to.
Sorry I replied from gmane; I should have included a link to the original thread, but I really expected gmane to do that. The thread is at: http://www.haskell.org/pipermail/haskell-cafe/2006-December/020615.html
It doesn't work with GHC head, and I can't really do anything about that. Mostly curiosity.
The main reason this doesn't work with the head is because the implementation of associated type *synonyms* (as opposed to associated data types) is still incomplete. (See also http://haskell.org/haskellwiki/GHC/Indexed_types.) We are working at the implementation, but I just relocated from New York to Sydney, which is why not much happened in the last two months.
But I also don't quite understand the intention of this code:
I will try to fill in the details, but surely it is all expanded in the original thread. The idea is that we have an indexed/effectful monad where bind and return have a parameterized type: class WitnessMonad m where (>>=) :: m a b x -> (x -> m b c y) -> m a c y return :: x -> m a a x We can produce instances of WitnessMonad from an existing Monad using an adaptor newtype WitnessAdaptor m a b x = W {unW::m x} instance Monad m => WitnessMonad (WitnessAdaptor m) And rebind the do syntax to our WitnessMonad. But using vanilla Monads via this trick requires to lift and unlift every monadic action with the adaptor. An example in the IO monad: test1 :: IO String test1 = unW$ do msg <- W getLine W$ putStrLn "Thanks!" return msg From here on the intent was on producing a solution using ATs that hides this explicit wrapping. I don't really know the details of the proposed solution. Thanks pepe
participants (10)
-
Bulat Ziganshin
-
Chung-chieh Shan
-
David Roundy
-
Iavor Diatchki
-
ihope
-
Jacques Carette
-
Malcolm Wallace
-
Manuel M T Chakravarty
-
Nicolas Frisby
-
Pepe Iborra