[Haskell-cafe] beginners question about fromMaybe
Ryan Ingram
ryani.spam at gmail.com
Tue Jun 2 21:49:25 EDT 2009
Luke's answer is great (although it changes argument order). Hint:
http://www.haskell.org/haskellwiki/Things_to_avoid#Avoid_explicit_recursion
I also like the "pattern guards" GHC extension; I tend to use it over
"maybe" and "either". I find the resulting code more readable:
> {-# LANGUAGE PatternGuards #-}
> probePhase is sc xs m = concatMap prefix xs where
> prefix x
> | Just val <- Map.lookup (getPartialTuple is x) m = joinTuples sc x val
> | otherwise = []
Alternatively, I might write it like this:
> import Control.Monad
> maybeM :: MonadPlus m => Maybe a -> m a
> maybeM = maybe mzero return
> probePhase is sc xs m = do
> x <- xs
> val <- maybeM $ Map.lookup (getPartialTuple is x) m
> joinTuples sc x val
This now works for any xs that is an instance of MonadPlus (assuming
joinTuples is also polymorphic).
Both of these examples are more wordy than Luke's quick two-liner,
but, to me, it's worth it for the additional "maintainability" of that
code. I am perhaps in the minority on this issue, though :)
-- ryan
On Tue, Jun 2, 2009 at 4:20 PM, Luke Palmer <lrpalmer at gmail.com> wrote:
>
>
> On Tue, Jun 2, 2009 at 4:59 PM, Nico Rolle <nrolle at web.de> wrote:
>>
>> hi there
>>
>> heres a code snipped, don't care about the parameters.
>> the thing is i make a lookup on my map "m" and then branch on that return
>> value
>>
>> probePhase is sc [] m = []
>> probePhase is sc (x:xs) m
>> | val == Nothing = probePhase is sc xs m
>> | otherwise = jr ++ probePhase is sc xs m
>> where
>> jr = joinTuples sc x (fromMaybe [] val)
>> key = getPartialTuple is x
>> val = Map.lookup key m
>
> Here's my take. This ought to be equivalent, but I haven't tested.
> probePhase is sc m = concatMap prefix
> where
> prefix x = let key = getPartialTuple is x in
> maybe [] (joinTuples sc x) $ Map.lookup key m
>>
>>
>>
>> the line "jr = joinTuples sc x (fromMaybe [] val)" is kind of ugly
>> because i know that it is not Nothing.
>> is there a better way to solve this?
>> regards
>> _______________________________________________
>> Haskell-Cafe mailing list
>> Haskell-Cafe at haskell.org
>> http://www.haskell.org/mailman/listinfo/haskell-cafe
>
>
> _______________________________________________
> Haskell-Cafe mailing list
> Haskell-Cafe at haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
>
>
More information about the Haskell-Cafe
mailing list