Pattern match(es) are non-exhaustive

Have you written another line of getSymbol which begins:

getSymbol Nothing = ...

If not, that’s why you’re seeing that warning. GHC is telling you that getSymbol is a partial function, and if it receives Nothing as an input as runtime, it will throw a runtime error.

7 Likes

The COMPLETE pragma is only necessary if you are using pattern synonyms, which requires the PatternSynonyms extension to be turned on.

2 Likes

Let me extrapolate this to some more general advice. If you look at getSymbol, you’ll see that if is a value of type Maybe Operations -> Maybe Char. In other words, it’s a function which takes a value of type Maybe Operations and produces a value of type Maybe Char. In order for this function to be total (i.e. defined on any possible input), you need to have a pattern matching any possible input. The line

getSymbol (Just oper) ...

only matches input values of the form Just oper (where oper is a variable of type Operations) but such input values are only a subset of the values that live in the type Maybe Operations. That is because another value lives in Maybe Operations, namely Nothing. So you need a state explicitly how getSymbol will handle this with a second pattern match.

Haskell lets you write partial functions (functions defined only on a subset of the domain) but you rarely want to do this, and what you’re seeing is a warning to that effect.

2 Likes

reuben explained the issue very well, and so I don’t want to reexplain it, but I do want to add one last thing.

You might still be wondering why the Nothing input case isn’t caught by your otherwise guard, or, in the second form, by the _ case. This is because for the program to get to those cases, you need to have given it an input of the form (Just oper) :: Maybe Operations and Nothing is not of that form (this is the disjointness of sum types). It won’t go into those cases if you pass Nothing into the function, because that would be the wrong pattern, since Nothing are Just a are different constructors. Since you didn’t also supply a Nothing case, the pattern is unexhaustive. The otherwise guard is superfluous because you already exhausted all of the Just (oper) :: Maybe Operations options. If it still doesn’t make sense, write out on a piece of paper all of the values of the type Maybe Operations, and then see if there’s one last one that’s missing from your function definition. I can understand why you might think at first that the otherwise guard would catch a Nothing input, but it does not because the pattern you’re matching on is (pseudo notation) (Just a) :: Maybe Operations | Nothing :: Maybe Operations. This is also why the compiler error is telling you that the pattern not matched is the Nothing pattern. Sorry, I probably did end up reexplaining, but I hope this helps you see why what you wrote didn’t work, instead of just explaining how to fix it.

2 Likes

Not sure this is the best but works.

getSymbol :: Maybe Operations -> Maybe Char
getSymbol (Just oper)
  | oper == Addition = Just '+'
  | oper == Subtraction = Just '-'
  | oper == Multiplication = Just '*'
  | oper == Division = Just '/'
  | oper == Modulus = Just '%'
getSymbol isNothing = Nothing

I did realized that there was a Nothing to be matched on but I was surprised that otherwise or _ didn’t work and still am. I thought that on the LHS of = in a guard one only needed an expression that evaluated to True or False. But it appears in this case it needed to do that and be of type Operations since that is what I was matching on.

I got on the right track when I re-read Rubin’s comment and “a second pattern match” grabbed my attention. In my mind each guard was “a pattern match”. I now see I had a terminology mix-up.

Thank you! That was very educational!

Not sure if I read the “and still am” right but in case you are still wondering:
The guards are further constraining the patter-match for Just oper that’s why the otherwise did not fire.

I’d suggest to not use == but pattern-matching too for the operations. Here are a few way to rewrite this:

getSymbol :: Maybe Operations -> Maybe Char
getSymbol (Just Addition) = Just '+'
getSymbol (Just Subtraction) = Just '-'
getSymbol (Just Multiplication) = Just '*'
getSymbol (Just Division) = Just '/'
getSymbol (Just Modulus) = Just '%'
getSymbol isNothing = Nothing

or maybe nicer (notice that you actually only care about getting a symbol for the operations and that you are in the situation where fmap for Maybe can be used):

getSymbol:: Maybe Operations -> Maybe Char
getSymbol = fmap getSymbol'

getSymbol' :: Operations -> Char
getSymbol' Addition = '+'
getSymbol' Subtraction = '-'
getSymbol' Multiplication = '*'
getSymbol' Division = '/'
getSymbol' Modulus = '%'
3 Likes

Before you wrote that, did you try writing getSymbol Nothing = Nothing? What you wrote works, for sure, but its like writing

f :: Bool -> Int
f True    = 1
f isFalse = 0

Yes, that works, but can you see why it’s kind of silly? There is only one other data constructor in the Bool type, namely False, and so we know that the only other argument to the function that the compiler will accept is False, so why wouldn’t we use the constructor itself to pattern match on, instead of providing a defaulting case which is what putting a variable like isNothing or isFalse does? It’s the same with your function, the only other possible input to your function that Haskell will accept is Nothing, so why wouldn’t you just pattern match on it?

