type checking that I can't figure out ....

Hello Haskellers, I isolated to a not so small piece:
{-# OPTIONS -fglasgow-exts #-} {-# LANGUAGE UndecidableInstances #-}
import Control.Monad.Identity import Control.Monad.Reader import Control.Monad.State import qualified Data.List as L import qualified Data.Map as M import Data.Array
import IOExts The type of a regular expression.
data Re t = ReOr [Re t] | ReCat [Re t] | ReStar (Re t) | RePlus (Re t) | ReOpt (Re t) | ReTerm [t] deriving (Show)
The internal type of a regular expression.
type SimplRe t = Int data SimplRe' t = SReOr (SimplRe t) (SimplRe t) | SReCat (SimplRe t) (SimplRe t) | SReStar (SimplRe t) | SReLambda | SReNullSet | SReTerm t deriving (Eq, Ord, Show)
The regular expression builder monad.
data (Ord t) => ReRead t = ReRead { rerNullSet :: SimplRe t, rerLambda :: SimplRe t }
data (Ord t) => ReState t = ReState { resFwdMap :: M.Map (SimplRe t) (ReInfo t), resBwdMap :: M.Map (SimplRe' t) (SimplRe t), resNext :: Int, resQueue :: ([SimplRe t], [SimplRe t]), resStatesDone :: [SimplRe t] }
type ReM m t a = StateT (ReState t) (ReaderT (ReRead t) m) a
TEMP WNH Dfa construction
data ReDfaState t = ReDfaState { dfaFinal :: Bool, dfaTrans :: [(t, SimplRe t)] } deriving (Show)
TEMP WNH The ReInfo type
data ReInfo t = ReInfo { reiSRE :: SimplRe' t, reiNullable :: Bool, reiDfa :: Maybe (ReDfaState t) } deriving (Show)
TEMP WNH
class (Monad m, Ord t) => ReVars m t where { } instance (Monad m, Ord t) => ReVars m t where { }
TEMP WNH
remLookupFwd :: (ReVars m t) => SimplRe t -> ReM m t (ReInfo t) remLookupFwd re = do fwd <- gets resFwdMap -- let { Just reinfo = M.lookup fwd re } -- PROBLEM reinfo <- M.lookup fwd re -- PROBLEM return reinfo
When I "compile" with ghci I get: Dfa_exp.lhs:91:32: Couldn't match expected type `M.Map (M.Map (SimplRe t) (ReInfo t)) t1' against inferred type `SimplRe t2' In the second argument of `M.lookup', namely `re' In a 'do' expression: reinfo <- M.lookup fwd re In the expression: do fwd <- gets resFwdMap reinfo <- M.lookup fwd re return reinfo I trimmed the original code down a lot! But still can't why I am getting type check errors!!! Help! Kind regards, Vasili

remLookupFwd :: (ReVars m t) => SimplRe t -> ReM m t (ReInfo t) remLookupFwd re = do fwd <- gets resFwdMap -- let { Just reinfo = M.lookup fwd re } -- PROBLEM reinfo <- liftMaybe $ M.lookup re fwd -- PROBLEM return reinfo
liftMaybe :: Monad m => Maybe a -> m a liftMaybe Nothing = fail "Nothing" liftMaybe (Just x) = return x
I made two changes: 1. You had the arguments to M.lookup backwards. 2. lookup does not return any generalized Monad, just Maybe (I think that should be changed). I added the simple liftMaybe function to convert the Maybe result into something that will work with your state monad. Michael

Hi Michael,
Let me look tomorrow morning. In any case, many thanks!
Kind regards,
Vasili
On Tue, Jun 2, 2009 at 11:12 PM, Michael Snoyman
remLookupFwd :: (ReVars m t) => SimplRe t -> ReM m t (ReInfo t) remLookupFwd re = do fwd <- gets resFwdMap -- let { Just reinfo = M.lookup fwd re } -- PROBLEM reinfo <- liftMaybe $ M.lookup re fwd -- PROBLEM return reinfo
liftMaybe :: Monad m => Maybe a -> m a liftMaybe Nothing = fail "Nothing" liftMaybe (Just x) = return x
I made two changes:
1. You had the arguments to M.lookup backwards. 2. lookup does not return any generalized Monad, just Maybe (I think that should be changed). I added the simple liftMaybe function to convert the Maybe result into something that will work with your state monad.
Michael

Am Mittwoch 03 Juni 2009 06:12:46 schrieb Michael Snoyman:
I made two changes:
1. You had the arguments to M.lookup backwards. 2. lookup does not return any generalized Monad, just Maybe (I think that should be changed).
Data.Map.lookup used to return a value in any monad you wanted, I believe until 6.8 inclusive. I don't think it's going to change again soon.
I added the simple liftMaybe function to convert the Maybe result into something that will work with your state monad.
Michael

On Wed, Jun 3, 2009 at 8:42 AM, Daniel Fischer
Am Mittwoch 03 Juni 2009 06:12:46 schrieb Michael Snoyman:
I made two changes:
1. You had the arguments to M.lookup backwards. 2. lookup does not return any generalized Monad, just Maybe (I think that should be changed).
Data.Map.lookup used to return a value in any monad you wanted, I believe until 6.8 inclusive. I don't think it's going to change again soon.
Is there a reason why it only returns in the Maybe monad? I often times have to write a liftMaybe function to deal with that. Michael

Michael Snoyman wrote:
On Wed, Jun 3, 2009 at 8:42 AM, Daniel Fischer
wrote: Am Mittwoch 03 Juni 2009 06:12:46 schrieb Michael Snoyman:
2. lookup does not return any generalized Monad, just Maybe (I think that should be changed).
Data.Map.lookup used to return a value in any monad you wanted, I believe until 6.8 inclusive. I don't think it's going to change again soon.
Is there a reason why it only returns in the Maybe monad? I often times have to write a liftMaybe function to deal with that.
Here's the proposal that changed it: http://hackage.haskell.org/trac/ghc/ticket/2309 The discussion about the proposal can be found here: http://www.haskell.org/pipermail/libraries/2008-May/009698.html (There's even the suggestion of adding a function like liftMaybe to Data.Maybe, but apparently nobody turned that into a formal proposal.) Regards, Bertram

It seems like if we could get fail out of Monad and into something
like MonadFail/Zero, then it might make sense to make a lookup that
returned an instance of that instead?
Dan
On Wed, Jun 3, 2009 at 8:13 PM, Bertram Felgenhauer
Michael Snoyman wrote:
On Wed, Jun 3, 2009 at 8:42 AM, Daniel Fischer
wrote: Am Mittwoch 03 Juni 2009 06:12:46 schrieb Michael Snoyman:
2. lookup does not return any generalized Monad, just Maybe (I think that should be changed).
Data.Map.lookup used to return a value in any monad you wanted, I believe until 6.8 inclusive. I don't think it's going to change again soon.
Is there a reason why it only returns in the Maybe monad? I often times have to write a liftMaybe function to deal with that.
Here's the proposal that changed it: http://hackage.haskell.org/trac/ghc/ticket/2309
The discussion about the proposal can be found here: http://www.haskell.org/pipermail/libraries/2008-May/009698.html
(There's even the suggestion of adding a function like liftMaybe to Data.Maybe, but apparently nobody turned that into a formal proposal.)
Regards,
Bertram _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

On Wed, Jun 3, 2009 at 8:52 PM, Daniel Peebles
It seems like if we could get fail out of Monad and into something like MonadFail/Zero, then it might make sense to make a lookup that returned an instance of that instead?
Dan
Do you mean splitting up MonadPlus/Alternative into two classes? Or we could just return in MonadPlus/Alternative. Antoine

Yeah, in a way similar to ArrowPlus/ArrowZero. Then again, I'm not
sure whether it would be meaningful to split up MonadPlus like that.
On Thu, Jun 4, 2009 at 12:40 AM, Antoine Latter
On Wed, Jun 3, 2009 at 8:52 PM, Daniel Peebles
wrote: It seems like if we could get fail out of Monad and into something like MonadFail/Zero, then it might make sense to make a lookup that returned an instance of that instead?
Dan
Do you mean splitting up MonadPlus/Alternative into two classes? Or we could just return in MonadPlus/Alternative.
Antoine

Daniel Peebles wrote:
Yeah, in a way similar to ArrowPlus/ArrowZero. Then again, I'm not sure whether it would be meaningful to split up MonadPlus like that.
Well, we could always have: class MonadZero m => MonadPlus m The suggestion is just to broaden the scope of mzero so that you can have it without requiring mplus as well (since mplus is much more specific than mzero). If we have a MonadZero, then the call to fail when pattern binds fail could be replaced with calls to mzero (or at the very least, fail can be moved to MonadZero as well to clean up Monad). Then Monad is clean and accurate, and people just depend on MonadZero if they choose to do pattern binds rather than catching all patterns with a case expression. -- Live well, ~wren

G'day Vasili. This should do it: remLookupFwd :: (ReVars m t) => SimplRe t -> ReM m t (ReInfo t) remLookupFwd re = do fwd <- gets resFwdMap let { Just reinfo = fromJust (M.lookup re fwd) } return reinfo The FiniteMap lookup operation took its arguments in the opposite order. That's really the only problem here AFAICT. Wow, this brings back memories. I wrote this module about ten years ago, and I'm shocked that it's still getting use. I'd appreciate a copy when you're done updating it for the modern era. Cheers, Andrew Bromage
participants (8)
-
ajb@spamcop.net
-
Antoine Latter
-
Bertram Felgenhauer
-
Daniel Fischer
-
Daniel Peebles
-
Michael Snoyman
-
Vasili I. Galchin
-
wren ng thornton