Bugs item #1146068, was opened at 2005-02-22 10:11
Message generated for change (Comment added) made by p1738j
You can respond by visiting: 
https://sourceforge.net/tracker/?func=detail&atid=108032&aid=1146068&group_id=8032

Category: Compiler (Type checker)
Group: 6.4
Status: Open
Resolution: None
Priority: 5
Submitted By: Nobody/Anonymous (nobody)
Assigned to: Nobody/Anonymous (nobody)
Summary: Data.Generics type error

Initial Comment:
I get a strange type error when using
Data.Generics.Twins - but if I include the text of the
definition in my own file it works!

I attach two files, one type checks, one does not. The
only difference is that I move a definition between
modules.

/Patrik


----------------------------------------------------------------------

Comment By: Patrik Jansson (p1738j)
Date: 2005-02-22 10:18

Message:
Logged In: YES 
user_id=1151788

The error is the following:
Compiling Main             ( testeq_bad.hs, interpreted )

testeq_bad.hs:21:34:
    Inferred type is less polymorphic than expected
      Quantified type variable `a' escapes
      Expected type: a1 -> GenericQ Bool
      Inferred type: a1 -> a -> Bool
    In the first argument of `gzipWithQ', namely `geq''
    In the first argument of `and', namely `(gzipWithQ geq'
x y)'
Failed, modules loaded: none.


----------------------------------------------------------------------

Comment By: Patrik Jansson (p1738j)
Date: 2005-02-22 10:16

Message:
Logged In: YES 
user_id=1151788

-- I did not manage to later add the second file - here it
is instead:
-- I tested this with ghci-6.4.20050214
-----
{-# OPTIONS -fglasgow-exts #-}
import Data.Generics.Basics
import Data.Generics.Aliases
import Data.Generics.Twins(gmapAccumQ)

-- | Twin map for queries
gzipWithQ :: GenericQ (GenericQ r) -> GenericQ (GenericQ [r])
gzipWithQ f x y = case gmapAccumQ perkid funs y of
                   ([], r) -> r
                   _       -> error "gzipWithQ" 
 where
  perkid a d = (tail a, unGQ (head a) d)
  funs = gmapQ (\k -> GQ (f k)) x

-- | Generic equality: an alternative to \deriving Eq\
geq :: Data a => a -> a -> Bool
geq x y = geq' x y
  where
    geq' :: forall a b. (Data a, Data b) => a -> b -> Bool
    geq' x y =     (toConstr x == toConstr y)
                && and (gzipWithQ geq' x y)




----------------------------------------------------------------------

Comment By: Patrik Jansson (p1738j)
Date: 2005-02-22 10:13

Message:
Logged In: YES 
user_id=1151788

This was submitted by me (Patrik Jansson = p1738j at sf.net)
- I just loggon on too late. 

----------------------------------------------------------------------

You can respond by visiting: 
https://sourceforge.net/tracker/?func=detail&atid=108032&aid=1146068&group_id=8032
_______________________________________________
Glasgow-haskell-bugs mailing list
Glasgow-haskell-bugs@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs

Reply via email to