[GHC] #14515: "Same" higher-rank kind synonyms behave differently
GHC
ghc-devs at haskell.org
Thu Nov 23 14:48:28 UTC 2017
#14515: "Same" higher-rank kind synonyms behave differently
-------------------------------------+-------------------------------------
Reporter: Iceland_jack | Owner: (none)
Type: bug | Status: new
Priority: normal | Milestone:
Component: Compiler (Type | Version: 8.2.1
checker) |
Resolution: | Keywords: TypeInType
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: |
-------------------------------------+-------------------------------------
Changes (by RyanGlScott):
* keywords: => TypeInType
* failure: None/Unknown => GHC rejects valid program
* component: Compiler => Compiler (Type checker)
Comment:
For the sake of convenience, here's all of the various combinations in one
file:
{{{#!hs
{-# LANGUAGE GADTs #-}
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE TypeInType #-}
module Bug where
import Data.Kind
type HRank1 ty = forall k1. k1 -> ty
type HRank2 ty = forall k2. k2 -> ty
data HREFL11 :: HRank1 (HRank1 Type) where
HREFL11 :: HREFL11 a a
data HREFL12 :: HRank1 (HRank2 Type) where
HREFL12 :: HREFL12 a a
data HREFL21 :: HRank2 (HRank1 Type) where
HREFL21 :: HREFL21 a a
data HREFL22 :: HRank2 (HRank2 Type) where
HREFL22 :: HREFL22 a a
}}}
--
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/14515#comment:1>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
More information about the ghc-tickets
mailing list