Generalized phase control for GHC

2008-06-14 Thread Max Bolingbroke
Hi, As some of you may know, I'm working on adding support for dynamically loaded plugins to GHC this summer. As part of this we need a way to specify ordering on the compiler phases installed, so e.g. you can say that a phase you install should run after strictness analysis does. This problem

Re: Recursive functions and constant parameter closures (inlining/strictness analyzer question)

2008-06-20 Thread Max Bolingbroke
Hi Dan, I've only got time for a quick reply now, I'll see if I can take a more substantitative look at your examples next week. Specifically, will GHC simply always perform the static argument transform, or will it have some kind of heuristic to decide when it's useful? It seems, according

Re: Recursive functions and constant parameter closures (inlining/strictness analyzer question)

2008-06-23 Thread Max Bolingbroke
I've been wondering if a nice option would be to be able to feed profiler information in at compile time and have it override the heuristics. That way, inlining, specialization, SAT, etc., decisions could be made based on how the code actually gets used during a typical run of the program.

Re: Recursive functions and constant parameter closures (inlining/strictness analyzer question)

2008-06-23 Thread Max Bolingbroke
2008/6/22 Simon Peyton-Jones [EMAIL PROTECTED]: | However, if I had to pick something out of the air, I'd say this: always do | SAT when the argument in question is a function. Yes, that might well be a good heuristic to try, if you are interested to pursue this, Max. Making the function

Re: Recursive functions and constant parameter closures (inlining/strictness analyzer question)

2008-06-25 Thread Max Bolingbroke
2008/6/23 Dan Doel [EMAIL PROTECTED]: On Monday 23 June 2008, Isaac Dupree wrote: there's no chance for the lower-level near code generation to reverse-SAT to eliminate the heap usage? (which would obviously be a different optimization that might be useful in other ways too, if it could be

Re: Generalized phase control for GHC

2008-07-05 Thread Max Bolingbroke
Hi Roman, Three things. Firstly, what would lenient ordering be useful for? You probably had a specific use case in mind? I suspect that when you have multiple plugins all specifying constraints on the phase ordering independently it is possible to end up in a situation where using each plugin

Re: Generalized phase control for GHC

2008-07-05 Thread Max Bolingbroke
If you don't need a dependency and it can be ignored anyway, why would you want to specify it in the first place? I just can't quite imagine a situation in which I would use this. I think it makes sense because many of the inter-pass dependencies we have in the GHC pipeline today are actually

Re: Generalized phase control for GHC

2008-07-07 Thread Max Bolingbroke
Ah -- Roman you mean you want to add a phase-ordering constraint at some time *other* than when you declare one or other of the phases. Are you sure this is important? It's an awkward addition because, like orphan instances, it means there's an interface file with perhaps-vital info which

Re: Generalized phase control for GHC

2008-07-07 Thread Max Bolingbroke
Also, why do you want phase aliases? I don't quite see how to achieve this without aliases. This will be even more of a problem once I add additional fusion layers. I've added phase equality to the implementation. It seems like a nice clean extension. Since this lets you add constraints to

Re: Weekly IRC meeting?

2008-07-30 Thread Max Bolingbroke
It would be nice if we could make some more progress on the revision control issue from last week. I don't know if people are ready to actually make a choice of RCS at this stage, but I've tried to make all the information necessary to make a choice available at

Re: tools for comparing ghc's debug outputs?

2008-07-31 Thread Max Bolingbroke
2008/7/31 Claus Reinke [EMAIL PROTECTED]: What tools are there for facilitating comparisons of ghc's debug output? I have reduced a performance problem in my code to a case where switching two lines of code doubles or halves the performance (the results of those lines are stored in record

Re: Version control systems

2008-08-06 Thread Max Bolingbroke
2008/8/6 david48 [EMAIL PROTECTED]: cat: _darcs/prefs/defaultrepo: No such file or directory Couldn't work out defaultrepo at ./darcs-all line 27. You can't yet build from the Git repo, alas. I've added the necessary patches and scripts (you need sync-all, not darcs-all) to

Re: Version control systems

2008-08-06 Thread Max Bolingbroke
2008/8/6 Duncan Coutts [EMAIL PROTECTED]: On Tue, 2008-08-05 at 22:12 -0700, Don Stewart wrote: marlowsd: Following lots of useful discussion and evaluation of the available DVCSs out there, the GHC team have made a decision: we're going to switch to git. Hooray, this will generate a lot

Re: Version control systems

2008-08-15 Thread Max Bolingbroke
2008/8/15 Isaac Dupree [EMAIL PROTECTED]: So let's figure out how it would work (I have doubts too!) So, within the directory that's a git repo (ghc), we have some other repos, git (testsuite) and darcs (some libraries). Does anyone know how git handles nested repos even natively? You can

Re: Version control systems

2008-08-15 Thread Max Bolingbroke
2008/8/15 Ian Lynagh [EMAIL PROTECTED]: You can explicitly tell Git about nested Git repos using http://www.kernel.org/pub/software/scm/git/docs/git-submodule.html. This essentially associates a particular version of each subrepo with every version of the repo that contains them, so e.g.

Re: Compiler optimizations questions for ghc 6.10...

2009-02-17 Thread Max Bolingbroke
2009/2/17 Tyson Whitehead twhiteh...@gmail.com: (compiled with ghc 6.10 with options -O2 -ddump-simpl) I was wondering why lvl_s1mF is not being inlined into a_s1Gv in the core at the bottom of this email as that is the only place it is ever referenced. The relevant GHC code is

Re: Compiler optimizations questions for ghc 6.10...

2009-02-18 Thread Max Bolingbroke
2009/2/18 Tyson Whitehead twhiteh...@gmail.com: On February 17, 2009 19:24:44 Max Bolingbroke wrote: 2009/2/17 Tyson Whitehead twhiteh...@gmail.com: (compiled with ghc 6.10 with options -O2 -ddump-simpl) That should have been -ddump-stranal instead of -ddump-simpl. Right. Mystery solved

Re: Compiler optimizations questions for ghc 6.10...

2009-02-18 Thread Max Bolingbroke
2009/2/18 Max Bolingbroke batterseapo...@hotmail.com: Yes - GHC wants to share the work of (maxBound-x)`div`10 between several partial applications of digit. This is usually a good idea, but in this case it sucks because it's resulted in a massively increased arity. IMHO GHC should fix

Re: Compiler optimizations questions for ghc 6.10...

2009-02-19 Thread Max Bolingbroke
2009/2/19 Krasimir Angelov kr.ange...@gmail.com: I was surprised to see this case expression: case GHC.Prim.-# 9223372036854775807 ipv_s1bD of wild2_a1xi [ALWAYS Just L] { What is the purpose to compare the value with maxBound before the division? The case expression doesn't

Re: optimization and rewrite rules questions

2009-02-26 Thread Max Bolingbroke
2009/2/24 Claus Reinke claus.rei...@talk21.com: In the recently burried haskell-cafe thread speed: ghc vs gcc, Bulat pointed out some of the optimizations that GHC doesn't do, such as loop unrolling. I suggested a way of experimenting with loop unrolling, using template haskell to bypass GHC's

Re: Loop unrolling + fusion ?

2009-02-28 Thread Max Bolingbroke
2009/2/28 Don Stewart d...@galois.com: So now, since we've gone to such effort to produce a tiny loop like, this, can't we unroll it just a little? Sadly, my attempts to get GCC to trigger its loop unroller on this guy haven't succeeded. -funroll-loops and -funroll-all-loops doesn't  touch it,

Re: Loop unrolling + fusion ?

