
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 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

If you're absolutely certain that the lookup always succeeds, then you
can use pattern matching as follows:
where
jr = joinTuples sc x val
key = getPartialTuple is x
Just val = Map.lookup key m
On 6/3/09, Nico Rolle
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
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@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

I just noticed that my suggestion doesn't work. You're testing whether
val is Nothing and in my code snipped val has a different type.
On 6/3/09, Raynor Vliegendhart
If you're absolutely certain that the lookup always succeeds, then you can use pattern matching as follows:
where jr = joinTuples sc x val key = getPartialTuple is x Just val = Map.lookup key m
On 6/3/09, Nico Rolle
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
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@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

On Tue, Jun 2, 2009 at 4:59 PM, Nico Rolle
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@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

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
On Tue, Jun 2, 2009 at 4:59 PM, Nico Rolle
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@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

On Wed, Jun 3, 2009 at 8:59 AM, Nico Rolle
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
the line "jr = joinTuples sc x (fromMaybe [] val)" is kind of ugly because i know that it is not Nothing.
Although pattern matching is probably nicer, there's also fromJust which will throw an exception if you pass it Nothing. I prefer: case Map.lookup key m of Nothing -> next Just val -> (joinTuples sc x val) ++ next where next = probePhase ... key = ...
participants (5)
-
Luke Palmer
-
Nico Rolle
-
Raynor Vliegendhart
-
Ryan Ingram
-
Toby Hutton