[GHC] #11397: Type mismatch in local definitions in Haskell 98 code

#11397: Type mismatch in local definitions in Haskell 98 code -------------------------------------+------------------------------------- Reporter: Lemming | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1-rc1 (Type checker) | Keywords: | Operating System: Unknown/Multiple Architecture: | Type of failure: None/Unknown Unknown/Multiple | Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- Here is the affected code with all package dependencies removes: {{{ $ cat PairMismatch.hs module PairMismatch (inverseFrequencyModulationChunk) where newtype VectorLazy a = VectorLazy a newtype Vector a = Vector a newtype Pointer a = Pointer a empty :: VectorLazy a empty = undefined cons :: Vector a -> Pointer a cons = undefined unfoldrResult :: (a -> Either c (b, a)) -> a -> (VectorLazy b, c) unfoldrResult = undefined switchL :: b -> (a -> Pointer a -> b) -> Pointer a -> b switchL = undefined inverseFrequencyModulationChunk :: (Num t, Ord t) => (s -> Maybe (t,s)) -> (t,s) -> Vector v -> (VectorLazy v, Maybe (t,s)) inverseFrequencyModulationChunk nextC (phase,cst0) chunk = let {- switch :: (Maybe (t, s) -> r) -> ((t, v) -> (s, Pointer v) -> r) -> t -> (s, Pointer v) -> r -} switch l r t (cp0,xp0) = maybe (l Nothing) (\(c1,cp1) -> switchL (l (Just (t,cp0))) (\x1 xp1 -> r (t+c1,x1) (cp1,xp1)) xp0) (nextC cp0) {- go :: (t,v) -> (s, Pointer v) -> Either (Maybe (t,s)) (v, ((t,v), (s, Pointer v))) -} go (c,x) cxp = if c<1 then switch Left go c cxp else Right (x, ((c-1,x),cxp)) in switch ((,) empty) (curry $ unfoldrResult (uncurry go)) phase (cst0, cons chunk) $ ghci-8.0.0.20160109 PairMismatch.hs GHCi, version 8.0.0.20160109: http://www.haskell.org/ghc/ :? for help [1 of 1] Compiling PairMismatch ( PairMismatch.hs, interpreted ) PairMismatch.hs:35:24: error: • Couldn't match type ‘a’ with ‘(t, s)’ ‘a’ is a rigid type variable bound by a type expected by the context: forall a. Maybe a at PairMismatch.hs:35:24 Expected type: forall a. Maybe a Actual type: Maybe (t, s) • In the first argument of ‘l’, namely ‘(Just (t, cp0))’ In the first argument of ‘switchL’, namely ‘(l (Just (t, cp0)))’ In the expression: switchL (l (Just (t, cp0))) (\ x1 xp1 -> r (t + c1, x1) (cp1, xp1)) xp0 • Relevant bindings include cp1 :: s (bound at PairMismatch.hs:33:20) c1 :: t (bound at PairMismatch.hs:33:17) cp0 :: s (bound at PairMismatch.hs:30:22) t :: t (bound at PairMismatch.hs:30:19) r :: (t, t1) -> (s, Pointer t1) -> b (bound at PairMismatch.hs:30:17) switch :: ((forall a. Maybe a) -> b) -> ((t, t1) -> (s, Pointer t1) -> b) -> t -> (s, Pointer t1) -> b (bound at PairMismatch.hs:30:8) inverseFrequencyModulationChunk :: (s -> Maybe (t, s)) -> (t, s) -> Vector v -> (VectorLazy v, Maybe (t, s)) (bound at PairMismatch.hs:22:1) (Some bindings suppressed; use -fmax-relevant-binds=N or -fno-max- relevant-binds) Failed, modules loaded: none. }}} It works with GHC-7.10.3 and before. I may try to further simplify the code and choose a better ticket header, if I got an idea what went wrong. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11397 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11397: Type mismatch in local definitions in Haskell 98 code -------------------------------------+------------------------------------- Reporter: Lemming | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler (Type | Version: 8.0.1-rc1 checker) | Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by Lemming): * Attachment "PairMismatch.hs" added. Offending module as a separate file -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11397 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11397: Type mismatch in local definitions in Haskell 98 code -------------------------------------+------------------------------------- Reporter: Lemming | Owner: Type: bug | Status: new Priority: highest | Milestone: 8.0.1 Component: Compiler (Type | Version: 8.0.1-rc1 checker) | Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by rwbarton): * priority: normal => highest * milestone: => 8.0.1 Comment: Setting as release blocker since it is a change in behavior in a supposedly Haskell 2010 program. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11397#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11397: Type mismatch in local definitions in Haskell 98 code -------------------------------------+------------------------------------- Reporter: Lemming | Owner: Type: bug | Status: new Priority: highest | Milestone: 8.0.1 Component: Compiler (Type | Version: 8.0.1-rc1 checker) | Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by monoidal): Smaller example: {{{ module PairMismatch (f) where f :: a -> [Maybe a] f x = let switch l = [l Nothing, l (Just x)] in switch id }}} While investigating this, I found two more programs that compile with GHC 7.10 but fail with HEAD, I'm not sure if the cause is the same or different. {{{ module PairMismatch2 (f) where u :: a u = u f :: a f = let switch l = l u in switch u }}} {{{ module PairMismatch3 (f) where f :: a f = let switch l = l undefined in switch undefined }}} -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11397#comment:2 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11397: Type mismatch in local definitions in Haskell 98 code -------------------------------------+------------------------------------- Reporter: Lemming | Owner: goldfire Type: bug | Status: new Priority: highest | Milestone: 8.0.1 Component: Compiler (Type | Version: 8.0.1-rc1 checker) | Keywords: Resolution: | TypeApplicaitons Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by simonpj): * keywords: => TypeApplicaitons * owner: => goldfire Comment: Thanks for the examples. I think they are artefacts of `TypeApplications`, and the "return-tv" plumbing. Richard and I have a plan for this, which he is going to execute shortly -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11397#comment:3 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11397: Type mismatch in local definitions in Haskell 98 code -------------------------------------+------------------------------------- Reporter: Lemming | Owner: goldfire Type: bug | Status: new Priority: highest | Milestone: 8.0.1 Component: Compiler (Type | Version: 8.0.1-rc1 checker) | Keywords: Resolution: | TypeApplications Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by simonpj): * keywords: TypeApplicaitons => TypeApplications -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11397#comment:4 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11397: Type mismatch in local definitions in Haskell 98 code
-------------------------------------+-------------------------------------
Reporter: Lemming | Owner: goldfire
Type: bug | Status: new
Priority: highest | Milestone: 8.0.1
Component: Compiler (Type | Version: 8.0.1-rc1
checker) | Keywords:
Resolution: | TypeApplications
Operating System: Unknown/Multiple | Architecture:
| Unknown/Multiple
Type of failure: None/Unknown | Test Case:
Blocked By: | Blocking:
Related Tickets: | Differential Rev(s):
Wiki Page: |
-------------------------------------+-------------------------------------
Comment (by Richard Eisenberg

#11397: Type mismatch in local definitions in Haskell 98 code -------------------------------------+------------------------------------- Reporter: Lemming | Owner: goldfire Type: bug | Status: merge Priority: highest | Milestone: 8.0.1 Component: Compiler (Type | Version: 8.0.1-rc1 checker) | Keywords: Resolution: | TypeApplications Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: | typecheck/should_compiler/T11397 Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by goldfire): * testcase: => typecheck/should_compiler/T11397 * status: new => merge -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11397#comment:6 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11397: Type mismatch in local definitions in Haskell 98 code -------------------------------------+------------------------------------- Reporter: Lemming | Owner: goldfire Type: bug | Status: closed Priority: highest | Milestone: 8.0.1 Component: Compiler (Type | Version: 8.0.1-rc1 checker) | Keywords: Resolution: fixed | TypeApplications Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: | typecheck/should_compiler/T11397 Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * status: merge => closed * resolution: => fixed Comment: This was merged in 278e1fa2fd7b33254e323d394706e72f4664ad02. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11397#comment:7 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
participants (1)
-
GHC