
#15893: View Patterns affect typechecking in an unpredictable manner -------------------------------------+------------------------------------- Reporter: theindigamer | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: ⊥ Component: Compiler | Version: 8.4.3 Keywords: ViewPatterns | Operating System: Unknown/Multiple Architecture: | Type of failure: GHC rejects Unknown/Multiple | valid program Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- Copying the text from my [https://stackoverflow.com/questions/53294823 /viewpatterns-affects-typechecking-in-an-unpredictable-manner StackOverflow question]. {{{ {-# LANGUAGE ViewPatterns #-} import Data.Text (Text) import qualified Data.Text as T import qualified Data.Vector.Unboxed as UV import qualified Data.Vector.Generic as V bar :: Int -> UV.Vector Char -> (Text, Text) bar i v = (t_pre, t_post) where f = T.pack . V.toList (f -> t_pre, f -> t_post) = V.splitAt i v }}} This gives an unexpected type error (tested with GHC 8.4.3), concerning ambiguous type variables and `f` being out of scope. {{{ • Ambiguous type variable ‘v0’ arising from a use of ‘V.toList’ prevents the constraint ‘(V.Vector v0 Char)’ from being solved. Relevant bindings include f :: v0 Char -> Text (bound at Weird.hs:11:5) Probable fix: use a type annotation to specify what ‘v0’ should be. These potential instances exist: instance V.Vector UV.Vector Char -- Defined in ‘Data.Vector.Unboxed.Base’ ...plus one instance involving out-of-scope types instance primitive-0.6.3.0:Data.Primitive.Types.Prim a => V.Vector Data.Vector.Primitive.Vector a -- Defined in ‘Data.Vector.Primitive’ • In the second argument of ‘(.)’, namely ‘V.toList’ In the expression: T.pack . V.toList In an equation for ‘f’: f = T.pack . V.toList | 11 | f = T.pack . V.toList | ^^^^^^^^ Weird.hs:13:6: error: Variable not in scope: f :: UV.Vector Char -> t | 13 | (f -> t_pre, f -> t_post) = V.splitAt i v | ^ Weird.hs:13:18: error: Variable not in scope: f :: UV.Vector Char -> t1 | 13 | (f -> t_pre, f -> t_post) = V.splitAt i v | ^ }}} Some of the other answers on SO have done some digging (e.g. enabling FlexibleContexts / NoMonomorphismRestriction doesn't solve the issue). I haven't yet figured out how to minimize the example further to remove the dependency on Vector... Is this a compiler bug or a documentation bug? -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/15893 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler