Re: [Haskell-cafe] [Maybe Int] sans Nothings

2011-05-24 Thread Alexander Solla
On Mon, May 23, 2011 at 6:21 PM, Richard O'Keefe o...@cs.otago.ac.nz wrote:


 On 24/05/2011, at 5:49 AM, Alexander Solla wrote:
  There's a library function for it, but also:
 
   filter ((/=) Nothing)

 The problem with that in general is that it only
 applies to [Maybe t] if Eq t, but you don't
 actually _need_ t to support equality.
 filter isJust
 will do the job, where isJust is in Data.Maybe.


Indeed, isJust will do the job.   Sometimes it is acceptable to just use the
tools you know.  For example, filtering a list of (Maybe Int)s.  This is a
balance that is tough to get right.

Personally, I find non-functional values without Eq instances to be
degenerate.  So I really do not mind superfluous Eq constraints.  I would
not hesitate to use filter ((/=) Nothing) in a function whose type has no
free type variables.  It's just a bit of plumbing inside of a more complex
function.

But the point of avoiding unnecessary constraints is a good one, especially
for constraints that constrain more strongly, e.g., Ord.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] [Maybe Int] sans Nothings

2011-05-24 Thread Henning Thielemann
Alexander Solla schrieb:

 Personally, I find non-functional values without Eq instances to be
 degenerate.  So I really do not mind superfluous Eq constraints.  I
 would not hesitate to use filter ((/=) Nothing) in a function whose type
 has no free type variables.  It's just a bit of plumbing inside of a
 more complex function.

Sometimes it seems to be better to not allow Eq on Float and Double.
Since most algebraic laws do not hold for those types, it is more often
an error than an intention to compare two Float values. And how to
compare (IO a) values? Also, by thinking about function types, you often
get interesting use cases. Thus I would not assume too quickly that a
type will always be instantiated by types other than a function type.
Thus I would stick to (filter isJust) and use this consistently for
monomorphic and polymorphic types.

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


Re: [Haskell-cafe] [Maybe Int] sans Nothings

2011-05-24 Thread Alexander Solla


  Personally, I find non-functional values without Eq instances to be
  degenerate.  So I really do not mind superfluous Eq constraints.  I
  would not hesitate to use filter ((/=) Nothing) in a function whose type
  has no free type variables.  It's just a bit of plumbing inside of a
  more complex function.

 Sometimes it seems to be better to not allow Eq on Float and Double.
 Since most algebraic laws do not hold for those types, it is more often
 an error than an intention to compare two Float values. And how to
 compare (IO a) values?


Floats, Doubles, and IO are all degenerate types, for the reasons you
outline.  (Admittedly, Float and Double have Eq instances, but invalid Eq
semantics)  Notice how their value semantics each depend on the machine your
runtime runs on, as opposed to merely the runtime.  Bottom is another one of
these degenerate types, since comparisons on arbitrary values are
undecidable.

Also, by thinking about function types, you often
 get interesting use cases. Thus I would not assume too quickly that a
 type will always be instantiated by types other than a function type.
 Thus I would stick to (filter isJust) and use this consistently for
 monomorphic and polymorphic types.


I am not suggesting (filter ((/=) Nothing)) /over/ (filter isJust).
 Obviously, once one is aware of a  better tool, one should use it.  But I
am suggesting that for simple cases which are unlikely to change in any
substantive way, we should probably just use the tools we already know of,
as opposed to searching for the right one.  Both might involve costs.
 There is a cost involved in going to Google, thinking up a search term,
finding that Data.Maybe has relevant functions, picking the right one.  It
takes less time to write filter ... than to type haskell removing nothing
from list, for example.  When dealing with known unknowns, there is a
balance to be made, and it is not easy.

Michael's choice to ask the list imposed costs.  (Not that we mind, we're
all volunteers, after all).  But it probably took 10 minutes to get the
first reply.  He could have written a bit of code that worked correctly,
given the context of his problem, in 20 seconds.  Then again, he probably
worked on a different bit of code until somebody sent a solution, so we
probably only have to account for the time spent in context switching, for
everyone involved.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] [Maybe Int] sans Nothings

2011-05-23 Thread michael rice
What's the best way to end up with a list composed of only the Just values,no 
Nothings?
Michael
== 
import Control.Monad.Stateimport Data.Maybe

type GeneratorState = State Int
tick :: GeneratorState (Maybe Int)tick = do n - get          if ((n `mod` 7) 
== 0)            then              return Nothing            else do            
  put (n+1)              return (Just n)
{-*Main evalState (sequence $ replicate 9 tick) 1[Just 1,Just 2,Just 3,Just 
4,Just 5,Just 6,Nothing,Nothing,Nothing]-}
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] [Maybe Int] sans Nothings

