[GHC] #12643: class declaration works in ghci, but not in a file
GHC
ghc-devs at haskell.org
Fri Sep 30 04:31:17 UTC 2016
#12643: class declaration works in ghci, but not in a file
-------------------------------------+-------------------------------------
Reporter: dmwit | Owner:
Type: bug | Status: new
Priority: normal | Milestone:
Component: Compiler | Version: 8.0.1
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:
-------------------------------------+-------------------------------------
The following ghci session prints no errors:
{{{
> :set -XStandaloneDeriving -XDeriveGeneric
> import GHC.Generics
> import Control.Monad.Except
> deriving instance Generic (ExceptT e m a)
> class F a where f :: Rep (Except String a) x
}}}
However, when I transfer this to a file:
{{{
{-# LANGUAGE StandaloneDeriving #-}
{-# LANGUAGE DeriveGeneric #-}
import GHC.Generics
import Control.Monad.Except
deriving instance Generic (ExceptT e m a)
class F a where f :: Rep (Except String a) x
}}}
I get a mysterious error:
{{{
test.hs:6:17: error:
• Couldn't match type ‘Rep (Except String a0)’
with ‘Rep (Except String a)’
Expected type: Rep (Except String a) x
Actual type: Rep (Except String a0) x
NB: ‘Rep’ is a type function, and may not be injective
The type variable ‘a0’ is ambiguous
• In the ambiguity check for ‘f’
To defer the ambiguity check to use sites, enable
AllowAmbiguousTypes
When checking the class method:
f :: forall a. F a => forall x. Rep (Except String a) x
In the class declaration for ‘F’
}}}
If I turn on -fdefer-type-errors, I can verify that the type family indeed
reduces far enough for a and x to be arguments to injective types, so I
believe GHC should not consider this an error:
{{{
> :set -XRankNTypes
> :kind! forall a x. Rep (Except String a) x
forall a x. Rep (Except String a) x :: *
= D1
('MetaData
"ExceptT"
"Control.Monad.Trans.Except"
"transformers-0.5.2.0"
'True)
(C1
('MetaCons "ExceptT" 'PrefixI 'False)
(S1
('MetaSel
'Nothing 'NoSourceUnpackedness 'NoSourceStrictness
'DecidedLazy)
(Rec0 (Data.Functor.Identity.Identity (Either [Char] a)))))
x
}}}
--
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/12643>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
More information about the ghc-tickets
mailing list