#1730: type families GHC "impossible happened"
------------------------------------+---------------------------------------
    Reporter:  guest                |        Owner:  chak   
        Type:  bug                  |       Status:  new    
    Priority:  normal               |    Milestone:         
   Component:  Compiler             |      Version:  6.8    
    Severity:  normal               |   Resolution:         
    Keywords:  type families panic  |   Difficulty:  Unknown
          Os:  Unknown              |     Testcase:         
Architecture:  Unknown              |  
------------------------------------+---------------------------------------
Changes (by chak):

  * owner:  => chak

Comment:

 Copy of the code at hpaste to avoid it getting lost when it expires:
 {{{
 {-# OPTIONS -fglasgow-exts -cpp #-}
 -----------------------------------------------------------------------------
 -- |
 -- Module      :  Data.Collections.Foldable
 -- Copyright   :  Ross Paterson 2005, adaptation to MPTC+FD by Jean-
 Philippe Bernardy
 -- License     :  BSD-style (see the LICENSE file in the distribution)
 --
 -- Maintainer  :  jeanphilippe.bernardy (google mail address)
 -- Stability   :  experimental
 -- Portability :  MPTC+FD
 --
 -- Class of data structures that can be folded to a summary value.

 module Data.Collections.Foldable (
         -- * Folds
         Foldable(..),
         -- ** Special biased folds
         foldr',
         foldl',
         foldrM,
         foldlM,
         -- ** Folding actions
         -- *** Applicative actions
         traverse_,
         for_,
         sequenceA_,
         asum,
         -- *** Monadic actions
         mapM_,
         forM_,
         sequence_,
         msum,
         -- ** Specialized folds
         toList,
         --More general versions exist in Data.Collections
         --concat,
         --concatMap,
         and,
         or,
         any,
         all,
         sum,
         product,
         maximum,
         maximumBy,
         minimum,
         minimumBy,
         -- ** Searches
         elem,
         notElem,
         find
         ) where

 import Prelude hiding (foldl, foldr, foldl1, foldr1, mapM_, sequence_,
                 elem, notElem, concat, concatMap, and, or, any, all,
                 sum, product, maximum, minimum)
 import qualified Prelude (foldl, foldr, foldl1, foldr1)
 import Control.Applicative
 import Control.Monad (MonadPlus(..))
 import Data.Maybe (fromMaybe, listToMaybe)
 import Data.Monoid
 import Data.Array

 #ifdef __NHC__
 import Control.Arrow (ArrowZero(..)) -- work around nhc98 typechecker
 problem
 #endif

 #ifdef __GLASGOW_HASKELL__
 import GHC.Exts (build)
 #endif

 -- | Data structures that can be folded.
 --
 -- Minimal complete definition: 'foldMap' or 'foldr'.
 --
 -- For example, given a data type
 --
 -- > data Tree a = Empty | Leaf a | Node (Tree a) a (Tree a)
 --
 -- a suitable instance would be
 --
 -- > instance Foldable Tree
 -- >    foldMap f Empty = mempty
 -- >    foldMap f (Leaf x) = f x
 -- >    foldMap f (Node l k r) = foldMap f l `mappend` f k `mappend`
 foldMap f r
 --
 -- This is suitable even for abstract types, as the monoid is assumed
 -- to satisfy the monoid laws.
 --
 class Foldable t where

         type FoldElem t

         -- | Combine the elements of a structure using a monoid.
         fold :: Monoid (FoldElem t) => t -> FoldElem t
         fold = foldMap id

         -- | Map each element of the structure to a monoid,
         -- and combine the results.
         foldMap :: Monoid m => (FoldElem t -> m) -> t -> m
         foldMap f = foldr (mappend . f) mempty

         -- | Right-associative fold of a structure.
         --
         -- @'foldr' f z = 'Prelude.foldr' f z . 'toList'@
         foldr :: (FoldElem t -> b -> b) -> b -> t -> b
         foldr f z t = appEndo (foldMap (Endo . f) t) z

         -- | Left-associative fold of a structure.
         --
         -- @'foldl' f z = 'Prelude.foldl' f z . 'toList'@
         foldl :: (b -> FoldElem t -> b) -> b -> t -> b
         foldl f z t = appEndo (getDual (foldMap (Dual . Endo . flip f) t))
 z

         -- | A variant of 'foldr' that has no base case,
         -- and thus may only be applied to non-empty structures.
         --
         -- @'foldr1' f = 'Prelude.foldr1' f . 'toList'@
         foldr1 :: (FoldElem t -> FoldElem t -> FoldElem t) -> t ->
 FoldElem t
         foldr1 f xs = fromMaybe (error "foldr1: empty structure")
                         (foldr mf Nothing xs)
           where mf x Nothing = Just x
                 mf x (Just y) = Just (f x y)

         -- | A variant of 'foldl' that has no base case,
         -- and thus may only be applied to non-empty structures.
         --
         -- @'foldl1' f = 'Prelude.foldl1' f . 'toList'@
         foldl1 :: (FoldElem t -> FoldElem t -> FoldElem t) -> t ->
 FoldElem t
         foldl1 f xs = fromMaybe (error "foldl1: empty structure")
                         (foldl mf Nothing xs)
           where mf Nothing y = Just y
                 mf (Just x) y = Just (f x y)

         -- | Tells whether the structure is empty.
         null :: t -> Bool
         null = all (const False)

         -- | Returns the size of the structure.
         size :: t -> Int
         size = foldr (const (+1)) 0

         -- | Tells whether the structure contains a single element.
         isSingleton :: t -> Bool
         isSingleton = (1 ==) . size -- FIXME: more efficient default.

 -- instances for Prelude types

 instance Foldable (Maybe a) where
         type FoldElem (Maybe a) = a

         foldr f z Nothing = z
         foldr f z (Just x) = f x z

         foldl f z Nothing = z
         foldl f z (Just x) = f z x

 instance Foldable [a] where
         type FoldElem [a] = a

         null = Prelude.null
         size = Prelude.length
         foldr = Prelude.foldr
         foldl = Prelude.foldl
         foldr1 = Prelude.foldr1
         foldl1 = Prelude.foldl1

 instance Ix i => Foldable (Array i a) where
         type FoldElem (Array i a) = (i,a)

         foldr f z = Prelude.foldr f z . assocs

 -- | Fold over the elements of a structure,
 -- associating to the right, but strictly.
 foldr' :: Foldable t => (FoldElem t -> b -> b) -> b -> t -> b
 foldr' f z xs = foldl f' id xs z
   where f' k
 }}}

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