#7354: Panic with recursion-schemes package and unit
------------------------+---------------------------------------------------
 Reporter:  amplitwist  |          Owner:                
     Type:  bug         |         Status:  new           
 Priority:  normal      |      Component:  GHCi          
  Version:  7.6.1       |       Keywords:                
       Os:  Linux       |   Architecture:  x86_64 (amd64)
  Failure:  GHCi crash  |       Testcase:                
Blockedby:              |       Blocking:                
  Related:              |  
------------------------+---------------------------------------------------

Comment(by amplitwist):

 Here's another test case.

 {{{
 {-# LANGUAGE CPP, TypeFamilies, Rank2Types, FlexibleContexts,
 FlexibleInstances, GADTs, StandaloneDeriving, UndecidableInstances #-}

 module Main where

 type family Base t :: * -> *
 data family Prim t :: * -> *

 class Functor (Base t) => Unfoldable t where
   embed :: Base t t -> t
   ana
     :: (a -> Base t a) -- ^ a (Base t)-coalgebra
     -> a               -- ^ seed
     -> t               -- ^ resulting fixed point
   ana g = a where a = embed . fmap a . g


 data instance Prim [a] b = Cons a b | Nil deriving (Eq,Ord,Show,Read)

 coalg 0 = Nil
 coalg n = Cons n (n-1)
 alg Nil = 1
 alg (Cons a b) = a * b

 instance Functor (Prim [a]) where
   fmap f (Cons a b) = Cons a (f b)
   fmap _ Nil = Nil
 }}}

 Load into GHCI, and evaluate:
 {{{
 *Main> ana alg
 ghc: panic! (the 'impossible' happened)
   (GHC version 7.6.1 for x86_64-unknown-linux):
         nameModule
 <<details unavailable>>

 Please report this as a GHC bug:  http://www.haskell.org/ghc/reportabug
 }}}

-- 
Ticket URL: <http://hackage.haskell.org/trac/ghc/ticket/7354#comment:2>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler

_______________________________________________
Glasgow-haskell-bugs mailing list
Glasgow-haskell-bugs@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs

Reply via email to