[Haskell-cafe] golf, predicate check function for MonadPlus (was
Re: How to read safely?)
Alexander Dunlap
alexander.dunlap at gmail.com
Thu Jul 2 15:16:38 EDT 2009
On Thu, Jul 2, 2009 at 3:36 AM, Jon Fairbairn<jon.fairbairn at cl.cam.ac.uk> wrote:
> Dan Doel <dan.doel at 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.Fairbairn at 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
More information about the Haskell-Cafe
mailing list