[GHC] #13735: RankNTypes don't work with PatternSynonyms
GHC
ghc-devs at haskell.org
Sun May 21 14:33:37 UTC 2017
#13735: RankNTypes don't work with PatternSynonyms
-------------------------------------+-------------------------------------
Reporter: Iceland_jack | Owner: (none)
Type: bug | Status: new
Priority: normal | Milestone:
Component: Compiler | Version: 8.0.1
Resolution: | Keywords:
| PatternSynonyms
Operating System: Unknown/Multiple | Architecture:
| Unknown/Multiple
Type of failure: None/Unknown | Test Case:
Blocked By: | Blocking:
Related Tickets: | Differential Rev(s):
Wiki Page: |
-------------------------------------+-------------------------------------
Comment (by RyanGlScott):
Another infelicity of the interaction between `PatternSynonyms` and
`RankNTypes` is that this unidirectional version typechecks:
{{{#!hs
{-# LANGUAGE PatternSynonyms #-}
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE ScopedTypeVariables #-}
module Bug where
data PLambda a = Var a | Int Int | Bool Bool | If (PLambda a) (PLambda a)
(PLambda a)
| Add (PLambda a) (PLambda a) | Mult (PLambda a) (PLambda a)
| Eq (PLambda a) (PLambda a) | Lam (a -> PLambda a)
| App (PLambda a) (PLambda a)
newtype Lam = L { un :: forall a. PLambda a }
pattern LLam a <- L (Lam a)
}}}
And this is what GHCi says about the inferred type of `LLam`:
{{{
GHCi, version 8.3.20170516: http://www.haskell.org/ghc/ :? for help
Loaded GHCi configuration from /home/rgscott/.ghci
[1 of 1] Compiling Bug ( Bug.hs, interpreted )
Ok, modules loaded: Bug.
λ> :i LLam
pattern LLam :: (a -> PLambda a) -> Lam -- Defined at Bug.hs:13:1
}}}
But this does not work in an expression context:
{{{#!hs
{-# LANGUAGE PatternSynonyms #-}
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE ScopedTypeVariables #-}
module Bug where
data PLambda a = Var a | Int Int | Bool Bool | If (PLambda a) (PLambda a)
(PLambda a)
| Add (PLambda a) (PLambda a) | Mult (PLambda a) (PLambda a)
| Eq (PLambda a) (PLambda a) | Lam (a -> PLambda a)
| App (PLambda a) (PLambda a)
newtype Lam = L { un :: forall a. PLambda a }
llam f = L (Lam f)
}}}
{{{
GHCi, version 8.3.20170516: http://www.haskell.org/ghc/ :? for help
Loaded GHCi configuration from /home/rgscott/.ghci
[1 of 1] Compiling Bug ( Bug.hs, interpreted )
Bug.hs:13:17: error:
• Couldn't match expected type ‘a -> PLambda a’
with actual type ‘p’
because type variable ‘a’ would escape its scope
This (rigid, skolem) type variable is bound by
a type expected by the context:
forall a. PLambda a
at Bug.hs:13:10-18
• In the first argument of ‘Lam’, namely ‘f’
In the first argument of ‘L’, namely ‘(Lam f)’
In the expression: L (Lam f)
• Relevant bindings include
f :: p (bound at Bug.hs:13:6)
llam :: p -> Lam (bound at Bug.hs:13:1)
|
13 | llam f = L (Lam f)
| ^
}}}
--
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/13735#comment:1>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
More information about the ghc-tickets
mailing list