Compile error regression from GHC 7.10 to 7.11
Consider the following program,
{-# LANGUAGE OverloadedStrings #-}
-- {-# LANGUAGE FlexibleContexts #-}
chunksOf :: Int -> String -> [String]
chunksOf n = go
where
-- go :: String -> [String]
go "" = []
go s@(_:_) = a : go b
where
(a,b) = splitAt n s
when compiled with GHC 7.8.4:
GHCi, version 7.8.4: http://www.haskell.org/ghc/ :? for help
Loading package ghc-prim ... linking ... done.
Loading package integer-gmp ... linking ... done.
Loading package base ... linking ... done.
[1 of 1] Compiling Main ( chunksof.hs, interpreted )
chunksof.hs:8:5: Warning:
Pattern match(es) are overlapped
In an equation for ‘go’: go s@(_ : _) = ...
Ok, modules loaded: Main.
λ:2>
when compiled with GHC 7.10:
GHCi, version 7.10.1.20150630: http://www.haskell.org/ghc/ :? for help
[1 of 1] Compiling Main ( chunksof.hs, interpreted )
chunksof.hs:8:5:
Non type-variable argument in the constraint: Data.String.IsString [t]
(Use FlexibleContexts to permit this)
When checking that ‘go’ has the inferred type
go :: forall t. (Eq t, Data.String.IsString [t]) => [t] -> [[t]]
In an equation for ‘chunksOf’:
chunksOf n
= go
where
go "" = []
go s@(_ : _)
= a : go b
where
(a, b) = splitAt n s
Failed, modules loaded: none.
NB: FlexibleContexts
is rightly suggested!
However, when compiled with GHC HEAD:
GHCi, version 7.11.20150630: http://www.haskell.org/ghc/ :? for help
[1 of 1] Compiling Main ( chunksof.hs, interpreted )
chunksof.hs:8:8: error:
Could not deduce (IsString [t]) arising from the literal ‘""’
from the context: Eq t bound by the inferred type of go :: Eq t => [t] -> [[t]] at chunksof.hs:(8,5)-(11,27)
In the pattern: ""
In an equation for ‘go’: go "" = []
In an equation for ‘chunksOf’:
chunksOf n
= go
where
go "" = []
go s@(_ : _)
= a : go b
where
(a, b) = splitAt n s
Failed, modules loaded: none.
Trac metadata
Trac field | Value |
---|---|
Version | 7.11 |
Type | Bug |
TypeOfFailure | OtherFailure |
Priority | normal |
Resolution | Unresolved |
Component | Compiler |
Test case | |
Differential revisions | |
BlockedBy | |
Related | |
Blocking | |
CC | |
Operating system | |
Architecture |