[GHC] #14763: GHC 8.4.1-alpha regression with FunctionalDependencies
GHC
ghc-devs at haskell.org
Mon Feb 5 19:56:53 UTC 2018
#14763: GHC 8.4.1-alpha regression with FunctionalDependencies
-------------------------------------+-------------------------------------
Reporter: RyanGlScott | Owner: (none)
Type: bug | Status: new
Priority: highest | Milestone: 8.4.1
Component: Compiler | Version: 8.4.1-alpha3
(Type checker) |
Keywords: FunDeps | Operating System: Unknown/Multiple
Architecture: | Type of failure: GHC rejects
Unknown/Multiple | valid program
Test Case: | Blocked By:
Blocking: | Related Tickets:
Differential Rev(s): | Wiki Page:
-------------------------------------+-------------------------------------
This regression prevents `esqeueleto-2.5.3` from building with GHC 8.4.1.
Here is a minimized example of the problem:
{{{#!hs
{-# LANGUAGE FunctionalDependencies #-}
{-# LANGUAGE GADTs #-}
{-# LANGUAGE KindSignatures #-}
{-# LANGUAGE MultiParamTypeClasses #-}
module Bug where
data Value a = Value a
data SomeValue expr where
SomeValue :: Esqueleto query expr backend => expr (Value a) -> SomeValue
expr
class Esqueleto (query :: * -> *) (expr :: * -> *) backend
| query -> expr backend, expr -> query backend
data SqlQuery a
data SqlBackend
data SqlExpr a where
ECompositeKey :: SqlExpr (Value a)
instance Esqueleto SqlQuery SqlExpr SqlBackend
match' :: SomeValue SqlExpr -> a
match' (SomeValue ECompositeKey) = undefined
}}}
On GHC 8.2.2, this typechecks without issue. On GHC 8.4.1-alpha (version
8.4.0.20180204), this fails with:
{{{
$ /opt/ghc/8.4.1/bin/ghci Bug.hs
GHCi, version 8.4.0.20180204: http://www.haskell.org/ghc/ :? for help
Loaded GHCi configuration from /home/rgscott/.ghci
[1 of 1] Compiling Bug ( Bug.hs, interpreted )
Bug.hs:25:19: error:
• Could not deduce: query ~ SqlQuery
arising from a functional dependency between:
constraint ‘Esqueleto query SqlExpr backend’
arising from a pattern with constructor:
SomeValue :: forall (query :: * -> *) (expr ::
* -> *) backend a.
Esqueleto query expr backend =>
expr (Value a) -> SomeValue expr,
in an equation for ‘match'’
instance ‘Esqueleto SqlQuery SqlExpr SqlBackend’ at
Bug.hs:22:10-46
from the context: Value a1 ~ Value a2
bound by a pattern with constructor:
ECompositeKey :: forall a. SqlExpr (Value a),
in an equation for ‘match'’
at Bug.hs:25:19-31
‘query’ is a rigid type variable bound by
a pattern with constructor:
SomeValue :: forall (query :: * -> *) (expr :: * -> *) backend
a.
Esqueleto query expr backend =>
expr (Value a) -> SomeValue expr,
in an equation for ‘match'’
at Bug.hs:25:9-31
Inaccessible code in
a pattern with constructor:
ECompositeKey :: forall a. SqlExpr (Value a),
in an equation for ‘match'’
• In the pattern: ECompositeKey
In the pattern: SomeValue ECompositeKey
In an equation for ‘match'’:
match' (SomeValue ECompositeKey) = undefined
|
25 | match' (SomeValue ECompositeKey) = undefined
| ^^^^^^^^^^^^^
}}}
--
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/14763>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
More information about the ghc-tickets
mailing list