Re: Re[2]: [Haskell-cafe] nested maybes

2007-02-05 Thread Martin DeMello

On 2/5/07, Bulat Ziganshin [EMAIL PROTECTED] wrote:

Hello J.,

Sunday, February 4, 2007, 11:46:57 PM, you wrote:

 exists s wmap = isJust $ find (==s) . snd = Map.lookup (sort s) wmap

exists s wmap =  Map.lookup (sort s) wmap
== snd
== find (==s)
== isJust

a==b = a=return.b


Very nice! Didn't know about ==. Thanks to everyone else who
responded too; I'm learning a lot from this thread.

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


Re: [Haskell-cafe] nested maybes

2007-02-05 Thread Bryan Donlan

Martin DeMello wrote:

On 2/5/07, Bulat Ziganshin [EMAIL PROTECTED] wrote:

Hello J.,

Sunday, February 4, 2007, 11:46:57 PM, you wrote:

 exists s wmap = isJust $ find (==s) . snd = Map.lookup (sort s) wmap

exists s wmap =  Map.lookup (sort s) wmap
== snd
== find (==s)
== isJust

a==b = a=return.b


Very nice! Didn't know about ==. Thanks to everyone else who
responded too; I'm learning a lot from this thread.


(==) is user-defined; that's what the last line is for :)
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] nested maybes

2007-02-04 Thread Martin DeMello

I have a Data.Map.Map String - (Layout, [String]) as follows:

type Anagrams = [String]
type Cell = (Layout, Anagrams)
type WordMap = Map.Map String Cell

exists str wmap =
 let a = Map.lookup (sort str) wmap in
 case a of
  Nothing - False
  Just x - case (find (== str) (snd x)) of
 Nothing - False
 _   - True

the existence test looks ugly - any more compact way to write it?

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


Re: [Haskell-cafe] nested maybes

2007-02-04 Thread Lemmih

On 2/4/07, Martin DeMello [EMAIL PROTECTED] wrote:

I have a Data.Map.Map String - (Layout, [String]) as follows:

type Anagrams = [String]
type Cell = (Layout, Anagrams)
type WordMap = Map.Map String Cell

exists str wmap =
  let a = Map.lookup (sort str) wmap in
  case a of
   Nothing - False
   Just x - case (find (== str) (snd x)) of
  Nothing - False
  _   - True

the existence test looks ugly - any more compact way to write it?


How about:
exists str = fromMaybe False . fmap (elem str.snd) . Map.lookup (sort str)

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


Re: [Haskell-cafe] nested maybes

2007-02-04 Thread J. Garrett Morris

Maybe has a Monad instance, so you can write this as follows (untested):

exists str wmap = boolFromMaybe exists'
   where exists' =
 do x - Map.lookup (sort str) wmap
find (== str) (snd x)
 boolFromMaybe (Just _) = True
 boolFromMaybe Nothing  = False

/g


On 2/4/07, Martin DeMello [EMAIL PROTECTED] wrote:

I have a Data.Map.Map String - (Layout, [String]) as follows:

type Anagrams = [String]
type Cell = (Layout, Anagrams)
type WordMap = Map.Map String Cell

exists str wmap =
  let a = Map.lookup (sort str) wmap in
  case a of
   Nothing - False
   Just x - case (find (== str) (snd x)) of
  Nothing - False
  _   - True

the existence test looks ugly - any more compact way to write it?

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




--
It is myself I have never met, whose face is pasted on the underside of my mind.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] nested maybes

2007-02-04 Thread Mattias Bengtsson
On Sun, 2007-02-04 at 19:54 +0530, Martin DeMello wrote:
 I have a Data.Map.Map String - (Layout, [String]) as follows:
 
 type Anagrams = [String]
 type Cell = (Layout, Anagrams)
 type WordMap = Map.Map String Cell
 
 exists str wmap =
   let a = Map.lookup (sort str) wmap in
   case a of
Nothing - False
Just x - case (find (== str) (snd x)) of
   Nothing - False
   _   - True
 
 the existence test looks ugly - any more compact way to write it?
 

Using the Maybe Monad is one solution i think (as in: i _think_ this
should work):

findIt str wmap = do 
  a - Map.lookup (sort str) wmap
  return $ find (== str) (snd a)

exists str wmap = 
  case findIt str wmap of
Nothing - False
Just _ - True

The Maybe monad is very nice for abstracting away all those
case-expressions.


signature.asc
Description: This is a digitally signed message part
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] nested maybes

2007-02-04 Thread J. Garrett Morris

On 2/4/07, Udo Stenzel [EMAIL PROTECTED] wrote:

J. Garrett Morris wrote:
Small improvement (Data.Maybe is underappreciated):

 exists str wmap = isJust exists'
where exists' =
  do x - Map.lookup (sort str) wmap
 find (== str) (snd x)


This is true.  Some time ago I swore off the use of fromRight and
fromLeft in favor of maybe, and have been forgetting about the other
functions in Data.Maybe ever since.


and maybe another improvement, though this is dependent on your tastes:

 exists s wmap = isJust $ Map.lookup (sort s) wmap = find (== s) . snd


If you're going to write it all on one line, I prefer to keep things
going the same direction:

exists s wmap = isJust $ find (==s) . snd = Map.lookup (sort s) wmap

