Alex Coleman
Alex Coleman

Reputation: 647

Pattern match on guard expression

Suppose I have some very simple code:

import qualified Data.Map as Map
import Data.Maybe(fromJust)

keySum :: Map.Map Char Int -> Char -> Char -> Either String Int
keySum m key1 key2
  | val1 == Nothing = Left $ show val1 ++ " not in map"
  | val2 == Nothing = Left $ show val2 ++ " not in map"
  | otherwise       = Right $ val1' + val2'
  where 
    val1 = Map.lookup key1 m
    val2 = Map.lookup key2 m
    val1' = fromJust val1
    val2' = fromJust val2

Certainly, I don't want to use fromJust, and would rather pattern match on the result of Map.lookup here.

But how can I achieve this, without evaluating Map.lookup twice or passing it through some wrapper function?

Upvotes: 2

Views: 76

Answers (1)

leftaroundabout
leftaroundabout

Reputation: 120711

You can use a pattern guard:

keySum m key1 key2
  | Just val1 <- Map.lookup key1 m
  , Just val2 <- Map.lookup key2 m
               = Right $ val1 + val2
  | key1 `Map.notMember` m
               = Left $ show key1 ++ " not in map"
  | otherwise  = Left $ show key2 ++ " not in map"

But perhaps a good old case is actually the cleaner option:

keySum m k₀ k₁ = case (`Map.lookup` m) <$> [k₀,k₁] of
     [Just v₀, Just v₁] -> Right $ v₀ + v₁
     [Nothing, _      ] -> Left $ show k₀ ++ " not in map"
     _                  -> Left $ show k₁ ++ " not in map"

That can be simplified further by observing that it's just a standard applicative chain:

keySum m k₀ k₁ = (+) <$> lku k₀ <*> lku k₁
 where lku k = case Map.lookup k m of
         Just v -> Right v
         Nothing -> Left $ show k ++ " not in map"

If you're into patterns, this can also be written thus (personally I'm not such a fan of this extension):

{-# LANGUAGE ViewPatterns     #-}

keySum m k₀ k₁ = (+) <$> lku k₀ <*> lku k₁
 where lku ((`Map.lookup` m) -> Just v) = Right v
       lku k = Left $ show k ++ " not in map"

And finally, there's no reason to restrict this to only two keys, might as well sequence over a whole arbitrary-length list. Incidentally, there's no reason to pick concrete types.

import Data.Traversable (forM)

keySum :: (Ord a, Show a, Num b) => Map.Map a b -> [a] -> Either String b
keySum m ks = sum <$> forM ks `id` \k -> case Map.lookup k m of
         Just v -> Right v
         Nothing -> Left $ show k ++ " not in map"

Upvotes: 3

Related Questions