2011-05-23 Thread Malcolm Wallace
On 23 May 2011, at 17:20, michael rice wrote:

 What's the best way to end up with a list composed of only the Just values,
 no Nothings?

Go to haskell.org/hoogle
Type in [Maybe a] - [a]
Click on first result.

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


Re: [Haskell-cafe] [Maybe Int] sans Nothings

2011-05-23 Thread Gregory Crosswhite

On 5/23/11 9:20 AM, michael rice wrote:
What's the best way to end up with a list composed of only the Just 
values,

no Nothings?





Try catMaybes in Data.Maybe.

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


Re: [Haskell-cafe] [Maybe Int] sans Nothings

2011-05-23 Thread Max Bolingbroke
On 23 May 2011 17:20, michael rice nowg...@yahoo.com wrote:

 What's the best way to end up with a list composed of only the Just values,
 no Nothings?

 http://haskell.org/hoogle/?hoogle=%3A%3A+%5BMaybe+a%5D+-%3E+%5Ba%5D

Data.Maybe.catMaybes is what you want :-)

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


Re: [Haskell-cafe] [Maybe Int] sans Nothings

2011-05-23 Thread Malcolm Wallace

On 23 May 2011, at 17:20, michael rice wrote:

 What's the best way to end up with a list composed of only the Just values,
 no Nothings?

Alternatively,

[ x  | Just x - originals ]

It also occurs to me that perhaps you still want the Just constructors.

[ Just x | Just x - originals ]
[ x  | x@(Just _) - originals ]


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


Re: [Haskell-cafe] [Maybe Int] sans Nothings

2011-05-23 Thread Gregory Crosswhite

On 5/23/11 9:29 AM, Max Bolingbroke wrote:
On 23 May 2011 17:20, michael rice nowg...@yahoo.com 
mailto:nowg...@yahoo.com wrote:


What's the best way to end up with a list composed of only the
Just values,
no Nothings?

http://haskell.org/hoogle/?hoogle=%3A%3A+%5BMaybe+a%5D+-%3E+%5Ba%5D

Data.Maybe.catMaybes is what you want :-)

Cheers,
Max



On 5/23/11 9:25 AM, Malcolm Wallace wrote:

On 23 May 2011, at 17:20, michael rice wrote:


What's the best way to end up with a list composed of only the Just values,
no Nothings?

Go to haskell.org/hoogle
Type in [Maybe a] -  [a]
Click on first result.

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


On 5/23/11 9:25 AM, Gregory Crosswhite wrote:

On 5/23/11 9:20 AM, michael rice wrote:
What's the best way to end up with a list composed of only the Just 
values,

no Nothings?





Try catMaybes in Data.Maybe.

Cheers,
Greg



GO TEAM HASKELL!!!

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


Re: [Haskell-cafe] [Maybe Int] sans Nothings

2011-05-23 Thread Alexander Solla
On Mon, May 23, 2011 at 9:20 AM, michael rice nowg...@yahoo.com wrote:

 What's the best way to end up with a list composed of only the Just values,
 no Nothings?

 Michael

 ==

 import Control.Monad.State
 import Data.Maybe


 type GeneratorState = State Int

 tick :: GeneratorState (Maybe Int)
 tick = do n - get
   if ((n `mod` 7) == 0)
 then
   return Nothing
 else do
   put (n+1)
   return (Just n)

 {-
 *Main evalState (sequence $ replicate 9 tick) 1
 [Just 1,Just 2,Just 3,Just 4,Just 5,Just 6,Nothing,Nothing,Nothing]
 -}


There's a library function for it, but also:

 filter ((/=) Nothing)

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


Re: [Haskell-cafe] [Maybe Int] sans Nothings

2011-05-23 Thread michael rice
Thanks, all.
Earlier, I was going to ask how to break out of a sequence op prematurely, 
i.e., you give it some replication number but want to break early if you get an 
end-flag value. While I was composing the post I thought of using Maybe for the 
good values and Nothing for the end value. Ergo, losing the Nothings at the end.
I was passing a map and an empty list into some state, but since the map 
doesn't change once it's created I moved it into a Reader. I was using the list 
to collect the elements but thought I can get that functionality automatically 
using sequence. 
So, one thing leads to another. It's interesting how ideas begin bubbling up 
after one absorbs some critical mass of Haskell.
Michael  
--- On Mon, 5/23/11, Malcolm Wallace malcolm.wall...@me.com wrote:

