
It sounds like you tried to redefine (>>) and (>>=) and make 'do' use the new definitions. This is not possible, regardless of what types you give (>>) and (>>=).
Watch out for rebindable syntax: (...)
At first reading, I thought that -XNoImplicitPrelude was required to turn this on. But now I'm not sure: (...)
I wrote this test to check your sugestion. It does build with -XNoImplicitPrelude, but not without it: ---------- module Test where { import Prelude hiding ( ( >> ) , ( >>= ) ) ; data PseudoMonad a = PseudoMonad a ; ( >> ) = \(PseudoMonad x) (PseudoMonad _) -> PseudoMonad x ; ( >>= ) = (\(PseudoMonad a) f -> f a) :: PseudoMonad Integer -> (Integer -> PseudoMonad Integer) -> PseudoMonad Integer; plusOne n = (PseudoMonad (n + 1)) :: PseudoMonad Integer; c = (PseudoMonad 1) >> ((PseudoMonad 2) >>= (\n -> plusOne n)); d = do {(PseudoMonad 1) ; a <- (PseudoMonad 2) ; plusOne a } } ---------- It's interesting that the types involved in >>= etc. should still be like "t t1", that's why I had to create PseudoMonad. Using just Integer (i.e., 2
3 would be valid) doesn't work, even if all operators are defined accordingly.
Best, Maurício