[GHC] #16323: Cannot deduce X error with X provided

GHC ghc-devs at haskell.org
Fri Feb 15 08:53:01 UTC 2019


#16323: Cannot deduce X error with X provided
----------------------------------------+---------------------------------
           Reporter:  pjljvdlaar        |             Owner:  (none)
               Type:  bug               |            Status:  new
           Priority:  normal            |         Milestone:
          Component:  Compiler          |           Version:  8.2.2
           Keywords:                    |  Operating System:  Windows
       Architecture:  Unknown/Multiple  |   Type of failure:  None/Unknown
          Test Case:                    |        Blocked By:
           Blocking:                    |   Related Tickets:
Differential Rev(s):                    |         Wiki Page:
----------------------------------------+---------------------------------
 The following code
 {{{#!hs
 {-# LANGUAGE FlexibleContexts      #-}
 {-# LANGUAGE TypeFamilies          #-}
 module TorXakis.Test
 ( -- * Referable
   Referable(..)
 )
 where
 import           Data.Hashable
 import qualified Data.HashMap         as HashMap

 -- | A referable class
 class Referable a where
     type Ref a
     toRef :: a -> Ref a

 -- | Map of Referable objects.
 data (Referable a, Ord (Ref a), Hashable (Ref a)) =>
             RefMap a = RefMap { -- | the HashMap
                                 toHashMap :: HashMap.Map (Ref a) a
                               } deriving (Eq, Ord, Show, Read)
 }}}
 gives the following errors
 {{{
 C:\TorXakis\sys\txs-basics\src\TorXakis\Test.hs:20:43: error:
     * Could not deduce (Ord (Ref a))
         arising from the 'deriving' clause of a data type declaration
       from the context: (Eq a, Referable a)
         bound by the deriving clause for `Eq (RefMap a)'
         at src\TorXakis\Test.hs:20:43-44
       Possible fix:
         use a standalone 'deriving instance' declaration,
           so you can specify the instance context yourself
     * When deriving the instance for (Eq (RefMap a))
    |
 20 |                               } deriving (Eq, Ord, Show, Read)
    |                                           ^^

 C:\TorXakis\sys\txs-basics\src\TorXakis\Test.hs:20:47: error:
     * Could not deduce (Hashable (Ref a))
         arising from the 'deriving' clause of a data type declaration
       from the context: (Ord a, Referable a)
         bound by the deriving clause for `Ord (RefMap a)'
         at src\TorXakis\Test.hs:20:47-49
       Possible fix:
         use a standalone 'deriving instance' declaration,
           so you can specify the instance context yourself
     * When deriving the instance for (Ord (RefMap a))
    |
 20 |                               } deriving (Eq, Ord, Show, Read)
    |                                               ^^^

 C:\TorXakis\sys\txs-basics\src\TorXakis\Test.hs:20:52: error:
     * Could not deduce (Ord (Ref a))
         arising from the 'deriving' clause of a data type declaration
       from the context: (Show a, Referable a)
         bound by the deriving clause for `Show (RefMap a)'
         at src\TorXakis\Test.hs:20:52-55
       Possible fix:
         use a standalone 'deriving instance' declaration,
           so you can specify the instance context yourself
     * When deriving the instance for (Show (RefMap a))
    |
 20 |                               } deriving (Eq, Ord, Show, Read)
    |                                                    ^^^^

 C:\TorXakis\sys\txs-basics\src\TorXakis\Test.hs:20:58: error:
     * Could not deduce (Ord (Ref a))
         arising from the 'deriving' clause of a data type declaration
       from the context: (Read a, Referable a)
         bound by the deriving clause for `Read (RefMap a)'
         at src\TorXakis\Test.hs:20:58-61
       Possible fix:
         use a standalone 'deriving instance' declaration,
           so you can specify the instance context yourself
     * When deriving the instance for (Read (RefMap a))
    |
 20 |                               } deriving (Eq, Ord, Show, Read)
    |                                                          ^^^^

 --  While building package txs-basics-0.1.0.0 using:
       C:\sr\setup-exe-cache\x86_64-windows-integersimple\Cabal-
 simple_Z6RU0evB_2.0.1.0_ghc-8.2.2.exe --builddir=.stack-w
 ork\dist\67675594 build lib:txs-basics --ghc-options " -ddump-hi -ddump-
 to-file"
     Process exited with code: ExitFailure 1
 }}}

 yet the requirements such as {{{Ord (Ref a)}}} are clearly given to the
 data definition!

 possibly related to #16319

-- 
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/16323>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler


More information about the ghc-tickets mailing list