[GHC] #8422: type nats solver is too weak!
GHC
ghc-devs at haskell.org
Sat Jan 23 12:28:55 UTC 2016
#8422: type nats solver is too weak!
-------------------------------------+-------------------------------------
Reporter: carter | Owner:
Type: bug | Status: new
Priority: normal | Milestone: 8.0.1
Component: Compiler (Type | Version: 7.7
checker) |
Resolution: | Keywords: TypeLits
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 thomie):
* keywords: => TypeLits
@@ -5,0 +5,24 @@
+
+ {{{#!hs
+ {-# LANGUAGE DataKinds #-}
+ {-# LANGUAGE GADTs #-}
+ {-# LANGUAGE KindSignatures #-}
+ {-# LANGUAGE TypeOperators #-}
+ module Fancy where
+
+ import GHC.TypeLits
+
+ infixr 3 :*
+
+ data Shape (rank :: Nat) where
+ Nil :: Shape 0
+ (:*) :: {-# UNPACK #-} !(Int :: *) -> !(Shape r) -> Shape (1 + r)
+
+ reverseShape :: Shape r -> Shape r
+ reverseShape Nil = Nil
+ reverseShape shs = go shs Nil
+ where
+ go :: Shape a -> Shape b -> Shape (a+b)
+ go Nil res = res
+ go (ix :* more ) res = go more (ix :* res)
+ }}}
New description:
I just built ghc HEAD today, and the type nat solver can't handle the
attached program, which *should* be simple to check! (and while I could
use unsafeCoerce to "prove" it correct, that defeats the purpose of having
the type nat solver!)
{{{#!hs
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE GADTs #-}
{-# LANGUAGE KindSignatures #-}
{-# LANGUAGE TypeOperators #-}
module Fancy where
import GHC.TypeLits
infixr 3 :*
data Shape (rank :: Nat) where
Nil :: Shape 0
(:*) :: {-# UNPACK #-} !(Int :: *) -> !(Shape r) -> Shape (1 + r)
reverseShape :: Shape r -> Shape r
reverseShape Nil = Nil
reverseShape shs = go shs Nil
where
go :: Shape a -> Shape b -> Shape (a+b)
go Nil res = res
go (ix :* more ) res = go more (ix :* res)
}}}
--
--
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/8422#comment:6>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
More information about the ghc-tickets
mailing list