[GHC] #11401: No match in record selector ctev_dest

#11401: No match in record selector ctev_dest -------------------------------------+------------------------------------- Reporter: Lemming | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1-rc1 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: -------------------------------------+------------------------------------- With the llvm-tf package I got the following problem: {{{ $ cat RecordSelectorCtevDest.hs {-# LANGUAGE TypeFamilies #-} {-# LANGUAGE MultiParamTypeClasses #-} {-# LANGUAGE FlexibleInstances #-} module RecordSelectorCtevDest where import Data.Word (Word32, ) import Foreign.Ptr (Ptr, ) newtype Value a = Value a newtype Function a = Function a newtype CodeGenFunction r a = CodeGenFunction a bind :: CodeGenFunction r a -> (a -> CodeGenFunction r b) -> CodeGenFunction r b bind (CodeGenFunction a) k = k a class (f ~ CalledFunction g, r ~ CallerResult g, g ~ CallerFunction f r) => CallArgs f g r where type CalledFunction g :: * type CallerResult g :: * type CallerFunction f r :: * call :: Function f -> g instance CallArgs (IO a) (CodeGenFunction r (Value a)) r where type CalledFunction (CodeGenFunction r (Value a)) = IO a type CallerResult (CodeGenFunction r (Value a)) = r type CallerFunction (IO a) r = CodeGenFunction r (Value a) call = undefined instance CallArgs b b' r => CallArgs (a -> b) (Value a -> b') r where type CalledFunction (Value a -> b') = a -> CalledFunction b' type CallerResult (Value a -> b') = CallerResult b' type CallerFunction (a -> b) r = Value a -> CallerFunction b r call = undefined test :: Function (IO (Ptr a)) -> Function (Ptr a -> IO Word32) -> CodeGenFunction Word32 (Value Word32) test start fill = bind (call start) (call fill) $ ghci-8.0.0.20160109 RecordSelectorCtevDest.hs GHCi, version 8.0.0.20160109: http://www.haskell.org/ghc/ :? for help [1 of 1] Compiling RecordSelectorCtevDest ( RecordSelectorCtevDest.hs, interpreted ) *** Exception: No match in record selector ctev_dest }}} -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11401 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11401: No match in record selector ctev_dest -------------------------------------+------------------------------------- Reporter: Lemming | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1-rc1 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 "RecordSelectorCtevDest.hs" added. Example module as file -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11401 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11401: No match in record selector ctev_dest -------------------------------------+------------------------------------- Reporter: Lemming | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1-rc1 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: | -------------------------------------+------------------------------------- Description changed by Lemming: Old description:
With the llvm-tf package I got the following problem: {{{ $ cat RecordSelectorCtevDest.hs
{-# LANGUAGE TypeFamilies #-} {-# LANGUAGE MultiParamTypeClasses #-} {-# LANGUAGE FlexibleInstances #-} module RecordSelectorCtevDest where
import Data.Word (Word32, ) import Foreign.Ptr (Ptr, )
newtype Value a = Value a newtype Function a = Function a newtype CodeGenFunction r a = CodeGenFunction a
bind :: CodeGenFunction r a -> (a -> CodeGenFunction r b) -> CodeGenFunction r b bind (CodeGenFunction a) k = k a
class (f ~ CalledFunction g, r ~ CallerResult g, g ~ CallerFunction f r) => CallArgs f g r where type CalledFunction g :: * type CallerResult g :: * type CallerFunction f r :: * call :: Function f -> g
instance CallArgs (IO a) (CodeGenFunction r (Value a)) r where type CalledFunction (CodeGenFunction r (Value a)) = IO a type CallerResult (CodeGenFunction r (Value a)) = r type CallerFunction (IO a) r = CodeGenFunction r (Value a) call = undefined
instance CallArgs b b' r => CallArgs (a -> b) (Value a -> b') r where type CalledFunction (Value a -> b') = a -> CalledFunction b' type CallerResult (Value a -> b') = CallerResult b' type CallerFunction (a -> b) r = Value a -> CallerFunction b r call = undefined
test :: Function (IO (Ptr a)) -> Function (Ptr a -> IO Word32) -> CodeGenFunction Word32 (Value Word32) test start fill = bind (call start) (call fill)
$ ghci-8.0.0.20160109 RecordSelectorCtevDest.hs GHCi, version 8.0.0.20160109: http://www.haskell.org/ghc/ :? for help [1 of 1] Compiling RecordSelectorCtevDest ( RecordSelectorCtevDest.hs, interpreted ) *** Exception: No match in record selector ctev_dest }}}
New description: With the llvm-tf package I got the following problem: {{{ $ cat RecordSelectorCtevDest.hs {-# LANGUAGE TypeFamilies #-} {-# LANGUAGE MultiParamTypeClasses #-} {-# LANGUAGE FlexibleInstances #-} module RecordSelectorCtevDest where newtype Value a = Value a newtype CodeGen r a = CodeGen a bind :: CodeGen r a -> (a -> CodeGen r b) -> CodeGen r b bind (CodeGen a) k = k a class (f ~ CalledFunction g, r ~ CallerResult g, g ~ CallerFunction f r) => CallArgs f g r where type CalledFunction g :: * type CallerResult g :: * type CallerFunction f r :: * call :: f -> g instance CallArgs (IO a) (CodeGen r (Value a)) r where type CalledFunction (CodeGen r (Value a)) = IO a type CallerResult (CodeGen r (Value a)) = r type CallerFunction (IO a) r = CodeGen r (Value a) call = undefined instance CallArgs b b' r => CallArgs (a -> b) (Value a -> b') r where type CalledFunction (Value a -> b') = a -> CalledFunction b' type CallerResult (Value a -> b') = CallerResult b' type CallerFunction (a -> b) r = Value a -> CallerFunction b r call = undefined test :: IO a -> (a -> IO ()) -> CodeGen () (Value ()) test start stop = bind (call start) (call stop) $ ghci-8.0.0.20160109 RecordSelectorCtevDest.hs GHCi, version 8.0.0.20160109: http://www.haskell.org/ghc/ :? for help [1 of 1] Compiling RecordSelectorCtevDest ( RecordSelectorCtevDest.hs, interpreted ) *** Exception: No match in record selector ctev_dest }}} The problem disappears when I remove the 'r' parameter from CodeGen, CallArgs and CallerFunction and remove the CallerResult consequently. -- -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11401#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11401: No match in record selector ctev_dest -------------------------------------+------------------------------------- Reporter: Lemming | Owner: Type: bug | Status: new Priority: highest | Milestone: 8.0.1 Component: Compiler | Version: 8.0.1-rc1 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 thomie): * priority: normal => highest * milestone: => 8.0.1 Comment: Regression from 7.10.3. Assert failure in `shortCutReduction` in `TcInteract.hs` with `devel2` build. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11401#comment:2 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11401: No match in record selector ctev_dest -------------------------------------+------------------------------------- Reporter: Lemming | Owner: Type: bug | Status: new Priority: highest | Milestone: 8.0.1 Component: Compiler | Version: 8.0.1-rc1 Resolution: | Keywords: TypeInType 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 goldfire): * keywords: => TypeInType -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11401#comment:3 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11401: No match in record selector ctev_dest -------------------------------------+------------------------------------- Reporter: Lemming | Owner: goldfire Type: bug | Status: new Priority: highest | Milestone: 8.0.1 Component: Compiler | Version: 8.0.1-rc1 Resolution: | Keywords: TypeInType 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 bgamari): * owner: => goldfire -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11401#comment:4 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11401: No match in record selector ctev_dest -------------------------------------+------------------------------------- Reporter: Lemming | Owner: goldfire Type: bug | Status: new Priority: highest | Milestone: 8.0.1 Component: Compiler | Version: 8.0.1-rc1 Resolution: | Keywords: TypeInType 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 Lemming): With ghc-8.0.0.20160202 I get the same error at a different place. Maybe this allows me to extract a simpler example code. Are you interested? -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11401#comment:5 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11401: No match in record selector ctev_dest -------------------------------------+------------------------------------- Reporter: Lemming | Owner: goldfire Type: bug | Status: new Priority: highest | Milestone: 8.0.1 Component: Compiler | Version: 8.0.1-rc1 Resolution: | Keywords: TypeInType 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 goldfire): Not if it's much trouble. I think this one should be easy to track down. But I have to finish #11471 first, as that's a larger change. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11401#comment:6 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11401: No match in record selector ctev_dest -------------------------------------+------------------------------------- Reporter: Lemming | Owner: goldfire Type: bug | Status: new Priority: highest | Milestone: 8.0.1 Component: Compiler | Version: 8.0.1-rc1 Resolution: | Keywords: TypeInType Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #11523 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by ekmett): * related: => #11523 -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11401#comment:7 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11401: No match in record selector ctev_dest -------------------------------------+------------------------------------- Reporter: Lemming | Owner: goldfire Type: bug | Status: new Priority: highest | Milestone: 8.0.1 Component: Compiler | Version: 8.0.1-rc1 Resolution: | Keywords: TypeInType Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #11523 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by ekmett): * cc: ekmett (added) -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11401#comment:8 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11401: No match in record selector ctev_dest -------------------------------------+------------------------------------- Reporter: Lemming | Owner: goldfire Type: bug | Status: new Priority: highest | Milestone: 8.0.1 Component: Compiler | Version: 8.0.1-rc1 Resolution: | Keywords: TypeInType Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #11523 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by adamgundry): * cc: adamgundry (added) Comment: I've [https://travis-ci.org/adamgundry/uom-plugin/jobs/112312216 run into this as well]. I'm attaching a trivial patch that fixes the bug and corrects a reference to a Note, but I don't know whether Richard's work will conflict with it or if a bigger change is in order. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11401#comment:9 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11401: No match in record selector ctev_dest -------------------------------------+------------------------------------- Reporter: Lemming | Owner: goldfire Type: bug | Status: new Priority: highest | Milestone: 8.0.1 Component: Compiler | Version: 8.0.1-rc1 Resolution: | Keywords: TypeInType Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #11523 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by adamgundry): * Attachment "T11401.patch" added. Patch against HEAD -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11401 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11401: No match in record selector ctev_dest -------------------------------------+------------------------------------- Reporter: Lemming | Owner: goldfire Type: bug | Status: new Priority: highest | Milestone: 8.0.1 Component: Compiler | Version: 8.0.1-rc1 Resolution: | Keywords: TypeInType Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #11523 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by goldfire): I actually have a patch for this locally, but it's queued behind something larger. Thanks for taking a look, though! -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11401#comment:10 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11401: No match in record selector ctev_dest -------------------------------------+------------------------------------- Reporter: Lemming | Owner: goldfire Type: bug | Status: new Priority: highest | Milestone: 8.0.1 Component: Compiler | Version: 8.0.1-rc1 Resolution: | Keywords: TypeInType Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #11523 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by adamgundry): Thanks, I suspected as much which was why I didn't put this on Phab. The patch was mostly to unblock testing one of my projects, and I thought I should stick it here in case it could do the same for anyone else. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11401#comment:11 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11401: No match in record selector ctev_dest
-------------------------------------+-------------------------------------
Reporter: Lemming | Owner: goldfire
Type: bug | Status: new
Priority: highest | Milestone: 8.0.1
Component: Compiler | Version: 8.0.1-rc1
Resolution: | Keywords: TypeInType
Operating System: Unknown/Multiple | Architecture:
| Unknown/Multiple
Type of failure: None/Unknown | Test Case:
Blocked By: | Blocking:
Related Tickets: #11523 | Differential Rev(s):
Wiki Page: |
-------------------------------------+-------------------------------------
Comment (by Richard Eisenberg

#11401: No match in record selector ctev_dest -------------------------------------+------------------------------------- Reporter: Lemming | Owner: goldfire Type: bug | Status: merge Priority: highest | Milestone: 8.0.1 Component: Compiler | Version: 8.0.1-rc1 Resolution: | Keywords: TypeInType Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: | typecheck/should_compile/T11401 Blocked By: | Blocking: Related Tickets: #11523 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by goldfire): * testcase: => typecheck/should_compile/T11401 * status: new => merge -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11401#comment:13 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11401: No match in record selector ctev_dest -------------------------------------+------------------------------------- Reporter: Lemming | Owner: goldfire Type: bug | Status: closed Priority: highest | Milestone: 8.0.1 Component: Compiler | Version: 8.0.1-rc1 Resolution: fixed | Keywords: TypeInType Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: | typecheck/should_compile/T11401 Blocked By: | Blocking: Related Tickets: #11523 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * status: merge => closed * resolution: => fixed Comment: Merged comment:12 as e0ca94e3111349c0cef96a20950bdc591e586548. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11401#comment:14 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
participants (1)
-
GHC