[GHC] #12542: Unexpected failure.. (bug?)
GHC
ghc-devs at haskell.org
Fri Aug 26 10:03:29 UTC 2016
#12542: Unexpected failure.. (bug?)
-------------------------------------+-------------------------------------
Reporter: Iceland_jack | Owner:
Type: bug | Status: new
Priority: normal | Milestone:
Component: Compiler | Version: 8.0.1
Resolution: | Keywords:
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: |
-------------------------------------+-------------------------------------
Comment (by Iceland_jack):
With
{{{#!hs
{-# Language
GADTs,LambdaCase,TypeOperators,ViewPatterns,ScopedTypeVariables#-}
{-# Language TypeApplications #-}
infixr :->
infixl 1 :$
data Full a
data a :-> b
data AST dom sig where
Sym :: dom sig -> AST dom sig
(:$) :: AST dom (a :-> sig) -> AST dom (Full a) -> AST dom sig
class Binding dom where
viewVar :: dom a -> Maybe Integer
viewBnd :: dom (a :-> b) -> Maybe Integer
freeVars :: forall dom a. Binding dom => AST dom a -> [Integer]
freeVars = \case
Sym (a -> Just v) -> [v]
Sym (b -> Just v) :$ body -> undefined
where
(a, b) = (viewVar @dom, undefined)
}}}
it also gives the error
{{{
/tmp/tPYo.hs:20:8: error:
• Couldn't match expected type ‘dom (a1 :-> a) -> Maybe t1’
with actual type ‘t0’
because type variable ‘a1’ would escape its scope
This (rigid, skolem) type variable is bound by
a pattern with constructor:
:$ :: forall (dom :: * -> *) sig a.
AST dom (a :-> sig) -> AST dom (Full a) -> AST dom sig,
in a case alternative
at /tmp/tPYo.hs:20:3-27
• In the pattern: b -> Just v
In the pattern: Sym (b -> Just v)
In the pattern: Sym (b -> Just v) :$ body
• Relevant bindings include
a :: dom a -> Maybe Integer (bound at /tmp/tPYo.hs:23:6)
b :: t0 (bound at /tmp/tPYo.hs:23:9)
freeVars :: AST dom a -> [Integer] (bound at /tmp/tPYo.hs:18:1)
Failed, modules loaded: none.
}}}
--
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/12542#comment:4>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
More information about the ghc-tickets
mailing list