Re: [Haskell] problem building syb-generics

2006-07-11 Thread Matthew Pocock
On Tuesday 04 July 2006 13:20, Simon Peyton-Jones wrote:

 Lexically-scoped type variables are undergoing a slight upheaval in GHC 6.6
 that has not quite settled, and that is what you are running into.

Thanks for the help. After a lot of trial  error, and reading and stuff I've 
got past the problems introduced by lexicals. Now I'm hitting another 
problem. I think there's a missmatch between Maybe (c a) returned by 
dataCast1 and Maybe (c (t' a)) returned by gcast1. Is this dues to something 
stupid I have done, or bit-rot between the two libraries?

Thanks

Matthew

Data/Generics2/Instances.hs:290:17:
    Couldn't match expected type `forall a1. (Data ctx a1) = c (t a1)'
           against inferred type `c1 (t1 a1)'
      Expected type: (forall a2. (Data ctx a2) = c (t a2))
                     - Maybe (c [a])
      Inferred type: c1 (t1 a1) - Maybe (c1 (t' a1))
    In the expression: gcast1
    In the definition of `dataCast1': dataCast1 _ = gcast1

The type of gcast is:
Data.Typeable.  gcast1  :: (Typeable1 t, Typeable1 t') = c (t a) - Maybe (c 
(t' a))

And the dataCast1 signature (in Data.Generics2.Basics) is:

class (Typeable a, Sat (ctx a)) = Data ctx a
   where
     -- | Mediate types and unary type constructors
     dataCast1 :: Typeable1 t
               = ctx ()
               - (forall a. Data ctx a = c (t a))
               - Maybe (c a)
  ...

The implementation (in Data.Generics2.Instances) is:

instance (Sat (ctx [a]), Data ctx a) =
         Data ctx [a] where
  dataCast1 _  = gcast1
  ...
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: Is this test summary good or bad?

2006-07-11 Thread Joel Reymont

On Jul 11, 2006, at 11:00 AM, Simon Marlow wrote:
Which ones hang?  Could you take one of the hanging tests, compile  
it with -debug, run with +RTS -Ds, and send us the output?


What ends up happening is this:

28683  p2  S  0:00.11 ../../timeout/timeout 300 cd ./typecheck/ 
should_compile  '/Users/joelr/work/Haskell/ghc/compiler/stage2/ghc- 
inplace' -no-recomp -dcore-lint -dcmm-lint -Di386_apple_darwin -c  
tc033.hs   -fno-warn-incomplete-patterns tc033.comp.stderr 21


29125  p2  R  1:53.48 ../../timeout/timeout 300 cd ./typecheck/ 
should_fail  '/Users/joelr/work/Haskell/ghc/compiler/stage2/ghc- 
inplace' -no-recomp -dcore-lint -dcmm-lint -Di386_apple_darwin -c  
tcfail011.hstcfail011.comp.stderr 21


Now, these things have been running there forever and I'm not even  
sure it's a Haskell problem. I suppose the test harness should have  
terminated the test after 300 seconds but didn't.


If I try to re-run the first process by hand it finishes instantly.  
If I try to re-run the whole thing as above, putting everything after  
300 in double quotes it also finishes instantly.


--
http://wagerlabs.com/





___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: RULES pragmas

2006-07-11 Thread Donald Bruce Stewart
Malcolm.Wallace:
 I have a question about {-# RULES #-} pragmas.  Here is a very simple
 attempt to use them:
 
 module Simplest where
 {-# RULES
 simplestRule   forall x.   id (id x) = x
   #-}
 myDefn = id (id 42)
 
 I want to verify whether ghc-6.4.1 does actually fire this rule, but
 have so far been unable to do so.  According to the manual (section
 7.10.5), the flag -ddump-rules should list simplestRule if it has been
 parsed correctly, and -ddump-simpl-stats should list the number of times
 it has fired.  But it does not appear in either listing.
 
 Reasoning that I have the syntax wrong, I have tried numerous variations
 on the indentation, added type signatures, etc., all to no avail.
 
 So what am I doing wrong?  And is there any way to ask the compiler to
 give a warning if the RULES pragma contains errors?

In this case, it's because it's missing -fglasgow-exts, I think.
The following works for me with both 6.4 and 6.5 compilers:

module Simplest where

{-# RULES
simplestRule forall x. id (id x) = x
#-}

myDefn = id (id 42)

when compiled with:
$ ghc-6.4.2 -fglasgow-exts -c -ddump-simpl-stats A.hs

 Grand total simplifier statistics
Total ticks: 11

2 PreInlineUnconditionally
3 PostInlineUnconditionally
1 UnfoldingDone
1 RuleFired
1 simplestRule
4 BetaReduction
2 SimplifierDone

However, in general, you need to be careful that your identifiers
weren't inlined in the first phase. To control this we add an INLINE [1]
pragma to identifiers we want to match in rules, to ensure they haven't
disappeared by the time the rule matching comes around.

Also, you need -O to have rules kick in locally.

So, 
module Simplest where

{-# RULES
simplestRule forall x. myid (myid x) = x
#-}

myDefn = myid (myid 42)

myid x = x
{-# INLINE [1] myid #-}

And:
$ ghc-6.4.2 -fglasgow-exts -O -c -ddump-simpl-stats A.hs

 Grand total simplifier statistics 
Total ticks: 15

6 PreInlineUnconditionally
2 UnfoldingDone
1 RuleFired
1 simplestRule
5 BetaReduction
1 KnownBranch
8 SimplifierDone

Cheers,
  Don
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users