Normally, from there I would be tempted to look for a points-free
implementation, but in this case I have a strong suspicion that would
simply be unreadable.

/g

--
It is myself I have never met, whose face is pasted on the underside of my mind.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] nested maybes

2007-02-04 Thread Neil Mitchell

Hi


This is true.  Some time ago I swore off the use of fromRight and
fromLeft in favor of maybe, and have been forgetting about the other
functions in Data.Maybe ever since.


I think you mean you swore off fromJust. Unfortunately when people
started to debate adding fromLeft and fromRight they decided against
logic and consistency, and chose not to add them...

Thanks

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


Re: [Haskell-cafe] nested maybes

2007-02-04 Thread Udo Stenzel
J. Garrett Morris wrote:
 On 2/4/07, Udo Stenzel [EMAIL PROTECTED] wrote:
  exists s wmap = isJust $ Map.lookup (sort s) wmap = find (== s) . snd
 
 If you're going to write it all on one line, I prefer to keep things
 going the same direction:

Hey, doing it this way saved me a full two keystrokes!!!1

Sure, you're right, everything flowing in the same direction is usually
nicer, and in central Europe, that order is from the left to the right.
What a shame that the Haskell gods chose to give the arguments to (.)
and ($) the wrong order!

 exists s wmap = isJust $ find (==s) . snd = Map.lookup (sort s) wmap
 
 Normally, from there I would be tempted to look for a points-free
 implementation, but in this case I have a strong suspicion that would
 simply be unreadable.

Well, depends on whether we are allowed to define new combinators.  I
sometimes use

-- Kleisli composition
infixl 1 @@
(@@) :: Monad m = (a - m b) - (b - m c) - (a - m c)
f @@ g = join . liftM g . f

and the resulting

 exists s = Map.lookup (sort s) @@ find (== s) . snd  isJust

isn't all that bad.  (To be read as: one can get used to it.)  I also
think, (@@) and () belong in the Prelude and () at type ((a-b) -
(b-c) - (b-c)) should be known under a shorter name.  Unfortunately,
everything short but (?) is already taken...  

Of course, the remaining variable s could also be transformed away,
but that's really pointless.


-Udo
-- 
Never confuse motion with action. -- Ernest Hemingway


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


Re: [Haskell-cafe] nested maybes

2007-02-04 Thread Donald Bruce Stewart
u.stenzel:
 J. Garrett Morris wrote:
  On 2/4/07, Udo Stenzel [EMAIL PROTECTED] wrote:
   exists s wmap = isJust $ Map.lookup (sort s) wmap = find (== s) . snd
  
  If you're going to write it all on one line, I prefer to keep things
  going the same direction:
 
 Hey, doing it this way saved me a full two keystrokes!!!1
 
 Sure, you're right, everything flowing in the same direction is usually
 nicer, and in central Europe, that order is from the left to the right.
 What a shame that the Haskell gods chose to give the arguments to (.)
 and ($) the wrong order!
 
  exists s wmap = isJust $ find (==s) . snd = Map.lookup (sort s) wmap
  
  Normally, from there I would be tempted to look for a points-free
  implementation, but in this case I have a strong suspicion that would
  simply be unreadable.
 
 Well, depends on whether we are allowed to define new combinators.  I
 sometimes use
 
 -- Kleisli composition
 infixl 1 @@
 (@@) :: Monad m = (a - m b) - (b - m c) - (a - m c)
 f @@ g = join . liftM g . f

By the way, this is now in Control.Monad (in darcs). Though since we
also want the flipped version, it becomes:

-- | Left-to-right Kleisli composition of monads.
(=)   :: Monad m = (a - m b) - (b - m c) - (a - m c)
f = g = \x - f x = g

-- | Right-to-left Kleisli composition of monads. '(=)', with the
arguments flipped
(=)   :: Monad m = (b - m c) - (a - m b) - (a - m c)
(=)   = flip (=)

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


Re: [Haskell-cafe] nested maybes

2007-02-04 Thread J. Garrett Morris

On 2/4/07, Udo Stenzel [EMAIL PROTECTED] wrote:

J. Garrett Morris wrote:
 On 2/4/07, Udo Stenzel [EMAIL PROTECTED] wrote:
Well, depends on whether we are allowed to define new combinators.  I
sometimes use

-- Kleisli composition
infixl 1 @@
(@@) :: Monad m = (a - m b) - (b - m c) - (a - m c)
f @@ g = join . liftM g . f


I was responding to this, but Dons beat me to it.  Personally, I use
this combinator quite a bit.  (As much as I would rather use , the
Kleisli arrow is a bit verbose to use for my taste.)


and the resulting

 exists s = Map.lookup (sort s) @@ find (== s) . snd  isJust

isn't all that bad.  (To be read as: one can get used to it.)  I also
think, (@@) and () belong in the Prelude and () at type ((a-b) -
(b-c) - (b-c)) should be known under a shorter name.  Unfortunately,
everything short but (?) is already taken...


Presumably you mean (a - b) - (b - c) - (a - c)?

I would personally be fine with Arrows being in the prelude (and, for
instance, (.) defined as flip ()).  I'd support your shorter name
idea if I could think of one...

/g

--
It is myself I have never met, whose face is pasted on the underside of my mind.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe