RE: Optimization beyond the Module Border

2008-03-20 Thread Matthew Pocock
 |  I'd be interested in any progress here -- we noticed issues with
 |  optimisations in the stream fusion package across module boundaries
 |  that we never tracked down. If there's some key things not firing,
 |  that would be good to know.
 |
 | I suspect that if all modules are compiled -O0, then you recompile one
 | module with -O2, high up in the dependency graph (i.e. it depends on
 | many lower-level modules), plus all things that in turn depend on it
 | (--make), you will not get the good performance you expect.  None of the
 | lower-level functions will have exported inlinings or fusion rules into
 | the interface file.  _All_ modules must be recompiled with -O2,
 | especially the bottom of the dependency chain, to get the best benefit
 | from optimisation.

 Absolutely correct.

 Should this be better documented?  If so, would someone like to think
 where in GHC's user manual they would have looked (or did look), and send
 me some text that would have helped them, had it been there?  As it were.

 Simon

Would it be possible for the compiler to say something like: You are
applying level 2 optimization but some dependencies where compiled without
optimization enabled. To get full optimization, consider recompiling x,y,z
with -O2 - at least this would give us a fighting chance to 'fix' things.

Matthew

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



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


Re: kind error

2007-10-23 Thread Matthew Pocock
Hi,

 Hello,

 data DecoratedFormula = DF{formula  :: Formula,
   iformula ::  IFormula}

 type FastClause = MH.Min US.Set DecoratedFormula

 FastClause.hs:71:25:
`US.Set' is not applied to enough type arguments
Expected kind `*', but `US.Set' has kind `* - *'
In the type synonym declaration for `FastClause'

My hunch would be that US.Set is expecting to be a set of something
(US.Set a for example) and that the first type argument of MH.Min is
expecting a type that can be used right away, rather than one that is
waiting for a type parameter.

So - did you mean something like:

type FastClause = MH.Min (US.Set DecoratedFormula)

Or perhaps something completely different?

Matthew

 Regards,

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



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


Re: UTF-8 decoding error

2006-09-27 Thread Matthew Pocock
Fortress (sun's possibly-not-vaporware hpc language) supports arbitrary 
unicode chars in code, and has an escape syntax for commonly used things. 
Similarly, proof-general/isabelle supports tex-style escapes for symbols  
greek. It seems to me that a pre-processor that turns human-friendly escapes 
(e.g. \{lambda} rather than some magic number) into unicode and a slightly 
intelligent IDE (or emacs mode?) would go most of the way to letting us use 
up-side-down ys and curly as with all the visual beauty and editor niceness 
that we have now with ascii.

Matthew

On Wednesday 20 September 2006 21:42, Duncan Coutts wrote:
 On Wed, 2006-09-20 at 18:14 +0200, Christian Maeder wrote:
  How can I convince ghc version 6.5.20060919 to accept latin1 characters
   in literals?
 
  I wish to keep source files (containing umlauts in strings) that can be
  compiled by either ghc-6.4.2 and ghc-6.6.

 You can use numeric escapes like \222.

 Duncan

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


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