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

GHC ghc-devs at haskell.org
Sun Jan 10 20:14:10 UTC 2016


#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


More information about the ghc-tickets mailing list