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

GHC ghc-devs at haskell.org
Sun Jan 10 19:56:16 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
           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


More information about the ghc-tickets mailing list