Re: copyArray# bug

2012-10-09 Thread Roman Leshchinskiy
Herbert Valerio Riedel wrote: > Roman Leshchinskiy writes: > > > [...] > >> If I'm right then I would suggest not to use copyArray# and >> copyMutableArray# for GHC < 7.8. > > I've grepped today's > > http://hackage.haskell.org/cgi-bin/ha

Re: copyArray# bug

2012-10-09 Thread Roman Leshchinskiy
Johan Tibell wrote: > Hi, > > I did quite a bit of work to make sure copyArray# and friends get > unrolled if the number of elements to copy is a constant. Does this > still work with the extra branch? I would expect it to but I don't know. Does the testsuite check for this? Roman ___

Re: copyArray# bug

2012-10-08 Thread Roman Leshchinskiy
Simon Marlow wrote: > On 06/10/2012 22:41, Roman Leshchinskiy wrote: >> I've been chasing a segfault in the dev version of vector and I think I >> finally traced it to a bug in the implementation of copyArray# and >> copyMutableArray#. More specifically, I think emitSe

copyArray# bug

2012-10-06 Thread Roman Leshchinskiy
I've been chasing a segfault in the dev version of vector and I think I finally traced it to a bug in the implementation of copyArray# and copyMutableArray#. More specifically, I think emitSetCards in StgCmmPrim.hs (and CgPrimOp.hs) will sometimes fail to mark the last card as dirty because in

Re: Unpack primitive types by default in data

2012-02-17 Thread Roman Leshchinskiy
On 17/02/2012, at 17:51, Johan Tibell wrote: > On Fri, Feb 17, 2012 at 12:52 AM, Roman Leshchinskiy > wrote: >> I'm not convinced that this is a good idea because it doesn't treat all >> types equally. The comparison with Java is problematic, IMO, because in >>

Re: Unpack primitive types by default in data

2012-02-17 Thread Roman Leshchinskiy
Jean-Marie Gaillourdet wrote: > Hi, > > On 17.02.2012, at 09:52, Roman Leshchinskiy wrote: > >> Johan Tibell wrote: >>> >>> The worry is that reboxing will cost us, but I realized today that at >>> least one other language, Java, does this already toda

Re: Unpack primitive types by default in data

2012-02-17 Thread Roman Leshchinskiy
Johan Tibell wrote: > Hi all, > > I've been thinking about this some more and I think we should > definitely unpack primitive types (e.g. Int, Word, Float, Double, > Char) by default. > > The worry is that reboxing will cost us, but I realized today that at > least one other language, Java, does th

Re: Changes to Typeable

