Re: [Haskell-cafe] type checking that I can't figure out ....

2009-06-04 Thread wren ng thornton

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
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] type checking that I can't figure out ....

2009-06-03 Thread Michael Snoyman
On Wed, Jun 3, 2009 at 8:42 AM, Daniel Fischer daniel.is.fisc...@web.dewrote:

 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
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] type checking that I can't figure out ...

2009-06-03 Thread Vasili I. Galchin
Hi Andrew (Bromage),

   I reversed the  parameter order to Data.Map.lookup and calling
fromJust to pull out value from Maybe wrapper ... all as you suggested:

 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) }
-- PROBLEM
return reinfo


I am still getting a type mismatch:


Swish\HaskellRDF\Dfa\Dfa.lhs:162:29:
Couldn't match expected type `Maybe t'
   against inferred type `ReInfo t1'
In the expression: fromJust (M.lookup re fwd)
In a pattern binding: Just reinfo = fromJust (M.lookup re fwd)
In the expression:
do fwd - gets resFwdMap
   let Just reinfo = fromJust (M.lookup re fwd)
   return reinfo

Vasili
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] type checking that I can't figure out ...

2009-06-03 Thread Ross Mellgren
You've applied two solutions to get the value out -- pattern matching  
(Just reinfo) and fromJust. You should use one or the other, but not  
both:


-- pattern matching
remLookupFwd :: (ReVars m t) = SimplRe t - ReM m t (ReInfo t)
remLookupFwd re
   = do fwd - gets resFwdMap
let { Just reinfo = M.lookup re fwd }--  
PROBLEM

return reinfo

-- fromJust
remLookupFwd :: (ReVars m t) = SimplRe t - ReM m t (ReInfo t)
remLookupFwd re
   = do fwd - gets resFwdMap
let { reinfo = fromJust (M.lookup re  
fwd) }-- PROBLEM

return reinfo

BTW, I would personally write this as one line (untested)

gets (fromJust . M.lookup re . resFwdMap)

-Ross

On Jun 3, 2009, at 1:18 PM, Vasili I. Galchin wrote:


Hi Andrew (Bromage),

   I reversed the  parameter order to Data.Map.lookup and  
calling fromJust to pull out value from Maybe wrapper ... all as you  
suggested:


 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) }-- PROBLEM

return reinfo


I am still getting a type mismatch:


Swish\HaskellRDF\Dfa\Dfa.lhs:162:29:
Couldn't match expected type `Maybe t'
   against inferred type `ReInfo t1'
In the expression: fromJust (M.lookup re fwd)
In a pattern binding: Just reinfo = fromJust (M.lookup re fwd)
In the expression:
do fwd - gets resFwdMap
   let Just reinfo = fromJust (M.lookup re fwd)
   return reinfo

Vasili
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] type checking that I can't figure out ...

2009-06-03 Thread Henning Thielemann
Ross Mellgren schrieb:
 You've applied two solutions to get the value out -- pattern matching
 (Just reinfo) and fromJust. You should use one or the other, but not both:
 
 -- pattern matching
 remLookupFwd :: (ReVars m t) = SimplRe t - ReM m t (ReInfo t)
 remLookupFwd re
= do fwd - gets resFwdMap
 let { Just reinfo = M.lookup re fwd }-- PROBLEM
 return reinfo
 
 -- fromJust
 remLookupFwd :: (ReVars m t) = SimplRe t - ReM m t (ReInfo t)
 remLookupFwd re
= do fwd - gets resFwdMap
 let { reinfo = fromJust (M.lookup re fwd) }   
 -- PROBLEM
 return reinfo
 
 BTW, I would personally write this as one line (untested)
 
 gets (fromJust . M.lookup re . resFwdMap)

fromJust should be avoided, since it is partial and if it results in an
error, the error message points to the implementation of fromJust, not
its application. Pattern matching is better, but 'maybe' and 'fromMaybe'
are best.

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] type checking that I can't figure out ...

2009-06-03 Thread Ross Mellgren

True, so perhaps better written as:

import Data.Maybe (fromMaybe)

gets (fromMaybe (error could not find re in resFwdMap) . M.lookup  
re . resFwdMap)


with more detail in error message as appropriate.

-Ross

On Jun 3, 2009, at 5:57 PM, Henning Thielemann wrote:


Ross Mellgren schrieb:

You've applied two solutions to get the value out -- pattern matching
(Just reinfo) and fromJust. You should use one or the other, but  
not both:


-- pattern matching
remLookupFwd :: (ReVars m t) = SimplRe t - ReM m t (ReInfo t)
remLookupFwd re
  = do fwd - gets resFwdMap
   let { Just reinfo = M.lookup re fwd }--  
PROBLEM

   return reinfo

-- fromJust
remLookupFwd :: (ReVars m t) = SimplRe t - ReM m t (ReInfo t)
remLookupFwd re
  = do fwd - gets resFwdMap
   let { reinfo = fromJust (M.lookup re fwd) }
-- PROBLEM
   return reinfo

BTW, I would personally write this as one line (untested)

gets (fromJust . M.lookup re . resFwdMap)


fromJust should be avoided, since it is partial and if it results in  
an

error, the error message points to the implementation of fromJust, not
its application. Pattern matching is better, but 'maybe' and  
'fromMaybe'

are best.

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] type checking that I can't figure out ....

2009-06-03 Thread Bertram Felgenhauer
Michael Snoyman wrote:
 On Wed, Jun 3, 2009 at 8:42 AM, Daniel Fischer 
 daniel.is.fisc...@web.dewrote:
  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


Re: [Haskell-cafe] type checking that I can't figure out ....

2009-06-03 Thread 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

On Wed, Jun 3, 2009 at 8:13 PM, Bertram Felgenhauer
bertram.felgenha...@googlemail.com wrote:
 Michael Snoyman wrote:
 On Wed, Jun 3, 2009 at 8:42 AM, Daniel Fischer 
 daniel.is.fisc...@web.dewrote:
  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

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] type checking that I can't figure out ....

2009-06-03 Thread Antoine Latter
On Wed, Jun 3, 2009 at 8:52 PM, Daniel Peebles pumpkin...@gmail.com 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
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] type checking that I can't figure out ....

2009-06-03 Thread Daniel Peebles
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 aslat...@gmail.com wrote:
 On Wed, Jun 3, 2009 at 8:52 PM, Daniel Peebles pumpkin...@gmail.com 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

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] type checking that I can't figure out ....

2009-06-02 Thread Vasili I. Galchin
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
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] type checking that I can't figure out ....

2009-06-02 Thread 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
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] type checking that I can't figure out ....

2009-06-02 Thread Vasili I. Galchin
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 mich...@snoyman.comwrote:

  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

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] type checking that I can't figure out ....

2009-06-02 Thread ajb

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
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] type checking that I can't figure out ....

2009-06-02 Thread 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.

 I added the simple liftMaybe function to convert the
 Maybe result into something that will work with your state monad.

 Michael

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe