Re: [Haskell-cafe] golf, predicate check function for MonadPlus (was Re: How to read safely?)

2009-07-06 Thread Dan Doel
On Thursday 02 July 2009 6:36:09 am Jon Fairbairn wrote:
 check :: (MonadPlus m) = (a - Bool) - a - m a
 check p a
 | p a = return a
 | otherwise = mzero

 I tried Hoogling for a function like check, but couldn't find it. Surely
 there's one in a library somewhere? It looks useful to me. (I'm rather
 taken by way the check (all isSpace . snd) part reads)

 Monad.guard comes close but fails to get the cigar; in fact

 guard b == check (const b) ()

 So check is more general.

I've often noticed the need for a similar function in conjunction with 
unfoldr:

  -- This is overly general for unfoldr, but it lines up with check
  stopAt :: (MonadPlus m) = (a - Bool) - (a - b) - a - m b
  stopAt p f x
| p x   = mzero
| otherwise = return (f x)

  -- stopAt p f x = guard (not $ p x)  return (f x)
  -- stopAt p f = liftM2 () (guard . not . p) (return . f)
  -- etc.

Then you can write:

  unfoldr (stopAt p $ f)

where p is a stopping predicate based on the seed, and f unfolds the seed one 
step. This lets you use the many functions in the standard library that have 
types like:

  s - (a, s)

where unfoldr wants them to instead be:

  s - Maybe (a, s)

However, I don't really like the name stopAt, and have never come up with 
anything better.

And of course: check = flip stopAt id . not

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


Re: [Haskell-cafe] golf, predicate check function for MonadPlus (was Re: How to read safely?)

2009-07-06 Thread Antoine Latter
On Mon, Jul 6, 2009 at 8:49 PM, Dan Doeldan.d...@gmail.com wrote:

 I've often noticed the need for a similar function in conjunction with
 unfoldr:

  -- This is overly general for unfoldr, but it lines up with check
  stopAt :: (MonadPlus m) = (a - Bool) - (a - b) - a - m b
  stopAt p f x
    | p x       = mzero
    | otherwise = return (f x)

  -- stopAt p f x = guard (not $ p x)  return (f x)
  -- stopAt p f = liftM2 () (guard . not . p) (return . f)
  -- etc.

 Then you can write:

  unfoldr (stopAt p $ f)


I have the following function sitting around:

unfoldUntil :: (b - Bool) - (b - (a, b)) - b - [a]
unfoldUntil p f n = unfoldr g n
 where g m | p m   = Nothing
   | otherwise = Just $ f m

But I don't remeber where I picked it up from. It looks like it fills
a similar niche.

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


[Haskell-cafe] golf, predicate check function for MonadPlus (was Re: How to read safely?)

2009-07-02 Thread Jon Fairbairn
Dan Doel dan.d...@gmail.com writes:

 There was talk of adding a readMaybe a while ago, but apparently it
 never happened.

 As it is, you can use reads, read s becomes:

 case reads s of
   [(a, rest)] | all isSpace rest - code using a
   _  - error case

 which ensures that you have an unambiguous parse with only trailing
 whitespace. You can, of course, modify that if you don't care about
 ambiguity or trailing characters.

I was wondering about a more algebraic way of writing that; here's a
version (that doesn't care about ambiguity)

readMaybe :: Read a = String - Maybe a
readMaybe
= join . fmap no_trailing_garbage . listToMaybe . reads
  where no_trailing_garbage = fmap fst . check (all isSpace . snd)

check :: (MonadPlus m) = (a - Bool) - a - m a
check p a
| p a = return a
| otherwise = mzero


I tried Hoogling for a function like check, but couldn't find it. Surely
there's one in a library somewhere? It looks useful to me. (I'm rather
taken by way the check (all isSpace . snd) part reads)

Monad.guard comes close but fails to get the cigar; in fact 

guard b == check (const b) ()

So check is more general.


Also, I don't see a singletonListToMaybe that one could use in place of
listToMaybe to require unambiguity. Could do

isSingleton [a] = True
isSingleton _ = False

and then use listToMaybe . join . check isSingleton -- aha! Another
use for check!




 Jón


[Footnote: I thought of writing guard == flip (check . const) () but
then realised it was pointless]

-- 
Jón Fairbairn jon.fairba...@cl.cam.ac.uk

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


Re: [Haskell-cafe] golf, predicate check function for MonadPlus (was Re: How to read safely?)

2009-07-02 Thread Alexander Dunlap
On Thu, Jul 2, 2009 at 3:36 AM, Jon Fairbairnjon.fairba...@cl.cam.ac.uk wrote:
 Dan Doel dan.d...@gmail.com writes:

 There was talk of adding a readMaybe a while ago, but apparently it
 never happened.

 As it is, you can use reads, read s becomes:

     case reads s of
       [(a, rest)] | all isSpace rest - code using a
       _                              - error case

 which ensures that you have an unambiguous parse with only trailing
 whitespace. You can, of course, modify that if you don't care about
 ambiguity or trailing characters.

 I was wondering about a more algebraic way of writing that; here's a
 version (that doesn't care about ambiguity)

 readMaybe :: Read a = String - Maybe a
 readMaybe
    = join . fmap no_trailing_garbage . listToMaybe . reads
      where no_trailing_garbage = fmap fst . check (all isSpace . snd)

 check :: (MonadPlus m) = (a - Bool) - a - m a
 check p a
    | p a = return a
    | otherwise = mzero


 I tried Hoogling for a function like check, but couldn't find it. Surely
 there's one in a library somewhere? It looks useful to me. (I'm rather
 taken by way the check (all isSpace . snd) part reads)

 Monad.guard comes close but fails to get the cigar; in fact

 guard b == check (const b) ()

 So check is more general.


 Also, I don't see a singletonListToMaybe that one could use in place of
 listToMaybe to require unambiguity. Could do

 isSingleton [a] = True
 isSingleton _ = False

 and then use listToMaybe . join . check isSingleton -- aha! Another
 use for check!




  Jón


 [Footnote: I thought of writing guard == flip (check . const) () but
 then realised it was pointless]

 --
 Jón Fairbairn                                 jon.fairba...@cl.cam.ac.uk


You can use the Kleisli composition operator (=) to make it a little nicer.

singletonListToMaybe :: [a] - Maybe a
singletonListToMaybe [x] = Just x
singletonListToMaybe _ = Nothing

check :: MonadPlus m = (a - Bool) - a - m a
check p a
  | p a = return a
  | otherwise = mzero

readMaybe = fmap fst.check (all isSpace.snd) = singletonListToMaybe.reads

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