2012-02-14 Thread Roman Leshchinskiy
On 13/02/2012, at 11:10, Simon Peyton-Jones wrote: > | Should there perhaps be a NewTypeable module which could then be renamed > | into Typeable once it is sufficiently well established? > > I started with that idea, but there would be a 2-stage process: > * Step 1: (when PolyTypable becomes a

Re: Changes to Typeable

2012-02-12 Thread Roman Leshchinskiy
On 12/02/2012, at 03:21, Iavor Diatchki wrote: > PS: I wouldn't worry too much about breaking existing code, as long as > derived Typeable instances continue to work---I never provide custom > ones and, in fact, I think that GHC should no allow them or, at least, > give a stern warning when it see

Re: Changes to Typeable

2012-02-11 Thread Roman Leshchinskiy
On 12/02/2012, at 01:44, John Meacham wrote: > I am not so sure, adding type applications to the language seems > fairly radical and will change many aspects of the language. Something > like Proxy that can be expressed in relatively vanilla haskell and > some handy desugarings is much more attra

Re: Changes to Typeable

2012-02-11 Thread Roman Leshchinskiy
On 10/02/2012, at 23:30, John Meacham wrote: > something I have thought about is perhaps a special syntax for Proxy, like > {:: Int -> Int } is short for (Proxy :: Proxy (Int -> Int)). not sure whether > that is useful enough in practice though, but could be handy if we are > throwing > around ty

Re: Changes to Typeable

2012-02-11 Thread Roman Leshchinskiy
On 10/02/2012, at 16:03, Simon Peyton-Jones wrote: > Friends > > The page describes an improved implementation of the Typeable class, making > use of polymorphic kinds. Technically it is straightforward, but it > represents a non-backward-compatible change to a widely used library, so we > nee

Re: Unit unboxed tuples

2012-01-11 Thread Roman Leshchinskiy
On 11/01/2012, at 19:28, Dan Doel wrote: > Then I'm afraid I still don't understand the difference. Is it that > case in core always evaluates? So: > >case undefined of x -> ... > > blows up, while > >case (# undefined #) of (# x #) -> ... > > does not? Yes. > Also, if so, how is (co

Re: Two Proposals

2011-10-06 Thread Roman Leshchinskiy
Manuel M T Chakravarty wrote: > Roman Leshchinskiy: >> >> What data structures other than lists do we want to construct using list >> literals? I'm not really sure what the use cases are. > > Parallel arrays! (I want to get rid of our custom syntax.) Why? Don&#x

RE: Two Proposals

2011-10-05 Thread Roman Leshchinskiy
Simon Peyton-Jones wrote: > > I'm not sure if this plan would support [("fred",45), ("bill",22)] :: Map > String Int. Probably not. Maybe that's a shortcoming... but such Maps > are a rather surprising use of list literals. What data structures other than lists do we want to construct using lis

Re: Two Proposals

2011-10-04 Thread Roman Leshchinskiy
Yitzchak Gale wrote: > Roman Leshchinskiy wrote: >> In general, if we are going to overload list literals then forcing the >> desugaring to always go through lists seems wrong to me. There are >> plenty >> of data structures where that might result in a significant pe

Re: Two Proposals

2011-10-04 Thread Roman Leshchinskiy
George Giorgidze wrote: > > This extension could also be used for giving data-parallel array literals > instead of the special syntax used currently. Unfortunately, it couldn't. DPH array literals don't (and can't really) go through lists. In general, if we are going to overload list literals the

Addr# field in ForeignPtr

2011-06-01 Thread Roman Leshchinskiy
Hi all, GHC defines ForeignPtr as: data ForeignPtr a = ForeignPtr Addr# ForeignPtrContents -- we cache the Addr# in the ForeignPtr object, but attach -- the finalizer to the IORef (or the MutableByteArray# in -- the case of a MallocPtr). The aim of the representation

Re: Broken ghc-7.0.3/vector combination?

2011-04-20 Thread Roman Leshchinskiy
Daniel Fischer wrote: > > Further investigation of the sorting code in vector-algorithms revealed > no bugs there, and if the runtime was forced to keep a keen eye on the > indices, by replacing unsafeRead/Write/Swap with their bounds-checked > counterparts or by 'trace'ing enough of their uses, th

Re: Faster Array#/MutableArray# copies

2011-03-01 Thread Roman Leshchinskiy
Simon Marlow wrote: > On 01/03/2011 11:55, Roman Leshchinskiy wrote: > >> >> Would it, in theory, be possible to have an "unpacked" array type? That >> is, could we have constructors for which the length of the closure is >> determined dynamically at r

Re: Faster Array#/MutableArray# copies

2011-03-01 Thread Roman Leshchinskiy
Simon Marlow wrote: > > For small arrays like this maybe we should have a new array type that > leaves out all the card-marking stuff too (or just use tuples, as Roman > suggested). Would it, in theory, be possible to have an "unpacked" array type? That is, could we have constructors for which the

Re: Faster Array#/MutableArray# copies

2011-02-18 Thread Roman Leshchinskiy
Johan Tibell wrote: > > * Could we use built-in compiler rules to catch array copies of known > length and replace them with e.g. unrolled loops? My particular use case > involves copying small arrays (size: 1-32). Ideally this should be as fast > as copying a tuple of the corresponding size but I'

Re: Faster Array#/MutableArray# copies

2011-02-18 Thread Roman Leshchinskiy
Max Bolingbroke wrote: > On 18 February 2011 01:18, Johan Tibell wrote: > > It seems like a sufficient solution for your needs would be for us to > use the LTO support in LLVM to inline across module boundaries - in > particular to inline primop implementations into their call sites. LLVM > would

Re: Injective type families?

2011-02-16 Thread Roman Leshchinskiy
On 14/02/2011, at 21:28, Conal Elliott wrote: > Is there a way to declare a type family to be injective? > > I have > > > data Z > > data S n > > > type family n :+: m > > type instance Z :+: m = m > > type instance S n :+: m = S (n :+: m) You could prove it :-) class Nat n where induct :

Re: Can't make sense of newArray# docs

2011-01-18 Thread Roman Leshchinskiy
On 18/01/2011, at 22:18, Johan Tibell wrote: > The docs for newArray# states: > > "Create a new mutable array of specified size (in bytes), in the > specified state thread, with each element containing the specified > initial value." The docs are wrong. > I'm trying to implement > the following

Re: Behavior of the inliner on imported class methods

2011-01-18 Thread Roman Leshchinskiy
Have you tried adding another (dummy) method to the class? GHC used to have problems with optimising single-method classes in the past. Roman On 18 Jan 2011, at 10:33, José Pedro Magalhães wrote: > Hello all, > > I fail to understand the behavior of the inliner in the following example: > >

Re: RFC: migrating to git

2011-01-13 Thread Roman Leshchinskiy
On 12 Jan 2011, at 23:31, "Edward Z. Yang" wrote: > Excerpts from Roman Leshchinskiy's message of Wed Jan 12 18:20:25 -0500 2011: >> How would we get the current functionality of darcs-all pull? Is it even >> possible? > > Here is the rebase-y workflow. Thank you making things clearer! >> >

Re: RFC: migrating to git

2011-01-12 Thread Roman Leshchinskiy
On 12/01/2011, at 22:22, Iavor Diatchki wrote: > When you issue the command "git submodule update", you are telling git to > advance the sub-module repo to the "expected version" (i.e., where the > pointer points to). The reason this does not happen automatically is that > you might have also

Re: RFC: migrating to git

2011-01-12 Thread Roman Leshchinskiy
On 12/01/2011, at 09:22, Simon Marlow wrote: > On 11/01/2011 23:11, Roman Leshchinskiy wrote: >> >> A quick look at the docs seems to indicate that we'd need to do >> >> git pull >> git submodule update >> >> which doesn't loo

Re: RFC: migrating to git

2011-01-11 Thread Roman Leshchinskiy
On 11/01/2011, at 22:20, Simon Marlow wrote: > On 11/01/11 21:57, Roman Leshchinskiy wrote: >> IMO, darcs-all works pretty well. I don't think I ever really had >> problems with missing library patches. > > I often see problems where someone has done 'darcs pull&#x

Re: RFC: migrating to git

2011-01-11 Thread Roman Leshchinskiy
On 11/01/2011, at 21:41, Iavor Diatchki wrote: > If GHC and the libraries on which it depends were in git (migrated, or > mirrored), then we could use git sub-modules to track the dependencies > between changes to GHC and changes to the libraries. > > Roughly, the workflow would be like th

Re: RFC: migrating to git

2011-01-11 Thread Roman Leshchinskiy
On 11/01/2011, at 16:14, Tony Finch wrote: > On Mon, 10 Jan 2011, Roman Leshchinskiy wrote: >> >> It also seems to make finding buggy patches rather hard. > > Have a look at `git bisect`. I'm aware of git bisect. It doesn't do what I want. I usually have a pret

Re: RFC: migrating to git

2011-01-10 Thread Roman Leshchinskiy
On 10/01/2011, at 13:27, Simon Marlow wrote: > On 10/01/2011 13:02, Max Bolingbroke wrote: >> However, I remember the last time this came up there were some issues >> that might make migration painful. From the top of my head: >> >> 1) Some people expressed concern that they would have to use two

Re: SpecConstr number of specializations (-fspec-constr-count)

2010-11-25 Thread Roman Leshchinskiy
On 25/11/2010, at 10:33, José Pedro Magalhães wrote: > Is this a bug, or is the value of spec-constr-count being manipulated in some > way for certain passes? spec-constr-count decreases for nested specialisations. For instance, if spec-constr-count is 6 and SpecConstr generates 2 specialisatio

Re: Loop optimisation with identical counters

2010-11-05 Thread Roman Leshchinskiy
On 06/11/2010, at 02:27, Sebastian Fischer wrote: > Interesting. This approach requires `f` to be inlined into its call site in > order to eliminate the redundant argument. This is different from the > proposal to provide a specialized version of `f` (where the arguments are > combined) which c

Re: Loop optimisation with identical counters

2010-11-05 Thread Roman Leshchinskiy
On 06/11/2010, at 00:28, David Peixotto wrote: > Yes, the LLVM code has Sp, Hp, Base all annotated as noalias. I believe that > Sp, Hp, and Base should never alias, but a (boxed) R1 should always alias > with either Sp or Hp. I had a hard time determining exactly how LLVM uses the > noalias ann

Re: Loop optimisation with identical counters

2010-11-05 Thread Roman Leshchinskiy
On 05/11/2010, at 23:22, David Peixotto wrote: > I spent some time looking at the code generated for llvm and the optimizations > it can apply. There were quite a bit of details to examine and I wrote it up > as blog post here: > http://www.dmpots.com/blog/2010/11/05/optimizing-haskell-loops-with-

Re: Loop optimisation with identical counters

2010-11-03 Thread Roman Leshchinskiy
LLVM doesn't eliminate the counters. FWIW, fixing this would improve performance of stream fusion code quite a bit. It's very easy to do in Core. Roman On 3 Nov 2010, at 10:45, Christian Hoener zu Siederdissen wrote: > Thanks, I'll do some measurements on this with ghc7. > > Gruss, > Christi

Re: Loop optimisation with identical counters

2010-11-03 Thread Roman Leshchinskiy
On 3 Nov 2010, at 10:45, Christian Hoener zu Siederdissen wrote: > Thanks, I'll do some measurements on this with ghc7. > > Gruss, > Christian > > On 11/02/2010 01:23 PM, Simon Marlow wrote: >> On 02/11/2010 08:17, Christian Höner zu Siederdissen wrote: >>> Hi, >>> >>> is the following prob

Re: Massive slowdown in mwc-random after switching to use of primitive package

2010-07-12 Thread Roman Leshchinskiy
On 11/07/2010, at 22:49, Bryan O'Sullivan wrote: > On Sun, Jul 11, 2010 at 12:59 AM, Dan Doel wrote: > >> You're using GHC 6.12.x presumably? > > That's right. > >> There are known performance problems with >> using abstract PrimMonads in that version (and, actually, just using IO as >> well

Re: Custom reducing functions for DPH

2010-05-10 Thread Roman Leshchinskiy
On 11/05/2010, at 05:29, Edward Z. Yang wrote: > Some of the important primitives offered by Data Parallel Haskell are > reduction primitives such as sumP and prodP, which take a data parallel > array and reduce it to a single value. I was wondering what the current > capabilities for end-users i

Re: -O vs. -O2

2010-05-09 Thread Roman Leshchinskiy
On 09/05/2010, at 07:50, Duncan Coutts wrote: > On Wed, 2010-05-05 at 21:24 +1000, Roman Leshchinskiy wrote: >> Whenever I do cabal sdist on one of my projects, I get this warning: >> >> Distribution quality warnings: >> 'ghc-options: -O2' is rarely needed. C

Re: -O vs. -O2

2010-05-09 Thread Roman Leshchinskiy
On 07/05/2010, at 19:53, Simon Marlow wrote: > On 05/05/2010 12:24, Roman Leshchinskiy wrote: >> Whenever I do cabal sdist on one of my projects, I get this warning: >> >> Distribution quality warnings: 'ghc-options: -O2' is rarely needed. >> Check that it

-O vs. -O2

2010-05-05 Thread Roman Leshchinskiy
Whenever I do cabal sdist on one of my projects, I get this warning: Distribution quality warnings: 'ghc-options: -O2' is rarely needed. Check that it is giving a real benefit and not just imposing longer compile times on your users. This finally got me curious and I did a nofib run to compare -O

Re: Parallel Haskell: 2-year project to push real world use

2010-05-04 Thread Roman Leshchinskiy
On 04/05/2010, at 18:37, Christian Höner zu Siederdissen wrote: > * Roman Leshchinskiy [04.05.2010 10:02]: >> On 04/05/2010, at 11:10, Christian Höner zu Siederdissen wrote: >> >>> Here http://www.tbi.univie.ac.at/newpapers/Abstracts/98-06-009.ps.gz is >>> a

Re: Parallel Haskell: 2-year project to push real world use

2010-05-04 Thread Roman Leshchinskiy
On 04/05/2010, at 11:10, Christian Höner zu Siederdissen wrote: > * Ben Lippmeier [04.05.2010 02:21]: >> >> You can certainly create an array with these values, but in the provided >> code it looks like each successive array element has a serial dependency on >> the previous two elements. How

Re: Parallel Haskell: 2-year project to push real world use

2010-05-03 Thread Roman Leshchinskiy
On 04/05/2010, at 09:21, Christian Höner zu Siederdissen wrote: > Hi, > > on that topic, consider this (rather trivial) array: > > a = array (1,10) [ (i,f i) | i <-[1..10]] where > f 1 = 1 > f 2 = 1 > f i = a!(i-1) + a!(i-2) > > (aah, school ;) > > Right now, I am abusing vector in ST by do

Re: Parallel Haskell: 2-year project to push real world use

2010-05-03 Thread Roman Leshchinskiy
On 03/05/2010, at 22:04, Johan Tibell wrote: > On Mon, May 3, 2010 at 11:12 AM, Simon Peyton-Jones > wrote: > | Does this mean DPH is ready for abuse? > | > | The wiki page sounds pretty tentative, but it looks like it's been awhile > | since it's been updated. > | > | http://www.haskell.org/has

index*OffAddr

2010-04-21 Thread Roman Leshchinskiy
In package vector, primitive vectors (the ones that Data.Vector.Unboxed is built on top of) are represented as follows (ByteArray and friends are wrappers for various GHC primitives provided by package primitive): data Vector a = Vector Int -- offset into the ByteArray

Re: Can't install Criterion package on ghc ..

2010-04-14 Thread Roman Leshchinskiy
On 15/04/2010, at 02:55, John Lato wrote: > The problem isn't with criterion itself, but with vector-algorithms. > The vector library relies heavily on type families, which have dodgy > support in ghc-6.10. As a matter of fact, this particular problem is easy to fix by adding a couple of type si

Re: Feedback request: priority queues in containers

2010-03-17 Thread Roman Leshchinskiy
On 17/03/2010, at 03:16, Louis Wasserman wrote: > I'm not willing to do this sort of typeclass wrapper thing, primarily because > nothing else in containers does -- even though we might have a Mapping type > class that handles both IntMap and Map, we don't. > > I'm inclined to let that design c

Re: Removing/deprecating -fvia-c

2010-02-17 Thread Roman Leshchinskiy
On 17/02/2010, at 18:37, Isaac Dupree wrote: > LLVM and GCC are open-source projects that are improving over time... is > there any particular reason we expect GCC to have poor numeric performance > forever? Past experience :-) GCC has been around for a while and if it doesn't optimise numeric

Re: Removing/deprecating -fvia-c

2010-02-16 Thread Roman Leshchinskiy
On 15/02/2010, at 04:58, Don Stewart wrote: > Do we have the blessing of the DPH team, wrt. tight, numeric inner loops? FWIW, I don't think we even use -fvia-C when benchmarking. In general, -fvia-C is a dead end wrt numeric performance because gcc just doesn't optimise well enough. So even if

Re: Inliner behaviour - tiny changes lead to huge performance differences

2009-11-13 Thread Roman Leshchinskiy
On 13/11/2009, at 18:04, Bryan O'Sullivan wrote: main = do args <- getArgs forM_ args $ \a -> do s <- B.readFile a let t = T.decodeUtf8 s print (T.length t) The streamUtf8 function looks roughly like this: streamUtf8 :: OnDecodeError -> ByteString -> Stream Char streamUtf8 onEr

Re: Really bad code for single method dictionaries?

2009-03-27 Thread Roman Leshchinskiy
On 27/03/2009, at 18:32, Don Stewart wrote: I don't think this is still the case. Roman, do you remember? Hmm, not really. I recall that there was some sort of problem which I didn't have time to investigate then but it's been so long... Roman __

Re: Loop unrolling + fusion ?

2009-03-08 Thread Roman Leshchinskiy
On 07/03/2009, at 09:26, Claus Reinke wrote: My preferred spec would be roughly {-# NOINLINE f #-} as now {-# INLINE f #-}works as now, which is for non-recursive f only (might in future be taken as go-ahead for analysis-based recursion unfolding) {-# INLINE f PEEL n #-} inline c

Re: Loop unrolling + fusion ?

2009-02-28 Thread Roman Leshchinskiy
On 01/03/2009, at 04:49, Don Stewart wrote: 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 to

Re: Strictness in data declaration not matched in assembler?

2008-10-16 Thread Roman Leshchinskiy
On 16/10/2008, at 21:34, Simon Peyton-Jones wrote: For strict *constructors*, on the other hand, we *do* guarantee to evaluate the argument before building the constructor. We generate a wrapper thus wC = \ab. case a of { a' -> C a' b } (Remember 'case' always evaluates in Core.) So

Re: Some initial results with DPH

2008-09-23 Thread Roman Leshchinskiy
On 23/09/2008, at 14:59, Roman Leshchinskiy wrote: dotp :: [:Int:] -> [:Int:] -> Int dotp v w = I.sumP [: (I.*) x y | x <- v, y <- w :] The way the vectoriser works at the moment, it will repeat the array w (lengthP v) times, i.e., create an array of length (lengthP v * leng

Re: Some initial results with DPH

2008-09-22 Thread Roman Leshchinskiy
Hi Austin, first of all, thanks a lot for taking the time to report your results! On 23/09/2008, at 11:48, Austin Seipp wrote: * The vectorise pass boosts compilation times *a lot*. I don't think this is exactly unwarrented since it seems like a pretty complicated transformation, but while m

Re: Build system idea

2008-08-28 Thread Roman Leshchinskiy
On 29/08/2008, at 01:31, Simon Marlow wrote: Roman Leshchinskiy wrote: On 28/08/2008, at 23:59, Simon Marlow wrote: The important thing about Cabal's way of specifying dependencies is that they can be made sound with not much difficulty. If I say that my package depends on base==3.

Re: Build system idea

2008-08-28 Thread Roman Leshchinskiy
On 29/08/2008, at 03:11, Ian Lynagh wrote: On Fri, Aug 29, 2008 at 12:57:59AM +1000, Roman Leshchinskiy wrote: On 28/08/2008, at 21:10, Ian Lynagh wrote: On Thu, Aug 28, 2008 at 10:27:22AM +0100, Simon Peyton-Jones wrote: PS: concerning your last point, about "separating the Simple

Re: Build system idea

2008-08-28 Thread Roman Leshchinskiy
On 28/08/2008, at 23:59, Simon Marlow wrote: The important thing about Cabal's way of specifying dependencies is that they can be made sound with not much difficulty. If I say that my package depends on base==3.0 and network==1.0, then I can guarantee that as long as those dependencies are

Re: Build system idea

2008-08-28 Thread Roman Leshchinskiy
On 28/08/2008, at 21:10, Ian Lynagh wrote: On Thu, Aug 28, 2008 at 10:27:22AM +0100, Simon Peyton-Jones wrote: PS: concerning your last point, about "separating the Simple build system", that might indeed be good. Indeed, the GHC plan described here http://hackage.haskell.org/trac/ghc/wik

Re: Build system idea

2008-08-28 Thread Roman Leshchinskiy
On 28/08/2008, at 19:27, Simon Peyton-Jones wrote: Duncan, I'm not following every detail here, but it's clear that you have some clear mental infrastructure in your head that informs and underpins the way Cabal is. Cabal "takes the view that...", has "principles", and "is clearly partiti

Re: Version control systems

2008-08-15 Thread Roman Leshchinskiy
On 16/08/2008, at 00:12, Ian Lynagh wrote: On Fri, Aug 15, 2008 at 11:12:20AM +1000, Manuel M T Chakravarty wrote: Moreover, as I wrote a few times before, some reasons for switching in the first place are invalidated by not having the core libraries in git, too. For example, one complain

Re: Build system idea

2008-08-14 Thread Roman Leshchinskiy
On 14/08/2008, at 18:01, Simon Marlow wrote: Roman Leshchinskiy wrote: But that is precisely my (other) point. A lot of that work is really unnecessary and could be done by Cabal since it only or mostly depends on the package information. Instead, it is implemented somewhere in

Re: Build system idea

2008-08-14 Thread Roman Leshchinskiy
On 14/08/2008, at 06:32, Duncan Coutts wrote: On Wed, 2008-08-13 at 22:47 +1000, Roman Leshchinskiy wrote: Again, I'm not arguing against a build system written in Haskell. I'd just like it to be completely separated from Haskell's packaging system. In particular, "

Re: Build system idea

2008-08-13 Thread Roman Leshchinskiy
On 13/08/2008, at 20:34, Simon Marlow wrote: Roman Leshchinskiy wrote: Of course there should be a standard build system for simple packages. It could be part of Cabal or a separate tool (for which Cabal could, again, act as a preprocessor). GHC is a special case: we already need a build

Re: Build system idea

2008-08-13 Thread Roman Leshchinskiy
On 13/08/2008, at 17:47, Simon Marlow wrote: Roman Leshchinskiy wrote: On 12/08/2008, at 20:11, Simon Marlow wrote: - Extract the code from Cabal that generates Makefiles, and treat it as part of the GHC build system. Rather than generating a Makefile complete with build rules, we

Re: Build system idea

2008-08-12 Thread Roman Leshchinskiy
On 12/08/2008, at 20:11, Simon Marlow wrote: - Extract the code from Cabal that generates Makefiles, and treat it as part of the GHC build system. Rather than generating a Makefile complete with build rules, we generate a Makefile that just has the package-specific metadata (list of mod

Re: Version control systems

2008-08-09 Thread Roman Leshchinskiy
On 10/08/2008, at 05:38, Don Stewart wrote: Instead, if we just use ubiquitous, common tools -- like git -- for everything, we minimise the pain for people, and sit firmly in the mainstream of open source. While I agree with this in general, I'm not sure it really applies to vcs (especially

Re: Version control systems

2008-08-09 Thread Roman Leshchinskiy
On 10/08/2008, at 14:40, Manuel M T Chakravarty wrote: Personally, I am more than happy to stay with darcs, too, but my understanding was that at least the Simons decided that we are going to move from darcs to git. All I am saying is that whatever vcs ghc uses, you need to be able to *ea

Re: Build system woes

2008-07-30 Thread Roman Leshchinskiy
On 30/07/2008, at 23:46, Simon Marlow wrote: We can talk about the general issues on IRC. But I thought I'd answer a few of the specific questions quickly: Thanks, Simon! Roman Leschinskiy wrote: I don't think I understand how GHC itself is built any longer, either. What does cabal-bin

Re: Generalized phase control for GHC

2008-07-07 Thread Roman Leshchinskiy
Simon Peyton-Jones wrote: 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? Fairly. I've explained why in a follow-up to Max's message. Also, why do you want phase aliases

Re: Generalized phase control for GHC

2008-07-05 Thread Roman Leshchinskiy
Max Bolingbroke wrote: 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 pipeli

Re: Generalized phase control for GHC

2008-07-05 Thread Roman Leshchinskiy
Max Bolingbroke wrote: 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

Re: Generalized phase control for GHC

2008-07-04 Thread Roman Leshchinskiy
Hi Max, sorry for replying so late, I've completely forgotten about this. I would be interested in feedback on the design before the implementation is complete and in the wild. I'm especially interested in hearing if you believe that loss of support for numeric phase numbers > 2 is a problem, a

Re: Building ndp Problem

2008-06-09 Thread Roman Leshchinskiy
Dominic Steinitz wrote: I think I have things working now but the "make" system seems to have problems. I followed the instructions here: http://www.haskell.org/haskellwiki/Data_Parallel_Haskell/PackageNDP but got the messages below. Sorry, I haven't checked whether doing "make" works in the

Re: desperately seeking RULES help

2008-06-09 Thread Roman Leshchinskiy
Simon Peyton-Jones wrote: The -fno-method-sharing flag was supposed to be a bit experimental, which is why it takes the cheap-and-cheerful route of being a static flag. (Only dynamic flags can go in OPTIONS_GHC.) It's dynamic in the HEAD, see Mon May 19 19:59:56 PDT 2008 Roman Leshchi

Re: scope of header files

2008-03-16 Thread Roman Leshchinskiy
Jason Dusek wrote: Ross Paterson <[EMAIL PROTECTED]> wrote: Jason Dusek wrote: Why doesn't GHC know about const? Because the Ptr type doesn't indicate const-ness (perhaps it should). If it did, could we read constant strings without unsafePerformIO? That would be unsound since a cons

Re: H98 Text IO

2008-02-26 Thread Roman Leshchinskiy
Duncan Coutts wrote: On Wed, 2008-02-27 at 00:31 +1100, Roman Leshchinskiy wrote: Duncan Coutts wrote: So here is a concrete proposal: * Haskell98 file IO should always use UTF-8. * Haskell98 IO to terminals should use the current locale encoding. Personally, I'd find

Re: H98 Text IO

2008-02-26 Thread Roman Leshchinskiy
Duncan Coutts wrote: So here is a concrete proposal: * Haskell98 file IO should always use UTF-8. * Haskell98 IO to terminals should use the current locale encoding. Personally, I'd find this deeply surprising. I don't care that much what locale gets used for I/O (if it m