pattern matching on function names or algebraic type data constructors

Hi, I ask myself if there is a way to make the following code work. I would like to pattern match on function names: ----------- f :: Float -> Int f x = 1 g :: Float -> Int g x = 2 pat :: (Float -> Int) -> Bool pat t = case t of f -> True g -> False main = do print $ pat f print $ pat g ----------- I don't understand the output: ----------- $ runghc test_pattern_match_on_function_2.hs test_pattern_match_on_function_2.hs:8:9: Warning: Pattern match(es) are overlapped In a case alternative: g -> ... True True ----------- What is the reason for this message? Now, I want to do it on data constructors in a GADT (which are functions if I am right): ----------- {-# LANGUAGE GADTs #-} data Foobar where Mult :: Float -> Foobar Plus :: Float -> Foobar pat :: (Float -> Foobar) -> Bool pat t = case t of Mult -> True Plus -> False main = do print $ pat Mult print $ pat Plus ----------- I obtain: ----------- $ runghc test_pattern_match_on_function.hs test_pattern_match_on_function.hs:9:9: Constructor `Mult' should have 1 argument, but has been given none In the pattern: Mult In a case alternative: Mult -> True In the expression: case t of { Mult -> True Plus -> False } test_pattern_match_on_function.hs:9:9: Couldn't match expected type `Float -> Foobar' with actual type `Foobar' In the pattern: Mult In a case alternative: Mult -> True In the expression: case t of { Mult -> True Plus -> False } ----------- Why does it not work? If Mult and Plus are functions, then I should not need to put their arguments in pattern matching. Thanks in advance, TP

I think the deeper meaning of the error message is that functions are not part of the Eq type class. So you cannot really compare functions. Think about it: 2 functions are the same (mathematically) if they have the same signature and if they return the same value for each legal input. This is computationally not decidable. We could compare function identity, but that would be in contrast to the "referential transparency principle" of Haskell. I'm wondering why the code even compiles though.
Code example:
Prelude> (const 4) == (const 5)
<interactive>:5:11:
No instance for (Eq (b0 -> a0))
arising from a use of `=='
Possible fix: add an instance declaration for (Eq (b0 -> a0))
In the expression: (const 4) == (const 5)
In an equation for `it': it = (const 4) == (const 5)
-Michael
Am 23.06.2013 um 11:34 schrieb TP
Hi,
I ask myself if there is a way to make the following code work. I would like to pattern match on function names:
----------- f :: Float -> Int f x = 1
g :: Float -> Int g x = 2
pat :: (Float -> Int) -> Bool pat t = case t of f -> True g -> False
main = do
print $ pat f print $ pat g -----------
I don't understand the output:
----------- $ runghc test_pattern_match_on_function_2.hs
test_pattern_match_on_function_2.hs:8:9: Warning: Pattern match(es) are overlapped In a case alternative: g -> ... True True -----------
What is the reason for this message?
Now, I want to do it on data constructors in a GADT (which are functions if I am right): ----------- {-# LANGUAGE GADTs #-}
data Foobar where Mult :: Float -> Foobar Plus :: Float -> Foobar
pat :: (Float -> Foobar) -> Bool pat t = case t of Mult -> True Plus -> False
main = do
print $ pat Mult print $ pat Plus -----------
I obtain:
----------- $ runghc test_pattern_match_on_function.hs
test_pattern_match_on_function.hs:9:9: Constructor `Mult' should have 1 argument, but has been given none In the pattern: Mult In a case alternative: Mult -> True In the expression: case t of { Mult -> True Plus -> False }
test_pattern_match_on_function.hs:9:9: Couldn't match expected type `Float -> Foobar' with actual type `Foobar' In the pattern: Mult In a case alternative: Mult -> True In the expression: case t of { Mult -> True Plus -> False } -----------
Why does it not work? If Mult and Plus are functions, then I should not need to put their arguments in pattern matching.
Thanks in advance,
TP
_______________________________________________ Beginners mailing list Beginners@haskell.org http://www.haskell.org/mailman/listinfo/beginners

Hi TP,
What is the reason for this message?
'f' and 'g' in the 'case' expression are local names/bindings and have nothing in common with the 'f' and 'g' functions. It's the same like introducing names/bindings with the 'let' expression: let f = ... g = ... in ... The bindings are overlapping, because both match all the time and GHC will always use the first one.
Why does it not work? If Mult and Plus are functions, then I should not need to put their arguments in pattern matching.
'Mult' and 'Plus' are data constructors which both expect one argument: a 'Float'. You also can't match the data constructors against a function, but only against a value of its type. pat :: Foobar -> Bool pat t = case t of Mult f -> True Plus f -> False Greetings, Daniel
participants (3)
-
Daniel Trstenjak
-
Michael Peternell
-
TP