I was being genuine when I said that if you are confused about what is going on, you should write down all the possible values of type Maybe Operations, (there are only six, it’s not a big list) and I still think that it will help you clear up what is going on. When you pattern match on a type, and this is why I referenced the disjointedness of sum types, you need to provide a case for each constructor, or else have a defaulting case. Maybe is defined like this

data Maybe a = Nothing | Just a

which means that it has two constructors, Nothing and Just a. It doesn’t matter what type a is in Maybe a, if you want to write a function to pattern match on Maybe a, you need to write your function like

g :: Maybe a -> b
g (Just a) = doSomething
g Nothing  = doSomethingElse

Otherwise you are missing a pattern (unless you provide a default, but again I outlined above why a default seems weird in this kind of situation). It doesn’t matter what doSomething does, it doesn’t matter if it itself is a case analysis on the type a that could even involves its own Maybe type, you are passing a value of type Maybe a into the function, so the only argument that will cause doSomething to be evaluated is one of the form Just a. Nothing is not of that form, it is a different type constructor, and so Haskell will not enter into the body of the Just a pattern when given Nothing because it does not match that pattern. There is no way for the guards to ‘catch’ the Nothing because Nothing is a pattern that is matched against the definition of your function getSymbol, not against a function on the other side of the equals sign, which in essence is what the guards are (if you don’t see how that is, rewrite your guards using nested if then else's, for example).

And here, I’ll write out all six of the values in case you really don’t want to do it:

(Just Addition)       :: Maybe Operations
(Just Subtraction)    :: Maybe Operations
(Just Multiplication) :: Maybe Operations
(Just Division)       :: Maybe Operations
(Just Modulus)        :: Maybe Operations
Nothing               :: Maybe Operations

No other value (other than something like undefined obviously) has the type Maybe Operations. If you want to pattern match on the type, you need to provide a case for each of the constructors, Just a and Nothing, and writing only one case that matches on Just a will not cover the Nothing case, because it is a different pattern, and so the compiler will throw a non-exhaustive pattern error.

1 Like

I did write down the possibilities as you listed them but it didn’t help because I already knew I needed to match Nothing in some way (or maybe it should be working and I’m still missing something). I just didn’t know how to and I now see it was a pretty wrong-headed simple thing. I wish the error had said: “Invalid pattern match” or something like that.

In addition to what I originally posted

getSymbol :: Maybe Operations -> Maybe Char
getSymbol (Just oper)
  ...
  | otherwise = Nothing

I had tried

getSymbol :: Maybe Operations -> Maybe Char
getSymbol (Just oper)
  ...
  | Nothing = Nothing

And I see now that was a case of not understanding patterns.

Given that realization I tried

I tried

getSymbol :: Maybe Operations -> Maybe Char
getSymbol Nothing = Nothing
getSymbol (Just oper)
  | oper == Addition = Just '+'
  | oper == Subtraction = Just '-'
  | oper == Multiplication = Just '*'
  | oper == Division = Just '/'
  | oper == Modulus = Just '%'

Gives warning

Pattern match(es) are non-exhaustive
In an equation for ‘getSymbol’:
    Patterns not matched:
        Just Addition
        Just Subtraction
        Just Multiplication
        Just Division
getSymbol :: Maybe Operations -> Maybe Char
getSymbol (Just oper)
  | oper == Addition = Just '+'
  | oper == Subtraction = Just '-'
  | oper == Multiplication = Just '*'
  | oper == Division = Just '/'
  | oper == Modulus = Just '%'
getSymbol Nothing = Nothing  

Same warning

So I still don’t see a way to use Nothing = Nothing.

simpleCalcCarstenK2.hs

data Operations = Addition | Subtraction | Multiplication | Division | Modulus
  deriving (Show, Eq)

getSymbol:: Maybe Operations -> Maybe Char
getSymbol = fmap getSymbol'

getSymbol' :: Operations -> Char
getSymbol' Addition = '+'
getSymbol' Subtraction = '-'
getSymbol' Multiplication = '*'
getSymbol' Division = '/'
getSymbol' Modulus = '%'

getOperation :: Foldable t => t Char -> Maybe Operations
getOperation str
| '+' `elem` str = Just Addition
| '-' `elem` str = Just Subtraction
| '*' `elem` str = Just Multiplication
| '/' `elem` str = Just Division
| '%' `elem` str = Just Modulus
| otherwise = Nothing

main :: IO ()
main = do
  userInput <- getContents
  print userInput
  let operation = getOperation userInput
  let b = getSymbol operation
  print b
> ghc simpleCalcCarstenK2.hs
> ./simpleCalcCarstenK2
1 + 2
"1 + 2\n"
-- press ctrl-d
Just '+'

So that is all good. Here is the question:

  • I’m passing to getSymbol a Maybe Operations
  • It appears that getSymbol is passing that Maybe Operations to getSymbol' but a Operations is expected.
  • What is really happening there?

That warning is why you probably want to use a case statement or pattern matching instead of guards in this case, see this explanation I wrote for a similar problem.

4 Likes
getSymbol :: Maybe Operations -> Maybe Char
getSymbol (Just Addition)       = Just '+'
getSymbol (Just Subtraction)    = Just '-'
getSymbol (Just Multiplication) = Just '*'
getSymbol (Just Division)       = Just '/'
getSymbol (Just Modulus)        = Just '%'
getSymbol Nothing               = Nothing

is how the function looks when it’s defined with pattern matching,

getSymbol' :: Maybe Operations -> Maybe Char
getSymbol' = \maybeOper -> case maybeOper of
  Just Addition       -> Just '+'
  Just Subtraction    -> Just '-'
  Just Multiplication -> Just '*'
  Just Division       -> Just '/'
  Just Modulus        -> Just '%'
  Nothing             -> Nothing

is the equivalent way of writing it using case. The point of bringing up the process of writing down all of the different pieces of data that can have the type was to get you to write these out, but I can understand how what I said might not have made this point entirely clear. When you pattern match, you need to cover all cases, or otherwise have a default. Because your original attempt didn’t have a default, it only had cases for a Just a, there was no definition given for the Nothing case. Again, it didn’t matter that you had a wild card or otherwise in the function that the Just a pattern called, Nothing would never enter it because you told the function you only wanted inputs of the pattern Just a there.

3 Likes

Sorry to revive this but I was helping a friend with some code which made me remember this post, and I realized that we were so caught up in the discussion of pattern matching that we didn’t paused to think about monads. A better way, I think, to handle this would be like this

data Operations = Addition | Subtraction | Multiplication | Division | Modulus
  deriving (Show, Eq)

fromOpToChar :: Operations -> Char
fromOpToChar Addition       = '+'
fromOpToChar Subtraction    = '-'
fromOpToChar Multiplication = '*'
fromOpToChar Division       = '/'
fromOpToChar Modulus        = '%'

getSymbol :: Maybe Operations -> Maybe Char
getSymbol maybeOper = maybeOper >>= liftOpToChar
  where
    liftOpToChar = return . fromOpToChar

This way, we separate the monadic code from the nonmonadic code. There isn’t a real reason to wrap the process of going from an operation to a character in Maybe, because every data constructor in Operations has a corresponding Char. Maybe only comes into play when you’re trying to pass the result of a failed parse (assuming this code is being used for parsing). But of course that’s exactly what >>= does for Maybe, if you feed it Nothing it pipes that all the way through, otherwise it takes what’s inside Just and feeds it into the function. So we can write fromOpToChar in a pure way, and isolate the monadic code to getSymbol only.

I know the original question was about pattern matching, not necessarily about how to use moands, but I think this answer actually does address the original question in that it shows that we can leverage >>= to not have to write the Nothing case ourselves, and only pattern match on the actual constructors in Operations. The power and glory of monads.

3 Likes

You’re reinventing fmap:

getSymbol = fmap fromOpToChar
3 Likes

Absolutely. I think I tunnel visioned on monads so much that I completely ignored the types. That’s interesting though, hlint doesn’t pick up on this but it seems obvious, at least to a person, when you look at the types. I wonder how hard it is to check for that, something like (pure/return . f) should be a giveaway, but maybe it’s more complicated in context.

1 Like

I think hlint does pick up x >>= return . f, but you broke it up into two parts.

1 Like

Thanks for you comment on Maybe. I had that on my list to things to confirm but lots of this example was difficult for me so I never got to it.

I just starting a unit in the book I’m leaning from on functor, applicative and monad, so perhaps your answer will make more sense when I complete that.

You are simply not accounting for the possibility that the function is passed Nothing. If it is never passed Nothing, consider changing the signature to Operations -> Maybe Char.

The pattern matching occurs before the | guard checking. Guards only ever apply to one pattern match.

If you think you need it to be Maybe Operations -> Maybe Char, you can use >=> or do notation to “extract” the value(?) :: x from the Maybe x container and apply x -> Maybe y onto it (if it exists). This is possible because Maybe is a Monad (and a Functor).

I am confused why

getSymbol :: Maybe Operations -> Maybe Char
getSymbol Nothing = Nothing
getSymbol (Just oper)
  | oper == Addition = Just '+'
  | oper == Subtraction = Just '-'
  | oper == Multiplication = Just '*'
  | oper == Division = Just '/'
  | oper == Modulus = Just '%'

gives warning

Pattern match(es) are non-exhaustive
In an equation for ‘getSymbol’:
    Patterns not matched:
        Just Addition
        Just Subtraction
        Just Multiplication
        Just Division

Doesn’t oper act as a named wildcard for all Just _ instances?

@jaror

The problem is that GHC doesn’t really know anything about ==, so even if you cover all the cases with x == A || x == B || ... then it can still not conclude that it is exhaustive. And indeed, you can write an odd Eq instance and definition of == for your type so that it doesn’t handle all cases.

See also my earlier comment: Pattern match(es) are non-exhaustive - #11 by jaror

2 Likes

Thanks for the re-prompt @jaror. Very natural solutions proposed in your link, and I didn’t know LT.
I am impressed by the built-in self-awareness of GHC to acknowledge that it cannot guarantee that getSymbol well defined. This is a fine feature indeed!