[GHC] #13601: GHC errors but hangs
GHC
ghc-devs at haskell.org
Fri Apr 21 10:25:50 UTC 2017
#13601: GHC errors but hangs
-------------------------------------+-------------------------------------
Reporter: Iceland_jack | Owner: (none)
Type: bug | Status: new
Priority: normal | Milestone:
Component: Compiler | Version: 8.0.1
Keywords: | Operating System: Unknown/Multiple
Architecture: | Type of failure: None/Unknown
Unknown/Multiple |
Test Case: | Blocked By:
Blocking: | Related Tickets:
Differential Rev(s): | Wiki Page:
-------------------------------------+-------------------------------------
{{{#!hs
{-# LANGUAGE TypeFamilies, DataKinds, TypeInType #-}
import GHC.Exts
import Prelude (Bool(True,False),Integer,Ordering,undefined)
import qualified Prelude
import Data.Kind
--------------------
-- class hierarchy
type family
Rep (rep :: RuntimeRep) :: RuntimeRep where
-- Rep IntRep = IntRep
-- Rep DoubleRep = IntRep
-- Rep PtrRepUnlifted = IntRep
-- Rep PtrRepLifted = PtrRepLifted
class Boolean (Logic a) => Eq (a :: TYPE rep) where
type Logic (a :: TYPE rep) :: TYPE (Rep rep)
(==) :: a -> a -> Logic a
class Eq a => POrd (a :: TYPE rep) where
inf :: a -> a -> a
class POrd a => MinBound (a :: TYPE rep) where
minBound :: () -> a
class POrd a => Lattice (a :: TYPE rep) where
sup :: a -> a -> a
class (Lattice a, MinBound a) => Bounded (a :: TYPE rep) where
maxBound :: () -> a
class Bounded a => Complemented (a :: TYPE rep) where
not :: a -> a
class Bounded a => Heyting (a :: TYPE rep) where
infixr 3 ==>
(==>) :: a -> a -> a
class (Complemented a, Heyting a) => Boolean a
(||) :: Boolean a => a -> a -> a
(||) = sup
(&&) :: Boolean a => a -> a -> a
(&&) = inf
}}}
hangs with
{{{
$ ghci a.hs
GHCi, version 8.0.1: http://www.haskell.org/ghc/ :? for help
[1 of 1] Compiling Main ( a.hs, interpreted )
a.hs:18:16: error: C-c C-cInterrupted.
}}}
--
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/13601>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
More information about the ghc-tickets
mailing list