#1808: type families: impossible happened, at runtime in GHCi
-----------------------+----------------------------------------------------
  Reporter:  guest     |          Owner:       
      Type:  bug       |         Status:  new  
  Priority:  normal    |      Milestone:       
 Component:  Compiler  |        Version:  6.8  
  Severity:  normal    |       Keywords:       
Difficulty:  Unknown   |             Os:  Linux
  Testcase:            |   Architecture:  x86  
-----------------------+----------------------------------------------------
 in the following module:

 {{{
 {-# LANGUAGE TypeFamilies #-}

 module Bug where

 import Prelude hiding (foldr, null)
 import qualified Prelude (foldr, null)
 import Data.Monoid

 type family Elem a :: *

 class Foldable t where
         fold :: (Monoid a, a ~ (Elem t)) => t -> Elem t
         fold = foldMap id

         foldMap :: Monoid m => (Elem t -> m) -> t -> m
         foldMap f = foldr (mappend . f) mempty

         foldr :: (Elem t -> b -> b) -> b -> t -> b

         null :: t -> Bool

 -- Instances

 type instance Elem [a] = a

 instance Foldable [a] where
         null = Prelude.null
         foldr = Prelude.foldr
 }}}

 Expected behavior, using FunDeps:

 {{{
 $ ghci Control
 GHCi, version 6.8.0.20071028: http://www.haskell.org/ghc/  :? for help
 Loading package base ... linking ... done.
 [1 of 1] Compiling Control          ( Control.hs, interpreted )
 Ok, modules loaded: Control.
 *Control> null []
 True
 }}}

 behavior when code converted to type families:

 {{{
 $ ghci Bug
 GHCi, version 6.8.0.20071028: http://www.haskell.org/ghc/  :? for help
 Loading package base ... linking ... done.
 [1 of 1] Compiling Bug              ( Bug.hs, interpreted )
 Ok, modules loaded: Bug.
 *Bug> null []
 ghc-6.8.0.20071028: panic! (the 'impossible' happened)
   (GHC version 6.8.0.20071028 for i386-unknown-linux):
         nameModule $dMonoid{v arx}

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

 Commenting out the default instance for "fold" stops the error from
 occurring.

 The same code, using FunDeps:

 {{{
 {-# LANGUAGE MultiParamTypeClasses,
              FunctionalDependencies,
              FlexibleContexts,
              FlexibleInstances #-}

 module Control where

 import Prelude hiding (foldr, null)
 import qualified Prelude (foldr, null)
 import Data.Monoid

 class Foldable t a | t -> a where
         fold :: (Monoid a) => t -> a
         fold = foldMap id

         foldMap :: Monoid m => (a -> m) -> t -> m
         foldMap f = foldr (mappend . f) mempty

         foldr :: (a -> b -> b) -> b -> t -> b

         null :: t -> Bool

 -- Instances

 instance Foldable [a] a where
         null = Prelude.null
         foldr = Prelude.foldr
 }}}

-- 
Ticket URL: <http://hackage.haskell.org/trac/ghc/ticket/1808>
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