From: Malcolm Wallace malcolm.wall...@me.com
Subject: Re: [Haskell-cafe] [Maybe Int] sans Nothings
To: haskell-cafe Cafe haskell-cafe@haskell.org
Date: Monday, May 23, 2011, 12:35 PM


On 23 May 2011, at 17:20, michael rice wrote:

 What's the best way to end up with a list composed of only the Just values,
 no Nothings?

Alternatively,

    [ x      | Just x - originals ]

It also occurs to me that perhaps you still want the Just constructors.

    [ Just x | Just x - originals ]
    [ x      | x@(Just _) - originals ]


___
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] [Maybe Int] sans Nothings

2011-05-23 Thread Brent Yorgey
On Mon, May 23, 2011 at 10:49:55AM -0700, Alexander Solla wrote:
 On Mon, May 23, 2011 at 9:20 AM, michael rice nowg...@yahoo.com wrote:
 
  What's the best way to end up with a list composed of only the Just values,
  no Nothings?
 
  Michael
 
  ==
 
  import Control.Monad.State
  import Data.Maybe
 
 
  type GeneratorState = State Int
 
  tick :: GeneratorState (Maybe Int)
  tick = do n - get
if ((n `mod` 7) == 0)
  then
return Nothing
  else do
put (n+1)
return (Just n)
 
  {-
  *Main evalState (sequence $ replicate 9 tick) 1
  [Just 1,Just 2,Just 3,Just 4,Just 5,Just 6,Nothing,Nothing,Nothing]
  -}
 
 
 There's a library function for it, but also:
 
  filter ((/=) Nothing)
 
 is readable enough.

Just a minor quibble: note that

 filter (not . isNothing)

is slightly preferable since it does not introduce a frivolous
equality constraint on the type wrapped by the Maybe.

-Brent

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


Re: [Haskell-cafe] [Maybe Int] sans Nothings

2011-05-23 Thread Gregory Crosswhite

On 05/23/2011 12:08 PM, Brent Yorgey wrote:

Just a minor quibble: note that


  filter (not . isNothing)

is slightly preferable since it does not introduce a frivolous
equality constraint on the type wrapped by the Maybe.


Or even better,

filter isJust

:-)

Cheers,
Greg

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


Re: [Haskell-cafe] [Maybe Int] sans Nothings

2011-05-23 Thread Henning Thielemann
Brent Yorgey schrieb:
 On Mon, May 23, 2011 at 10:49:55AM -0700, Alexander Solla wrote:
 There's a library function for it, but also:

 filter ((/=) Nothing)
 is readable enough.
 
 Just a minor quibble: note that
 
 filter (not . isNothing)
 
 is slightly preferable since it does not introduce a frivolous
 equality constraint on the type wrapped by the Maybe.

Similar:
http://www.haskell.org/haskellwiki/Haskell_programming_tips#Reduce_type_class_constraints
http://www.haskell.org/haskellwiki/Haskell_programming_tips#Don.27t_ask_for_the_length_of_a_list_when_you_don.27t_need_it

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


Re: [Haskell-cafe] [Maybe Int] sans Nothings

2011-05-23 Thread Ertugrul Soeylemez
Gregory Crosswhite gcr...@phys.washington.edu wrote:

 Or even better,

  filter isJust

To make it worse again the original function can be generalized in a few
ways.  Here is a generalization from the inner Maybe type:

import Data.Foldable as F

catFoldables :: Foldable t = [t a] - [a]
catFoldables = concatMap F.toList

Here is a generalization from the outer list type:

joinMaybes :: (Alternative m, Monad m) = m (Maybe a) - m a
joinMaybes = (= maybe empty pure)

And finally the generalization from everything:

import Data.Foldable as F

joinFoldables :: (Alternative m, Foldable t, Monad m) = m (t a) - m a
joinFoldables = (= F.foldr (\x _ - pure x) empty)

The final function looks a bit scary, but is actually surprisingly easy
to understand, once you realize that 'foldr' is just a generalization of
the 'maybe' function.  The structure of Maybe is a list structure with
at most one element after all.


Greets,
Ertugrul


-- 
nightmare = unsafePerformIO (getWrongWife = sex)
http://ertes.de/

-- 
nightmare = unsafePerformIO (getWrongWife = sex)
http://ertes.de/



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


Re: [Haskell-cafe] [Maybe Int] sans Nothings

2011-05-23 Thread Richard O'Keefe

On 24/05/2011, at 5:49 AM, Alexander Solla wrote:
 There's a library function for it, but also:
 
  filter ((/=) Nothing)

The problem with that in general is that it only
applies to [Maybe t] if Eq t, but you don't
actually _need_ t to support equality.
filter isJust
will do the job, where isJust is in Data.Maybe.


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