[GHC] #15346: Core Lint error in GHC 8.6.1: From-type of Cast differs from type of enclosed expression
GHC
ghc-devs at haskell.org
Thu Jul 5 23:27:07 UTC 2018
#15346: Core Lint error in GHC 8.6.1: From-type of Cast differs from type of
enclosed expression
-------------------------------------+-------------------------------------
Reporter: RyanGlScott | Owner: (none)
Type: bug | Status: new
Priority: normal | Milestone: 8.6.1
Component: Compiler (Type | Version: 8.5
checker) |
Resolution: | Keywords: TypeInType
Operating System: Unknown/Multiple | Architecture:
Type of failure: Compile-time | Unknown/Multiple
crash or panic | Test Case:
Blocked By: | Blocking:
Related Tickets: | Differential Rev(s):
Wiki Page: |
-------------------------------------+-------------------------------------
Comment (by monoidal):
Here's a smaller version:
{{{
#!hs
{-# LANGUAGE AllowAmbiguousTypes #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE TypeInType #-}
{-# LANGUAGE TypeApplications #-}
module SGenerics where
import Data.Kind
import Data.Proxy
-----
type family Rep (a :: Type) :: Type
type instance Rep () = ()
type family PFrom (x :: a) :: Rep a
-----
class SDecide k where
test :: forall (a :: k). Proxy a
instance SDecide () where
test = undefined
test1 :: forall (a :: k). SDecide (Rep k) => Proxy a
test1 = seq (test @_ @(PFrom a)) Proxy
test2 :: forall (a :: ()). Proxy a
test2 = test1
}}}
--
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/15346#comment:2>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
More information about the ghc-tickets
mailing list