2009-03-01 Thread Max Bolingbroke
2009/3/1 Claus Reinke claus.rei...@talk21.com: It might be useful to point out that the interaction goes both ways. Not only are fused loops candidates for unrolling, but unrolling can also enable fusion, giving one example of why Core-level unrolling (in addition to backend-level loop

Re: Loop unrolling + fusion ?

2009-03-07 Thread Max Bolingbroke
2009/3/7 Claus Reinke claus.rei...@talk21.com: hmm, appropriate is one of those words that shouldn't occur in specs, not even rough ones, so let's flesh this out a bit, by abstract example. let f = ..f.. in f{n,m} -PEEL- let f = ..f.. in ..f{n-1,m}.. Probably what you intend here is that you

Re: Loop unrolling + fusion ?

2009-03-09 Thread Max Bolingbroke
2009/3/9 Roman Leshchinskiy r...@cse.unsw.edu.au: The problem here is that this only works for directly recursive functions which I, for instance, don't normally use in high-performance code. Most of my loops are pipelines of collective combinators like map, filter, fold etc. because these are

Re: Loop unrolling + fusion ?

2009-03-09 Thread Max Bolingbroke
2009/3/9 Claus Reinke claus.rei...@talk21.com: let f = ..f.. in f{n,m} -PEEL- let f = ..f.. in ..f{n-1,m}.. Probably what you intend here is that you create one copy of the definition every round rather than one per call site, is that right? I don't think so - ultimately, the point of both

Re: Loop unrolling + fusion ?

2009-03-09 Thread Max Bolingbroke
2009/3/9 Claus Reinke claus.rei...@talk21.com: But if you annotate all your unrolled and peeled new definitions as NOINLINE, do you still get the optimizations you want? There are probably a few GHC optimizations that can look through non-recursive lets, but RULES are not among those. The

Re: Loop unrolling + fusion ?

2009-03-19 Thread Max Bolingbroke
2009/3/19 Claus Reinke claus.rei...@talk21.com: If the map, filter, fold, etc can be unrolled, then the unrolled definitions would be fused, right? So what is missing is fine control (how much to unroll this particular call to map here). The issues is that In stream fusion the combinators like

Re: Loop unrolling + fusion ?

2009-03-19 Thread Max Bolingbroke
2009/3/19 Claus Reinke claus.rei...@talk21.com: Recursion unfolding spec, 2nd attempt. If this is an improvement on the first version, and after correcting any obvious issues, I should put it on the ghc trac wiki somewhere, and create a feature request ticket. I can't see any issues

Re: mkIfThenElse

2009-03-22 Thread Max Bolingbroke
It moved to MkCore: mkIfThenElse :: CoreExpr - CoreExpr - CoreExpr - CoreExpr mkIfThenElse guard then_expr else_expr -- Not going to be refining, so okay to take the type of the then clause = mkWildCase guard boolTy (exprType then_expr) [ (DataAlt falseDataCon, [], else_expr), --

Re: mkIfThenElse

2009-03-22 Thread Max Bolingbroke
2009/3/22 Colin Paul Adams co...@colina.demon.co.uk: Max == Max Bolingbroke batterseapo...@hotmail.com writes:    Max It moved to MkCore Thanks. What about mkWildId from Id.lhs? That one seems to have vanished. Looks that might be the same deal (moved to MkCore), assuming this is what you

Re: Puzzling (to me) type error message

2009-03-24 Thread Max Bolingbroke
2009/3/24 Colin Adams colinpaulad...@googlemail.com: UI.hs:625:45: Not in scope: type constructor or class `Move.Move' If I then comment-out the type signature for run_ai, it compiles fine with the following warning message: UI.hs:626:0:    Warning: Definition but no type signature for

Re: Really bad code for single method dictionaries?

2009-03-27 Thread Max Bolingbroke
2009/3/26 Jason Dusek jason.du...@gmail.com:  I was reading the stream fusion code today and came across a comment stating  that single element dictionaries interacted poorly with GHC's optimizer:    class Unlifted a where      [...]      expose [...]      -- | This makes GHC's optimiser

Re: Under OS X 10.5.6: GHC 6.10.1 Release Candidate 1

2009-03-27 Thread Max Bolingbroke
2009/3/27 Simon Marlow marlo...@gmail.com: I have a fix for num012 (the test is broken), but I still don't know what's going on with num009. num009 has been broken on OS X for as long as I can remember :-). I opened a ticket about it on Trac way back:

Re: doCorePass

2009-04-01 Thread Max Bolingbroke
2009/4/1 Colin Paul Adams co...@colina.demon.co.uk: Between 6.8 and 6.11, function doCorePass in module SimplCore has changed types from: CoreToDo - HscEnv - UniqSupply - RuleBase  - ModGuts - IO (SimplCount, ModGuts) to: CorePass (== CoreToDo) - ModGuts - CoreM ModGuts The file to

Re: Chimeric syntax

2009-04-28 Thread Max Bolingbroke
2009/4/28 Scott Michel scooter@gmail.com: This got me to thinking that either ghc has issues or I have some fundamental misunderstanding of Haskell syntax. Or, maybe I should use someone else's grammar. GHC's parser is over-generous by design. See

Re: Closure elimination transformation (continuation style passing code)

2009-05-20 Thread Max Bolingbroke
2009/5/20 Tyson Whitehead twhiteh...@gmail.com: 1- avoid forming the (iter xs) and (count i+1) closures by passing the function and the arguments instead of the function bound to the argument  iter []     next i done = done  iter (x:xs) next i done = next i x iter xs You have already

Re: Closure elimination transformation (continuation style passingcode)

2009-05-20 Thread Max Bolingbroke
2009/5/20 Claus Reinke claus.rei...@talk21.com: Work is underway to make library-specified optimizations more expressive (as core2core pass plugins), though I don't know the status of either that  (Max?-) I submitted a final version of the plugins patch to Simon some time ago - it's waiting

Re: Three patches for cabal

2009-06-03 Thread Max Bolingbroke
2009/6/3 Niklas Broberg niklas.brob...@gmail.com: First there's the constructor called TransformListComp, which should really be named GeneralizedListComp, since the constructor should describe the extension and not the implementation scheme. It's called TransformListComp because the then f

Re: group keyword with TransformListComp

2009-06-27 Thread Max Bolingbroke
Hi, I agree this is annoying. It was hard to find syntax which was both meaningful and currently unused, so we settled on this instead. As Simon says, suggestions are welcome! Note that group *should* be parsed as a special id, so you can still import D.L qualified and then use dot notation to

Re: [Haskell-cafe] Ghci dynamic linking (Was: C++ libraries and GHCI)

2009-09-30 Thread Max Bolingbroke
(Moving to ghc-users) I'd never seen V in nm output before: The symbol is a weak object. When a weak defined symbol is linked with a normal defined symbol, the normal defined symbol is used with no error. When a weak undefined symbol is linked and the symbol is not defined, the value of the

Re: inferred type doesn't type-check (using type families)

2009-11-03 Thread Max Bolingbroke
2009/11/3 Daniel Fischer daniel.is.fisc...@web.de: Am Dienstag 03 November 2009 19:28:55 schrieb Roland Zumkeller: Hi, Compiling class WithT a where   type T a f :: T a - a - T a f = undefined g x = f x 42 with -XTypeFamilies -fwarn-missing-signatures gives:              

Re: Question regarding the GHC users manual

2010-01-25 Thread Max Bolingbroke
Hi Tyson, I don't think this is a bug. type family F a b :: * - *   -- F's arity is 2,                              -- although its overall kind is * - * - * - * F Char [Int]       -- OK!  Kind: * - * Char :: * [Int] :: * So we can fill in the first two * in the kind * - * - * - * to get *

Re: GHC core plugins

2010-01-26 Thread Max Bolingbroke
Hi José, The patch implementing GHC plugins is with Simon PJ and awaiting merge into GHC (and has been for some time - he's a busy guy and its a big patch). However, even once it's merged some more work will need to be done to make sure that it plays nicely with the shared library support (now

Re: GHC core plugins

2010-01-28 Thread Max Bolingbroke
2010/1/28 José Pedro Magalhães j...@cs.uu.nl: Yes, that helped quite a lot. One last thing: currently it takes me about 6 minutes to rebuild the compiler after I change the core pass. Are there any tricks of the build system I can use to speed this up? I'm already using a fast build without

Re: Quasi quoting

2010-02-02 Thread Max Bolingbroke
(Sorry if you see this twice, Simon - I didn't reply to the list) 2010/2/2 Simon Marlow marlo...@gmail.com: Can you say precisely what it means to be in an Exp context? In a Type context == a HsSpliceTy constructor in the existing GHC AST In an Exp context == a HsSpliceE constructor in the

Re: Quasi quoting

2010-02-02 Thread Max Bolingbroke
2010/2/2 Isaac Dupree m...@isaac.cedarswampstudios.org: I'm concerned in both your proposals, that single-letter names like t and d are common function parameters, thus possibly producing - shadowing warnings for all such functions in modules that happen to use TH - errors, I think, for some

Re: Quasi quoting

2010-02-02 Thread Max Bolingbroke
2010/2/2 Twan van Laarhoven twa...@gmail.com:    class Quoted a where        parseQuote :: String - a        -- for performance reasons:        parseQuote' :: Ghc.PackedString - a Great idea! Thinking about it, you can use type classes to dispose of the QuasiQuote record entirely. Instead,

Re: Quasi quoting

2010-02-03 Thread Max Bolingbroke
On 3 February 2010 14:07, Sebastian Fischer s...@informatik.uni-kiel.de wrote: With a class-based approach only one parser that creates values of the same type could be used in a program. It would not be possible to embed multiple languages that create TH.Exp to be spliced into a single

Re: Shared GHC libraries and the runtime system

2010-02-22 Thread Max Bolingbroke
Hi Tyson, This blog post (http://blog.well-typed.com/2009/05/buildings-plugins-as-haskell-shared-libs/) might help explain the motivation (actually there are a few relevant posts on the well-typed site). Essentially, I believe that this is done so that you can vary the RTS by changing

Re: strictness of unused arguments

2010-03-12 Thread Max Bolingbroke
On 12 March 2010 13:13, Roman Beslik ber...@ukr.net wrote: Thanks for the answer. Sorry, I can not follow all of your thoughts because my knowledge of strictness analysis and GHC optimizations are very basic. :( I looked into GHC code once several years ago. BTW there are a lot of papers about

Re: Encountered absent arg

2010-04-07 Thread Max Bolingbroke
On 7 April 2010 00:23, Louis Wasserman wasserman.lo...@gmail.com wrote: biggest sources of angst!)  Looking at ghc-core, my code appears to always give the exception Oops!  Entered absent arg ww_s9eC{v} [lid] predmain:Data.Algebra.Ring.Ring{tc r2tU} c{tv a8Os} [tv] Is this typical?  Where

Re: Encountered absent arg

2010-04-11 Thread Max Bolingbroke
On 11 April 2010 22:11, Johannes Waldmann waldm...@imn.htwk-leipzig.de wrote: Louis Wasserman wasserman.louis at gmail.com writes: I compiled my code with -fdicts-strict. What is this actually supposed to do? It seems the documentation is missing:

Re: Using -fext-core without a Main function

2010-04-13 Thread Max Bolingbroke
The flag -fext-core is a red herring. GHC assumes any module with no module declaration is actually called Main and hence insists on a main declaration. mbolingbr...@perihelion ~/tmp $ ghc -c Hal.hs Hal.hs:1:0: The function `main' is not defined in module `Main' Compile this instead: module

Re: Getting a GHC repository got easier: new instructions

2010-04-26 Thread Max Bolingbroke
On 26 April 2010 13:42, Simon Marlow marlo...@gmail.com wrote: comments welcome! This is great news. However, I had some problems: 1) darcs-all does not add --lazy by default, which contradicts the wiki: $ ./darcs-all --testsuite get warning: adding --partial, to override use --complete

Re: hsc2hs on Mac OS 10.6 unreliable?

2010-06-09 Thread Max Bolingbroke
On 8 June 2010 22:03, Axel Simon axel.si...@in.tum.de wrote: The offsets that hsc2hs calculates are too large, so it is probably in x86_64 mode. Is it just this problem: http://hackage.haskell.org/trac/ghc/ticket/3400 If you use an older GHC you will need to manually patch the hsc2hs script to

Re: SPECIALIZE function for type defined elsewhere

2010-07-28 Thread Max Bolingbroke
On 28 July 2010 13:57, Sebastian Fischer s...@informatik.uni-kiel.de wrote: In my case, I don't want to put everything in a single module because I cannot know what other B-like modules people will implement.Are they bound to use `f` unspecialized for their types? Yes. GHC might inline f into

Re: Using associated data types to create unpacked data structures

2010-08-12 Thread Max Bolingbroke
On 12 August 2010 20:31, Johan Tibell johan.tib...@gmail.com wrote: Yes and dead code elimination should also be able to get rid of much of the code duplication even before it reaches the linker. I don't think dead code elimination will help, because presumably you want to generate

Re: exporting instances: was Using associated data types to create unpacked data structures

2010-08-13 Thread Max Bolingbroke
On 13 August 2010 00:13, John Lask jvl...@hotmail.com wrote: I have wondered and perhaps someone can explain: what are the issues in explicit control of instance export and import? (apart from defining an appropriate syntax) IMHO main problem with this (and related feature requests like local

Re: Bringing back Monad Comprehensions (in style)

2010-10-05 Thread Max Bolingbroke
On 5 October 2010 15:41, George Giorgidze giorgi...@gmail.com wrote: One can also look at how recently introduced 'order by' and 'group by' constructs generalise to monad comprehensions. If that works, one could implement even more stylish monad comprehension notation. They do: see the

Re: Bringing back Monad Comprehensions (in style)

2010-10-07 Thread Max Bolingbroke
On 7 October 2010 12:04, Sebastiaan Visser hask...@fvisser.nl wrote: What exactly are the benefits of Monad comprehensions over, for example, the do-notation or idioms? List comprehensions are just a specialisation of the do-notation for lists. Monad comprehensions are a generalisation for

Local evidence and type class instances

2010-10-16 Thread Max Bolingbroke
Hi GHC users, Now that the Glorious New type checker can handle local evidence seamlessly, is it a big implementation burden to extend it to deal with local *type class instances* in addition to local *equality constraints*? For example, you could write this: f :: Bool f = id id where

Re: Local evidence and type class instances

2010-10-16 Thread Max Bolingbroke
HI Antoine, I didn't know UHC already had this - thanks for the pointer! It seems they have read about implicit configurations too, as the example they use is very similar to the paper. In fact, they also have another extension to the concept that I was intentionally avoiding mentioning - they

Re: Unicode windows console output.

2010-11-03 Thread Max Bolingbroke
On 2 November 2010 21:05, David Sankel cam...@gmail.com wrote: Is there a ghc wontfix bug ticket for this? Perhaps we can make a small C test case and send it to the Microsoft people. Some[1] are reporting success with Unicode console output. I confirmed that I can output Chinese unicode from

Re: Loop optimisation with identical counters

2010-11-08 Thread Max Bolingbroke
On 6 November 2010 04:47, David Peixotto d...@rice.edu wrote: Are you sure about R1 aliasing Sp? AFAIK, R1 points to a closure on the heap, not to a stack location. That is, it can alias pointers on the stack or Hp but it can't alias the Sp itself. I don't think Sp can be aliased by

Re: Wadler space leak

2010-11-09 Thread Max Bolingbroke
On 9 November 2010 07:58, Duncan Coutts duncan.cou...@googlemail.com wrote: This proposal is mentioned favourably by Jörgen Gustavsson David Sands in [1] (see section 6, case study 6). They mention that there is a formalisation in Gustavsson's thesis [2]. That may say something about inlining,

Re: Parallel, Incremental Linking

2010-12-07 Thread Max Bolingbroke
On 7 December 2010 08:54, John Smith volderm...@hotmail.com wrote: Gold in an incremental and multi-threaded linker, but can only output ELF (not Windows). Is there a cross-platform solution suitable for GHC? Not AFAIK. One thing that would probably help a lot is if GHC-generated code stopped

Re: How to use llvm with ghc7?

2010-12-08 Thread Max Bolingbroke
On 8 December 2010 08:28, Magicloud Magiclouds magicloud.magiclo...@gmail.com wrote:  I am using debian 32bit system, llvm 2.6. I haven't seen your particular error before, but AFAIK -fllvm won't work with LLVM 2.7 because it depends on the GHC calling convention that is only present from that

Re: RFC: migrating to git

2011-01-10 Thread Max Bolingbroke
On 10 January 2011 11:19, Simon Marlow marlo...@gmail.com wrote: Let us know what you think - would this make life harder or easier for you?  Would it make you less likely or more likely to contribute? Well, as a sometime-contributor I would certainly be happier hacking on GHC if it were git

Re: RFC: migrating to git

2011-01-13 Thread Max Bolingbroke
On 12 January 2011 22:13, Claus Reinke claus.rei...@talk21.com wrote: You can emulate darcs's patch re-ordering in git if you put each independent sequence of patches on a separate branch. Then you can re-merge the branches in whatever order you want. This is a fairly common git workflow.

Re: Can't make sense of newArray# docs

2011-01-18 Thread Max Bolingbroke
On 18 January 2011 22:18, Johan Tibell johan.tib...@gmail.com wrote: Why is the size in bytes? I think the docs are wrong. The code for newArray# (in PrimOps.cmm) interprets n as a size in words: {{{ stg_newArrayzh { W_ words, n, init, arr, p, size; /* Args: R1 = words, R2 =

Re: backward compatibility

2011-01-20 Thread Max Bolingbroke
On 20 January 2011 02:47, John Meacham j...@repetae.net wrote: Allowing this was a specific feature that was included in ghc on purpose (as well as the relaxed if/then layout rule in do statements) So this is definitely a regression. Ian split this out in this patch:

Re: Release/git plans

2011-01-20 Thread Max Bolingbroke
On 20 January 2011 16:57, austin seipp a...@hacks.yi.org wrote: It would be nice to have this in GHC 7.2, but I was thinking of eventually extending the scope of compiler plugins to allow users to write Cmm optimisations as well. This would be particularly cool because Cmm optimisations in the

Re: Release/git plans

2011-01-22 Thread Max Bolingbroke
On 21 January 2011 23:59, austin seipp a...@hacks.yi.org wrote: Perhaps Max can elaborate on why this design was rejected in favor of the current one, so we can see how and where it falls down, and what we really want. The only reason really is that it added a lot of mechanism. From the top of

Re: RFC: Compiler plugins for GHC (was: Release/git plans)

2011-01-23 Thread Max Bolingbroke
On 23 January 2011 00:31, austin seipp a...@hacks.yi.org wrote: or what the current state of dynamic linking on windows is. AFAIK it is meant to work. What I'm not sure about is whether any of the plugins code will have to be modified to make use of it. I suspect it won't since IIRC I went

Re: Question about Haskell AST

2011-01-25 Thread Max Bolingbroke
On 24 January 2011 17:20, Jane Ren j2...@ucsd.edu wrote: When I try this, I get AstWalker: panic! (the 'impossible' happened)  (GHC version 7.0.1 for x86_64-apple-darwin):        lexical error at character 'i' It looks like you need to add the CPP extension to the DynFlags:

Re: RFC: migrating to git

2011-01-25 Thread Max Bolingbroke
On 25 January 2011 09:35, Lars Viklund z...@acc.umu.se wrote: A subtree seems to be a way of getting the contents of a branch merged at a non-root location. It might be a relevant read and something to evaluate. There is also the git-subtree project (https://github.com/apenwarr/git-subtree).

Re: [Haskell-cafe] How to #include into .lhs files?

2011-02-04 Thread Max Bolingbroke
On 4 February 2011 05:03, Michael Snoyman mich...@snoyman.com wrote: My guess (a complete guess) is that the deliterate step is creating a temporary .hs file elsewhere on your filesystem, which is why the CPP step can't find B.hs without a fully-qualified path. That is what is happening (you

Re: Faster Array#/MutableArray# copies

2011-02-18 Thread Max Bolingbroke
On 18 February 2011 01:18, Johan Tibell johan.tib...@gmail.com wrote: C compilers, like gcc, go to great lengths making memcpy fast and I was thinking that we might be able to steal a trick or two from them. I'd like some feedback on these ideas: It seems like a sufficient solution for your

Re: cabal install network was: Re: ANNOUNCE: GHC 7.0.2 Release Candidate 2

2011-02-21 Thread Max Bolingbroke
On 21 February 2011 11:50, Christian Maeder christian.mae...@dfki.de wrote: The problem (below) is caused by the new flags  -isysroot /Developer/SDKs/MacOSX10.5.sdk -mmacosx-version-min=10.5 inside hsc2hs that have been added to fix http://hackage.haskell.org/trac/ghc/ticket/4860.

Re: ghc-7.0.2 on macports wanted

2011-03-11 Thread Max Bolingbroke
On 10 March 2011 17:51, Christian Maeder christian.mae...@dfki.de wrote: Why does the base package depend on iconv only on macs? iconv is not needed under linux or solaris (unless you install haskeline, which is not in the platform. I don't have access to a Linux box to check, but according to

Re: trac ticket spam

2011-03-12 Thread Max Bolingbroke
On 31 January 2011 16:54, Simon Marlow marlo...@gmail.com wrote: On 31/01/2011 16:45, Claus Reinke wrote: Is there any way to have a moderate first comment by new submitter policy for trac, to avoid the kind of ticket spam we have at the moment? They seem to have started commenting on

Re: GHC7 (on OSX.5)

2011-03-20 Thread Max Bolingbroke
On 20 March 2011 19:01, wren ng thornton w...@freegeek.org wrote: Are these warnings I should be concerned about? No. These warnings just tell you explicitly that SpecConstr has exceeded the limit of specialisations that GHC is happy to generate. They are totally harmless and just mean that

Re: OPTIONS_GHC -prof -auto-all

2011-03-28 Thread Max Bolingbroke
On 26 March 2011 21:02, Henning Thielemann g...@henning-thielemann.de wrote: to the mentioned module, but GHC rejects this, because the profiler options are not allowed in the OPTIONS pragma. According to According to http://www.haskell.org/ghc/docs/7.0.1/html/users_guide/flag-reference.html

Re: -DDEBUG and testsuite

2011-04-06 Thread Max Bolingbroke
On 6 April 2011 12:04, Edward Z. Yang ezy...@mit.edu wrote: The ill fated commit I made yesterday was a partial attempt to address some of the problems: basically, it boils down to DEBUG blocks that induce extra debugging output that the test framework doesn't know about. You didn't used to

Re: MonoLocalBinds and hoopl

2011-06-19 Thread Max Bolingbroke
On 14 June 2011 14:28, Simon Peyton-Jones simo...@microsoft.com wrote: I must say I'm inclined to adopt this idea.  Any comments from others? This is something I suggested at the time you submitted let should not be generalised. I'm in favour of it, and from personal experience believe that this

Re: Superclass defaults

2011-08-22 Thread Max Bolingbroke
On 21 August 2011 21:03, Alexey Khudyakov alexey.sklad...@gmail.com wrote: I don't completely understant how does it work. Does client need to enable language extension to get default instances? I think that the extension would only be required to *define them*, not for them to be generated.

Re: Cheap and cheerful partial evaluation

2011-08-22 Thread Max Bolingbroke
On 21 August 2011 19:20, Edward Z. Yang ezy...@mit.edu wrote: And no sooner do I send this email do I realize we have 'inline' built-in, so I can probably experiment with this right now... You may be interested in my related ticket #5029: http://hackage.haskell.org/trac/ghc/ticket/5059 I don't

Re: Panic when using syb with GHC API

2011-08-26 Thread Max Bolingbroke
On 26 August 2011 09:22, Simon Peyton-Jones simo...@microsoft.com wrote: The underlying issue is that before type checking GHC (obviously) doesn't know the types of things, while afterwards it does.  The whole HsSyn tree is parameterised over the types of identifiers:  Parsed:       HsExpr

Re: Parallel --make (GHC build times on newer MacBook Pros?)

2011-08-29 Thread Max Bolingbroke
On 27 August 2011 09:00, Evan Laforge qdun...@gmail.com wrote: Right, that's probably the one I mentioned.  And I think he was trying to parallelize ghc internally, so even compiling one file could parallelize.  That would be cool and all, but seems like a lot of work compared to just

Re: Discussion about the ConstraintKinds extension

2011-10-18 Thread Max Bolingbroke
On 18 October 2011 02:25, bob zhang bobzhang1...@gmail.com wrote:      take a contrived example,      class C B = B a where      here B :: * - Constraint,  I think this definition is reasonable, since B does not appears in the      first position of the context. I think you are getting an

Re: Discussion about the ConstraintKinds extension

2011-10-20 Thread Max Bolingbroke
On 18 October 2011 13:49, bob zhang bobzhang1...@gmail.com wrote:     In my contrived example the definition of class C is like this         class C c where { foo :: c Int = }         class C B = B a where { ...}     will this pass under your proposal? Yes I would allow this to pass. If

Re: Discussion about the ConstraintKinds extension

2011-10-22 Thread Max Bolingbroke
On 20 October 2011 19:51, bob zhang bobzhang1...@gmail.com wrote: That would be great. Would you mind send me a patch, or commit it to the source tree. I've made this change in commit 5ff06e90f56b7da00f4fec74358b2e736133c263. Hope that helps. Max

Re: behaviour change in getDirectoryContents in GHC 7.2?

2011-11-01 Thread Max Bolingbroke
Hi Ganesh, On 1 November 2011 07:16, Ganesh Sittampalam gan...@earth.li wrote: Can anyone point me at the rationale and details of the change and/or suggest workarounds? This is my implementation of Python's PEP 383 [1] for Haskell. IMHO this behaviour is much closer to what users expect.For

Re: behaviour change in getDirectoryContents in GHC 7.2?

2011-11-01 Thread Max Bolingbroke
Hi John, On 1 November 2011 17:14, John Millikin jmilli...@gmail.com wrote: GHC 7.2 assumes Linux/BSD paths are text, which 1) silently breaks all existing code and 2) makes it impossible to fix within the given API. Please can you give an example of code that is broken with the new behaviour?

Re: behaviour change in getDirectoryContents in GHC 7.2?

2011-11-02 Thread Max Bolingbroke
On 1 November 2011 20:13, John Millikin jmilli...@gmail.com wrote: $ ghci-7.2.1 GHC import System.Directory GHC getDirectoryContents path-test [\161\165,\61345\61349,..,.] GHC readFile path-test/\161\165 world\n GHC readFile path-test/\61345\61349 *** Exception: path-test/: openFile:

Re: behaviour change in getDirectoryContents in GHC 7.2?

2011-11-02 Thread Max Bolingbroke
On 2 November 2011 10:03, Jean-Marie Gaillourdet j...@gaillourdet.net wrote: As far as I know, not all encodings are reversable. I.e. there are byte sequences which are invalid utf-8. Therefore, decoding and re-encoding might not return the exact same byte sequence. The PEP 383 mechanism

Re: behaviour change in getDirectoryContents in GHC 7.2?

2011-11-02 Thread Max Bolingbroke
On 2 November 2011 09:37, Max Bolingbroke batterseapo...@hotmail.com wrote: On 1 November 2011 20:13, John Millikin jmilli...@gmail.com wrote: $ ghci-7.2.1 GHC import System.Directory GHC getDirectoryContents path-test [\161\165,\61345\61349,..,.] GHC readFile path-test/\161\165 world\n

Re: behaviour change in getDirectoryContents in GHC 7.2?

2011-11-02 Thread Max Bolingbroke
On 2 November 2011 13:53, Max Bolingbroke batterseapo...@hotmail.com wrote: I think the only way to fix this last case in general is to fix iconv itself, so I'm going to see if I can get a patch upstream. Fixing it for people with UTF-8 locales should be enough for 99% of users, though. One

Re: behaviour change in getDirectoryContents in GHC 7.2?

2011-11-02 Thread Max Bolingbroke
On 2 November 2011 17:15, John Millikin jmilli...@gmail.com wrote: What package does this patch -- unix, directory, something else? The base package. The problem lay in the implementation of GHC.IO.Encoding.fileSystemEncoding on non-Windows OSes. Maybe I'm misunderstanding, but it sounds like

Re: behaviour change in getDirectoryContents in GHC 7.2?

2011-11-02 Thread Max Bolingbroke
On 2 November 2011 16:29, Ian Lynagh ig...@earth.li wrote: If I understand correctly, you use U+EF00-U+EFFF to encode the characters 0-255 when they are not a valid part of the UTF8 stream. Yes. So why not encode U+EF00 (which in UTF8 is 0xEE 0xBC 0x80) as U+EFEE U+EFBC U+EF80, and so on?

  1   2   >