#3667: Overly specific type inference.
------------------------------+---------------------------------------------
Reporter: Sean Erle Johnson | Owner:
Type: bug | Status: new
Priority: normal | Component: Compiler
Version: 6.10.4 | Severity: normal
Keywords: | Testcase:
Os: Unknown/Multiple | Architecture: Unknown/Multiple
------------------------------+---------------------------------------------
The inferred type for perms in the following code is too specific:
{{{
import Data.List
main = print $ perms 4 [1..4]
test = perms 4 ['1'..'4']
perms = combBase delete
combBase :: (a -> [a] -> [a]) -> Int -> [a] -> [[a]]
combBase next = worker
where worker 0 _ = [[]]
worker _ [] = [[]]
worker l xs = concatMap (\x -> map (x:) (worker (l-1) (next x
xs))) xs
}}}
Compiling with ghc (with the --make switch) yields:
{{{
TypeInferenceBug.hs:3:24:
No instance for (Num Char)
arising from the literal `1' at TypeInferenceBug.hs:3:24
Possible fix: add an instance declaration for (Num Char)
In the expression: 1
In the second argument of `perms', namely `[1 .. 4]'
In the second argument of `($)', namely `perms 4 ([1 .. 4])'
}}}
Typing ":t perms" into ghci gives the following signature (after the main
function is commented out):
{{{
perms :: Int -> [Char] -> [[Char]]
}}}
Compiling occurs without complaint when perms is given the explicit (and
more general) type signature and ghci reports the correct type signature:
{{{
perms :: Eq a => Int -> [a] -> [[a]]
perms = combBase delete
}}}
The type is correctly inferred for combBase regardless of if it has an
explicit type signature or not.
I tested this on Windows but not on Linux yet, though I suspect that this
problem is architecture-independent.
--
Ticket URL: <http://hackage.haskell.org/trac/ghc/ticket/3667>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler_______________________________________________
Glasgow-haskell-bugs mailing list
[email protected]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs