Well, it doesn't quite have the same drawbacks as submodules, because our solution places a burden
only on someone who wants to recover a particular repository state, rather than on everyone doing
development.
I think it's worth keeping an eye on submodules in case they fix the gotchas in the U
My stance is that it is possibly better if we do not try to include a
one-size-fits-it-all record system into the language, but if the
language provided support for basic things that almost all record
system *libraries* would need.
Agreed. To the extent that such libraries could be improved
by
I am unsure which of this list of proposals you are referring to. The
URL you quote is this
http://hackage.haskell.org/trac/haskell-prime/wiki/FirstClassLabels
That sounds familiar, I think I wrote that when I was younger;-)
but it doesn't seem to actually contain a design, merely some options
You are misunderstanding what 'undecidable instances' does.
s/undecidable/incoherent/g
Claus
GHC wants to solve the constraint (D Foo beta) where beta is
as-yet-unconstrained type variable. It finds that one instance *matches*
(by instantiating only the instance declaration, not the constra
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 existing tickets now (#4510),
which could turn into a real mess really quickly, if the currently known
spam account
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 existing tickets now (#4510),
which could turn into a real mess really quickly, if the currently known
spam account
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.
What happens after the merges? Does one maintain the branches
somehow, or do
We can't even do this reliably with darcs. Several times I've tried to
unpull one of Simon's patches to work around a bug, and the dependencies
end up being more than just the textual dependencies. Then I have to
fall back to unpulling by date, which is what git would do. And then
sometimes
The main advantages to darcs are that it can manipulate the sequence of
patches better than git.
The main advantage of git is that every version is accurately named. If
two people have a commit with a given hash, they will have exactly the
same files and history.
I've been wondering about this
scion-server mimics a GHCi command line, of sorts. scion-server
is used very successfully to syntax-highlight the Eclipse editor,
show a source's outline, provide type information when hovering
over a name, and provide completions.
That's not the problem, per se. Let's say I'm hovering over a
Hello, I'm the maintainer for EclipseFP, which involves using the scion
library and the GHC API to provide IDE functionality. I have a little
issue
that no doubt stems from me not understanding the GHC API well, and I
would
be grateful for any light on the matter.
A meta-comment: the GHC API
> instance (EmbedAsChild m c, m1 ~ m) => EmbedAsChild m (XMLGenT m1 c)
That looked to me like a long-winded way of saying:
> instance (EmbedAsChild m c) => EmbedAsChild m (XMLGenT m c)
Unless I'm missing something?
These two instances are not equivalent:
- the first matches even if m and
Please test as much as possible; bugs are much cheaper if we find them
before the release!
Could you please have a look at the documentation issues
in the Windows installer before release? Points 4-6 in:
http://hackage.haskell.org/trac/ghc/ticket/4292
(documentation links in haddock and
Message-
| From: glasgow-haskell-users-boun...@haskell.org [mailto:glasgow-haskell-
| users-boun...@haskell.org] On Behalf Of Claus Reinke
| Sent: 22 September 2010 16:05
| To: GHC users
| Subject: Re: GHCi 6.12.3 stdout redirection works for :type, but not for
| :info
|
|
| > The problem is that
The problem is that my code for redirecting the output
of GHCi commands still works for things like :type, but
no longer for things like :info (this is my smallest example
demonstrating the effect).
The difference seems to be between commands that use
old-style GHCi output (works with redirect
Dear GHCi / IO experts,
I'm encountering some odd GHCi behaviour with some
old ghci.conf code of mine (used to work in older GHCis).
The problem is that my code for redirecting the output
of GHCi commands still works for things like :type, but
no longer for things like :info (this is my smallest
Johan:
I started writing a manual traversal of the RenamedSource AST
(as I want qualified names) but I thought I check if I'm going
about this right before I spend all the time required to write
the traversal for the whole AST.
Manual traversal code on ASTs tends to consist mainly
of boilerpl
Indeed, though I don't think this is the case, because I get lots of
lag even when no logs are written.
In the part you deleted I mentioned one source of lag that does
not disappear when no logs are written, and a way of using
profiling cost centers to track down other sources (the ones
I mention
On Sat, Jun 19, 2010 at 8:46 AM, Claus Reinke
wrote:
I put the simple version at
http://hpaste.org/fastcgi/hpaste.fcgi/view?id=26329#a26329
This one displays much better performance with DList + Writer.Strict
than List + StrictWriter so I guess it's not too surprising. However,
*somethin
I put the simple version at
http://hpaste.org/fastcgi/hpaste.fcgi/view?id=26329#a26329
This one displays much better performance with DList + Writer.Strict
than List + StrictWriter so I guess it's not too surprising. However,
*something* is still generating a lot of lag
Some lag is to be expe
I have been experimenting some more with environments for lab work for
an FP intro course. One thing students tend to have difficulty with in
the initial labs are the error messages including type classes, or any
kind of more general type than they expected. I am trying to work around
this, by sup
Hallo Kiel!-)
we are trying to use the GHC API for a source-to-source transformation
on Haskell programs. The result of parsing and typechecking a module
enables us to apply the transformation, but writing the transformed
module back using the pretty printer (Outputable) generates invalid
Haske
one thing that isn't so good is that we lack a library of GHC-related
papers. ideally, i just have to add a link to some GHC/Papers#GC that
contains everything ever published about this topic.
http://haskell.org/haskellwiki/Research_papers#Categories
http://haskell.org/haskellwiki/Research_pape
I got frustrated with vi tags not working after some unrelated code is
edited in a source file. Moreover non-exported top level declarations
were not available in vi tags file. Here is an attempt to fix it:
http://www.hck.sk/users/peter/pub/ghc/betterCTags.patch
I'm all in favour of ctags impr
{-# LANGUAGE MultiParamTypeClasses #-}
module A where
class Foo a b where foo :: a -> b
instance Foo Bool Int where
foo True = 1
foo False = 0
module B where
import A
bar :: (Foo a b) => [a] -> [b]
bar = map foo
I can load B.hs into GHCi and call bar with
|What you describe is exactly how I would *want* things to work. It's
|nice to hear my wishes echoed from a user perspective. :-)
actually, I was describing how things seem to work right now.
|> Only MultiParamTypeClasses does (and neither extension is needed in the
|> module defining 'f', if 'T
just a few comments from a user (who would really, really, like to be
able to define pragma collections, so that he doesn't have to switch
on half a dozen separate extensions every time;-).
The following toy program requires MultiParamTypeClasses OR
FlexibleContexts in order to be accepted by GH
One thing that wasn't available when this discussion was last active
is 'mapException' (btw, similar to 'catch'/'catches', a 'mapExceptions'
would be useful).
so for mere traces, dynamic seems to be the choice (with an option of
pseudo-cbv or the real dynamic stack).
I don't know what pseudo
If you don't want to move from absolute paths for non-core packages,
the current system should just work, right?
Yes.
The current system being the $topdir one.
Though it also allows for the possibility of relocatable sets of
packages that are not installed relative to the compiler. But more
Here are the +RTS -xc and mapException outputs together (when I
remove the mapError annotations, only the first <..> is printed, so
that is the part to focus on, the rest is confusion)
Actually, it looks as if the implementation of mapException modifies
the stack that +RTS -xc prints. Not entir
One thing that wasn't available when this discussion was last active
is 'mapException' (btw, similar to 'catch'/'catches', a 'mapExceptions'
would be useful). For instance, appended below is the example from that
wiki page, with entirely local transformations to add source locations
and to use tha
But if you're registering global packages that are installed outside of
the GHC tree then you wouldn't register them using relative paths. I'm
not saying everything must use relative paths.
Please don't move your windmills while I'm fighting them!-)
If you don't want to move from absolute paths
Currently, there seem to be $topdir and $httptopdir.
And I can't see a justification for there being two.
Each variable provides an indirection that decouples the installation
from one source of _independent_ relocations (btw, I've always imagined
that it is called 'http' instead of 'html' to a
> It turns out that those variables are there to allow relocation, in
> fact $topdir is expanded by
> Distribution.Simple.GHC.getInstalledPackages, it seems that
> $httptopdir has been overlooked.
> I'd be tempted to say that it's ghc-pkg dump/describe responsibility
> to expand those vars instead
Not part of the core libs, so these are slowly disappearing from the
extralibs bundled shipped with GHC (in favour of the platform bundle).
As the stable/head buildbots (as opposed to stable fast/head fast) are
becoming less and less useful and cared for in the context of GHC,
could they perha
the mapException approach
I'm afraid it won't work as you hope for functions that return lazy data
structures. The 'evaluate' implicit in mapException only catches
top-level errors/exceptions, like 'seq' and not like 'deepSeq'.
Have a look at 'firstLetters2' in the example I provided. Perha
What is really frustrating is that GHC has the machinery to do this
trivially (RULES, soon core2core phase plugins as well), only that this machinery gets applied
when source location information is no longer available, so it is useless for this problem:-(
I'd be happy to be proven wrong in thi
JHC has had this for a while, but it calls the pragma 'SRCLOC_ANNOTATE'.
It is actually mentioned on this page:
http://hackage.haskell.org/trac/ghc/wiki/ExplicitCallStack
Yes, I know, but the discussion on that page wanted to go beyond this
(possibly triggered by your demonstration that
The second solution requires QuasiQuotes, so I do not know. If I would
want to compile with a different compiler it would break. If srcloc can be
defined as a simple token (not requiring special extensions at places where
it is used) then I could define it to an empty string in some low level mo
I was looking for something which works in optimized builds too.
{-# OPTIONS_GHC -fno-ignore-asserts #-}
overrides the -O default setting -fignore-asserts.
I know I could do it with preprocessor or (I think) template haskell too
but these tools seem to heavy for such a simple goal.
Given ho
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
count i x step xs = step xs count (i+1) (i+1)
test xs = iter xs count 0 0
More specifically, section "2.2.2 Moving GHC Around" indicates that
the entire GHC tree can be freely moved around "just by copying the
c:/ghc/ghc-version directory" (although it is necessary "to fix up the
links in 'Start/All Programs/GHC/ghc-version'" if this is done);
however, this information
I'm not sure I'd want -Wall on by default (though being -Wall clean is
very good). But exhaustive pattern checking might well help out a lot of
people coming from untyped backgrounds.
http://ocaml.janestreet.com/?q=node/64
Ron's also wondering why exhaustive pattern checking isn't on ?
Anyon
do print ("READ START",x) ; res <- readFile x ; print ("READ STOP",x)
; return res
Unless you've defined your own version of 'readFile', to mean read
entire file now, the first 'print' is optimistic and the second 'print' is a
lie.
readFile calls openFile >>= hGetContents. It's the openFile th
do print ("READ START",x) ; res <- readFile x ; print ("READ STOP",x)
; return res
Unless you've defined your own version of 'readFile', to mean read
entire file now, the first 'print' is optimistic and the second 'print' is a
lie.
Claus
do print ("WRITE START",x); writeFile x src ; print ("
I see, so I guess the short answer is "there's just no easy way to do it for
now". Perhaps I'll write a Perl script that will do it for me while waiting
for a standardized solution. The issue of source/binary version mismatches
shouldn't be a problem as long as the source I copy over is the same
I was going to suggest following the source links in the Haddock pages,
until I saw your motivation:
First, I had originally installed a binary distribution and then tried to
compile another program (a Haskell editor) that recommended I have source
available for all libraries, since it would be
I can't see any issues with this version of the spec.
Thanks. From the silence, we seemed to have lost the innocent
bystanders? Anyway, for those who haven't noticed, there is now
a feature request ticket (for that good feeling of closing it when this
is finally implemented;-) as well as a wik
Simon Peyton-Jones simonpj at microsoft.com :
PS: in the case that no one gets around to creating such a patch,
creating a ticket that documents the problem and points to the needed
specialisations would be a start
Was this created? I could not find something about it in the GHC trac.
Yes: h
Ticket is http://hackage.haskell.org/trac/ghc/ticket/3126 .
Sorting by constructor tag is perfectly safe when done right.
You can read about how to do it in my 1985 FPCA paper or in Simon's book.
I did, long ago. I learned functional programming by implementing a
small functional language, us
So a first comment on this. I spoke too soon, ghc clearly has a bug here.
It shouldn't reorder those matches against literals like that.
I suggest you report that bug, because, as you say, it violates the H98 report.
It would be nice if we could first reach a common understanding, so
that I can
Sorry to be the odd man out - perhaps an example will help to
clarify my reading of the language definition.
I find this "reordering" discussion somewhat nonsensical.
Haskell specifies top-to-botton, left-to-right matching.
This specifies exactly which tests that have to be made and in what orde
I don't find ordering of patterns appealing, I find it scary! I order
my patterns according to the semantics I desire, and then additionally
by what looks pretty. I'd like it if whatever cleverness GHC can work
is used rather than requiring me to think. If the order of patterns is
to become import
| very long list than the Cons-before-Nil order I wanted), but it is
| very frustrating if I'm not even given the chance because GHC
| sorts the alternatives, not even according to its own interpretation
| of branching performance, but completely arbitrarily!-)
All I'm saying is that GHC has neve
When you tried switching Nil and Cons, did you try it on many examples?
For a single example a 2-3% could be easily attributed to random
effects like different instruction cache hit patterns. If you get it
consistently over several programs then it seems likely to mean
something, but I'm not sure
Indeed GHC does not attempt to retain the order of alternatives, although
a) it might be possible to do so by paying more attention in numerous places
b) GHC may do so already, by accident, in certain cases
That adds even more unpredictability. One thing that I don't want
whenever I have to car
[commented cmm and asm elided - thanks, though! Some examples
like this would be helpful in the commentary (or are they there and
I've not yet seen them?)]
|I guess this is a long winded way of saying that the branches are being
|ordered such that the fall though case is not the one that you put
009 at 12:16 AM, Claus Reinke wrote:
I just noticed that GHC (6.11.20090320) seems to compile both
f (a:b:c) =
f (a:[]) = f [] =
and
f [] = f (a:[]) = f (a:b:c) =
to something like (looking at Core, but writing source)
f x = case x of { [] -> ..; (a:t) -> case t of { [] ->..; (b:c) ->..
I just noticed that GHC (6.11.20090320) seems to compile both
f (a:b:c) =
f (a:[]) =
f [] =
and
f [] =
f (a:[]) =
f (a:b:c) =
to something like (looking at Core, but writing source)
f x = case x of { [] -> ..; (a:t) -> case t of { [] ->..; (b:c) ->..}}
That doesn't seem right to me: if
Dear Simon*,
thanks for answering my concerns about -fvia-C replacement. Are these
answers somewhere in the ghc wiki, or perhaps they'd make a good basis
for a useful ghc blog post?
So, -fasm will soon be up to speed with -fvia-C in all cases, new native
backends are not more difficult than mo
{-# INLINE f PEEL n UNROLL m #-}
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 the ones
t
Recursion unfolding spec, 2nd attempt.
The main difference is to look at groups of mutually recursive
definitions as a whole, rather than trying to think about individual
definitions. That step actually seems sufficient to address most of
the shortcomings raised so far, such as avoiding runaway
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 peeling and unrolling is to
unfold a definition
{-# INLINE f PEEL n #-}
inline calls *into* recursive f (called loop peeling for loops)
{-# INLINE f UNROLL m #-}
inline recursive calls to f *inside* f (called loop unrolling for
loops)
{-# INLINE f PEEL n UNROLL m #-}
combine the previous two
The problem here is that this only works
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 peeling and unrolling
is to unfold a definition
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 calls *into* recursive f (called loop peeling
The implementation I'm thinking of is basically trivial. You just add
the information gathered from the pragmas onto the Ids, then have a
dedicated core pass that looks at the pragmas and does it's
worker/wrapper thing. The technology to do peeling/unrolling is
trivial and there already examples i
That was one of my questions in the optimization and rewrite rules
thread: shouldn't -fvia-C be supported (as a non-default option)
for at least as long as the alternative isn't a clear win in all cases?
The trouble with supporting multiple backends is that the cost in terms of
testing and main
Yes - this is why my use of a kind of unrolling fixes concatMap for
streams, because GHC is able to specialise the "unrolled" function
body on a particular lambda abstraction. However, this is really a
somewhat seperate issue than plain unrolling, as we just want to be
able to /specialise/ recursi
So now, since we've gone to such effort to produce a tiny loop like, this,
can't we unroll it just a little?
it is worth unrolling this guy, so we get the win of both aggressive high level
fusion, and aggressive low level loop optimisations?
It might be useful to point out that the interaction
| | A quick grep shows almost no specialization at all for Word, or for
| | IntXX/WordXX (see below). Still, none of that seems to explain the
| | example repeated at the top of this message.
|
| We'd be delighted to apply suitable library patches.
PS: in the case that no one gets around to creat
its loop unroller on this guy haven't succeeded. -funroll-loops and
-funroll-all-loops doesn't touch it,
That's because the C produced by GHC doesn't look like a loop to GCC. This can be fixed but given
that we are moving away from -fvia-C anyway, it probably isn't worth doing.
That was on
import Data.Array.Vector
import Data.Bits
main = print . productU . mapU (*2) . mapU (`shiftL` 2) $ replicateU (1 :: Int)
(5::Int)
and turns it into a loop like this:
$wfold :: Int# -> Int# -> Int#
$wfold =
\ (ww_sWX :: Int#) (ww1_sX1 :: Int#) ->
case ww1_sX1
A while ago, I needed lots of fairly small positive numbers,
together with a small number of flags for each, so I thought
I'd switch from Int to Word, and map the flags to bits.
Since there are few guarantees about the size of a Word (or Int), surely
it would be better to choose a definitely siz
Here is a trivial example with drastic difference between
T = Int and T = Word (~2.5x here):
main = print $ foldl' (+) 0 [1..1::T]
..
GHC.Prim.word2Int#
(GHC.Prim.and#
(GHC.Prim.int2Word# wild13_XbE)
(GHC.Prim.int2Word# y#_a4EZ))
Is that likely to cos
Looking at prelude/PrelRules.hs has reminded me of an old
conundrum: if I switch from Int to Word, should I expect any
performance differences?
A while ago, I needed lots of fairly small positive numbers,
together with a small number of flags for each, so I thought
I'd switch from Int to Word, an
but if we unfold a loop combinator at compile time, GHC's
normal optimizations can take over from there):
http://www.haskell.org/pipermail/haskell-cafe/2009-February/056241.html
Just a note - there is a solution that doesn't require Template
Haskell which I use in my own code. Here is a sketch:
| II is where I'd like to be able to distinguish variables, constants,
| and complex expressions in the left-hand sides of RULES, and
| I and III are where I'd like control over the rewrite strategy, as
| in strategy combinators.
I'm deep in icfp submissions, so no time to reply properly.
Okay
Okay, I've found a combination of incantations that happens to
work, but only for this particular example. So this does not solve
the original questions, and I'm still interested in suggestions. But it
does give a concrete example of what I'd like to be able to do (or
better, what GHC should be
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
blindspot (it usually doesn't unfold recursive
Q: is the information that --print-libdir returns available programmatically
to Haskell code?
$ ghc --print-libdir
C:\ghc\ghc-6.11.20090118
$ ghc -e GHC.Paths.libdir
"C:\\ghc\\ghc-6.11.20090118"
$ ghc -e ':browse GHC.Paths'
docdir :: FilePath
ghc :: FilePath
ghc_pkg ::
This is just a quick summary of our plans for GHC 6.10.2.
..
If there is a bug not in that list that is causing you major problems,
then please let us know.
Hi Ian,
I noticed that http://hackage.haskell.org/trac/ghc/ticket/1502
keeps getting pushed back (now 2 years old!).
Perhaps the summary
Defined in Data.Maybe
data Int = GHC.Base.I# GHC.Prim.Int#-- Defined in GHC.Base
Details how to do it are in tutorial from Claus Reinke:
http://www.haskell.org/pipermail/haskell-cafe/2007-September/032260.html
Understanding all the possibilities and limitations of ghci scripting
may take
Core types (in particular CoreExpr) are not instances of Show. They are
instances of Outputable, which allows them to be pretty printed.
However, this pretty printing is good to view the structure of the
expression that the CoreExpr represents, but doesn't show the structure
of the CoreExpr itself
manually when debugging. Most of my expriments are related to the
tickets I filled in: checking whether I can have some cheap workarourd
till they are implemented or whether they actually help as much as I hope.
That means that for anything more complicated I need access directly to
the repres
Is it possible to run ghci monad actions from ghci command line somehow?
For example: I would like to check whether "it" variable is of type
Bool and whether it is True using normal Haskell code (i.e. not using
ghci commands starting with colon like :type :print).
What I was searching for in
antecedent :: Rule -> Expression
antecedent r = case r of
..
Gc{} -> let x = grspe r in r `seq` Tm r
..
This looks wrong. The idea was to replace
Tm (grspe r)
(where the selection expression is put into Tm unevaluated) with
let x = grspe r
in x `seq` Tm x
ie,
Adding finalizers to arbitrary objects was useful for the memo table
application we had in mind when weak pointers were introduced, but for all
the other applications I've come across since then, we really want to add
finalizers to objects whose lifetimes are under programmer control. Notice
h
Peter Hercek wrote:
Is there a way to redirect output of a ghci debugger command
so that I can process it with a (ghci) script before it is
displayed?
Claus had some GHCi macros for doing this sort of thing. Claus?
Sure, recorded here (sections 4/5, but the rest of the page should
also be
No, it's a real problem. If we retained all the variables in scope at
every breakpoint, GHCi would grow a whole bunch of space leaks. It's
pretty important that adding debugging shouldn't change the space behaviour
of the program. Of course, constant factors are fine, but we're talking
asymp
fun x y =
let f1 = ... (f2 x) ... -- f1 calls f2
f2 x = x * 2
in case x of
1 -> f2 0
_ -> f2 (f1 y)
g x = let z = (some complex computation) in z `div` x
main = print (g (fun 1 2))
This is a classical example of why laziness gets in the way of
debugging. Now, when (f2 0) gets fina
- when I'm at a break point, I'd really like to see the current scope
or, if that is too expensive, the next enclosing scope, in full
(not only would that tell me what instantiation of my code I'm in,
it would also seem necessary if I want to reconstruct what the
current expression is)
>> It is supposed to show only free variables in the selected expression.
I'm sure I had cases when I was able to access variables which were
not free in the selected expression but which would have been in
scope if used in the selected expression. The values available seemed
correct (contrar
I don't think I'm just speaking for myself when I say that pseq is
confusing and the docs similarly.
Given the type
a -> b -> b
we would assume that it is lazy in it's first arg and strict in the
..
I'm not quite sure what this distinction means, actually.
If I recall the issue correctly:
It's a shame this doesn't just work out of the box in an xterm, on
Debian at least. Perhaps we should consider switching to haskeline? Do
we know anything about how portable and complete that is?
If a haskell-based solution could be made to work, that would be
great - if you think that editline
Should I add a ticket?
Sounds good - and if you could attach a small example showing how Array
is faster that would be helpful too.
Ok, ticket is http://hackage.haskell.org/trac/ghc/ticket/2727 .
Hope I got the example right - the effect is clear, but with "functional"
DiffArray, it is way to
I keep wanting to use DiffArray as the natural functional solution to
single-threaded array use. But everytime I try, I get smacked over
the head with the actual performance figures. Sometimes, even plain
arrays are faster in a loop doing array updates, in spite of all the
copying involved. And w
I'm currently studying the use of overlapping instances, and I was
hoping to instrument GHC to produce some variety of list of instances
that overlapped. I haven't done any GHC hacking so far, so I'm not
entirely familiar with the code base. Does anyone have any guidance
on which modules I shoul
The basic problem here is that the version number of the network package
has not been bumped. ..
.. Of course that's not true here because the package has
changed without the version being bumped.
..
Indeed the only reason it's trying to rebuild it at all is because the
installed version has diffe
We've been using the cabal-install build reporting stuff to get more
detailed info on build failures with ghc-6.10 vs 6.8. cabal-install
generates these build-reports.log files and individual log files for
each build.
Since you do have the infrastructure set up: haddock is also changing
with ghc
1 - 100 of 246 matches
Mail list logo