[GHC] #10134: Pattern Matching Causes Infinite Type Error
GHC
ghc-devs at haskell.org
Wed Mar 4 13:43:46 UTC 2015
#10134: Pattern Matching Causes Infinite Type Error
-------------------------------------+-------------------------------------
Reporter: dongen | Owner:
Type: bug | Status: new
Priority: normal | Milestone:
Component: Compiler | Version: 7.8.4
Resolution: | Keywords:
Operating System: Unknown/Multiple | Architecture:
Type of failure: None/Unknown | Unknown/Multiple
Blocked By: | Test Case:
Related Tickets: | Blocking:
| Differential Revisions:
-------------------------------------+-------------------------------------
Comment (by dongen):
OK Here's the simplest example. The problem goes away if you don't use
@Positive (2*(n+d))@ but just @Positive (n+d)@.
{{{
> module Dummy( Dummy ) where
> import CLaSH.Prelude
> type Positive n
> = ( KnownNat n
> , KnownNat (n-1)
> , ((n-1)+1)~n
> )
> data Dummy n d = Dummy
> { vec :: Vec n (Vec d Bool)
> } deriving Show
> nextDummy
> :: ( KnownNat n
> , KnownNat d
> , Positive (2*(n+d))
> )
> => Dummy n d -> Dummy n d
> nextDummy d
> = Dummy { vec = vec dFst }
> where -- d2' = nextDummy' d
> -- dFst = fst d2'
> -- dSnd = snd d2'
> (dFst,dSnd) = nextDummy' d
> nextDummy'
> :: ( KnownNat n
> , KnownNat d
> , Positive (2*(n+d))
> )
> => Dummy n d
> -> ( Dummy n d, Bool )
> nextDummy' _ = error []
}}}
--
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/10134#comment:7>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
More information about the ghc-tickets
mailing list