RE: [darcs-users] How to develop on a (GHC) branch with darcs

2010-12-09 Thread Simon Peyton-Jones
| thoroughly exhausted. Even when Darcs was in a far
| less advanced state than it is in now, the conclusion seemed
| to be that the best interests of the Haskell community at
| large are served by remaining with Darcs. So it would be a bit
| strange if this branching issue, which is a serious issue
| currently but will likely become a non-issue in a few months time,
| triggers GHC to abandon Darcs.

Let's not go overboard here.  Iavor was expressing his frustration with using 
Darcs, and that is useful information for the Darcs devs to have, so they know 
where to focus their efforts.  Already this thread has generated new useful 
information.  For example, Iavor knows about --skip-conflicts, and I know that 
things might be better in months not years.  Neither of us knew those things 
before.

For GHC, we have two strong incentives to stick with Darcs.  First, we use it 
at the moment and there'd be a lot of hoo-ha to change.  Second, Darcs is 
written by people in our community, and GHC is a big customer, so I for one 
am keen to be supportive.

But we don't want to discourage people who'd like to help with GHC either.  For 
example, here is one response to the thread, from Tim Middleton:

| For the record, I can say that as a Haskell fan and someone who's using 
| Haskell at work (for small tools and projects), and as someone who'd like 
| to contribute to GHC (especially to the cross-compiler effort), having to 
| work with darcs is a very frustrating. 

The more everyone can do to understand what the frustration is, and to describe 
workflows that make it as easy as possible, the better.

Simon

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


Re: [darcs-users] How to develop on a (GHC) branch with darcs

2010-12-09 Thread Simon Marlow

On 08/12/2010 17:39, Yitzchak Gale wrote:


Some of those are already in the works, and all except possibly
(5) are known to be within reach. So the answer is yes, this
problem is now on the verge of being solved in Darcs.


I think that might be a little overoptimistic.  The fundamental problem 
with darcs is that nobody understands the semantics.  Until there's a 
proper semantics that people can understand, I don't think the problems 
with merging and conflicts can really be fixed.  Even if the semantics 
can be nailed down, there are some difficult UI issues to solve.


We're not moving to v2 patches right now because we have enough 
experience with v1 to know how to avoid the bugs, but I'm less sure we 
could avoid the bugs in v2.  To the darcs folk: do you think this is 
unfounded paranoia?



On the other hand, I suppose GHC HQ can't afford to have
a revolt on their hands. So if the majority of people doing the
actual work on GHC want to change to git and are willing to put
in the effort to make the change, it will probably happen regardless.


Opinion on whether we should switch seems to be pretty evenly split at 
the moment (personally I'm agnostic).  Besides that, the main stumbling 
block is that the GHC tree consists of about 20 repos, with different 
maintainers, so making it so that a GHC developer only needs to use one 
VC tool could be tricky.


Cheers,
Simon

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


Re: New codegen failing test-cases

2010-12-09 Thread Simon Marlow

On 09/12/2010 04:42, Edward Z. Yang wrote:

Final status report for tonight, before I crash in bed;
I've managed to make it compile all the way to hoopl.
It seems like hoopl doesn't typecheck anymore? I haven't
been following the typechecker changes too closely so
some guidance would be appreciated.

libraries/hoopl/src/Compiler/Hoopl/Util.hs:190:37:
 Could not deduce (e ~ block C C)
   from the context (NonLocal block, LabelsPtr e)
   `e' is a rigid type variable bound by
   the type signature for `postorder_dfs_from_except'
 at libraries/hoopl/src/Compiler/Hoopl/Util.hs:179:43
 In the first argument of `get_children', namely `block'
 In the first argument of `vchildren', namely `(get_children block)'
 In the expression:
   vchildren (get_children block) cont' acc (setInsert id visited)

libraries/hoopl/src/Compiler/Hoopl/Util.hs:220:41:
 Could not deduce (e ~ block C C)
   from the context (NonLocal block, LabelsPtr e)
   `e' is a rigid type variable bound by
   the type signature for `preorder_dfs_from_except'
 at libraries/hoopl/src/Compiler/Hoopl/Util.hs:217:42
 In the first argument of `get_children', namely `b'
 In the first argument of `children', namely `(get_children b)'
 In the first argument of `unVM', namely
   `(children (get_children b))'

libraries/hoopl/src/Compiler/Hoopl/Util.hs:256:45:
 Couldn't match type `O' with `C'
 In the first argument of `addTargets', namely `b'
 In the expression: addTargets b setEmpty
 In an equation for `entryTargets':
 entryTargets (JustO b) = addTargets b setEmpty
make[1]: *** [libraries/hoopl/dist-install/build/Compiler/Hoopl/Util.o] Error 1
make: *** [all] Error 2


Yes, this is about where I got to with my merge.  The type errors are 
triggered by the move to MonoLocalBinds in the new type checker, and can 
be solved by adding type signatures to the appropriate places in Hoopl. 
 You might be able to get some help from GHC by using NoMonoLocalBinds 
with -fwarn-missing-local-sigs.


Cheers,
Simon

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


New flag in GHC 7.0.1: --with-rtsopts

2010-12-09 Thread Simon Marlow
It seems we forgot to mention in the 7.0.1 release notes that there's a 
new compile-time flag, --with-rtsopts.  From the documentation:



4.16.8. Linker flags to change RTS behaviour

GHC lets you exercise rudimentary control over the RTS settings for any 
given program, by using the -with-rtsopts linker flag. For example, to 
set -H128m -K1m, link with -with-rtsopts=-H128m -K1m.




Cheers,
Simon

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


Re: [darcs-users] How to develop on a (GHC) branch with darcs

2010-12-09 Thread Jean-Marie Gaillourdet
Hi Simon,

Simon Peyton-Jones simo...@microsoft.com writes:

 | known problem with darcs with no obvious solution.  For me, switching
 | GHC to git would certainly be a win.

 I have personal experience of git, because I co-author papers with git users. 
 I am not very technologically savvy, but my failure rate with git is close to 
 100%.  Ie I can do the equivalent of 'pull' or 'push' but I fail at 
 everything else with an incomprehensible error message.  Maybe I just need 
 practice (or more diligence), but I really don't understand git's underlying 
 model, despite trying, and reading several tutorials.  If anyone has a 
 favourite how to understand git doc, do point me at it.

I've felt the same for quite some time. Therefore I used to prefer
mercurial, because of its way more consistent user interface. But my
view has changed after I've seen this [1] introduction of magit [2] an
emacs git user interface. Now, I feel at least capable of working with
git in emacs. 


[1] http://vimeo.com/2871241
[2] http://philjackson.github.com/magit/

Cheers,
  Jean-Marie


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


MonoLocalBinds and hoopl

2010-12-09 Thread Edward Z. Yang
Hello all,

Here's an experience report for porting hoopl to manage MonoLocalBinds.  The
Compiler.Hoop.XUtil module has a rather interesting (but probably common) style 
of code
writing, along the lines of this:

fbnf3 (ff, fm, fl) block = unFF3 $ scottFoldBlock (ScottBlock f m l cat) block
where f n = FF3 $ ff n
  m n = FF3 $ fm n
  l n = FF3 $ fl n
  FF3 f `cat` FF3 f' = FF3 $ f' . f

f, m, l and cat are polymorphic functions that are only used once in the
main expression, and are floated outside to improve readability.  However, when
MonoLocalBinds is turned on, these all become monomorphic and the definitions
fail.  In contrast, this (uglier) version typechecks:

fbnf3 (ff, fm, fl) block = unFF3 $ scottFoldBlock (ScottBlock (FF3 . ff) (FF3 . 
fm) (FF3 . fl) (\(FF3 f) (FF3 f') - FF3 $ f' . f)) block

One suggestion that I had was that we should generalize local bindings that
are only used once, but Marlow pointed out that this would make the typechecker
more complex and I probably would agree.

As a userspace developer, I have two options:

1. Bite the bullet and put in the polymorphic type signatures (which
   can be quite hefty)
2. Inline the definitions
3. Move the polymorphic functions into the global namespace

(3) and (2) are not so nice because it breaks the nice symmetry between these
definitions, which always define f, m, l for the many, many definitions in
Hoopl of this style.

Cheers,
Edward

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


Re: New codegen failing test-cases

2010-12-09 Thread Ian Lynagh
On Wed, Dec 08, 2010 at 11:31:19PM -0500, Edward Z. Yang wrote:
 Ian, I'd love a little guidance with this patch:
 
 Thu Oct 21 13:08:53 BST 2010  Ian Lynagh ig...@earth.li
   * Use takeUniqFromSupply in emitProcWithConvention
   We were using the supply's unique, and then passing the same supply to
   initUs_, which sounds like a bug waiting to happen.
 {
 hunk ./compiler/codeGen/StgCmmMonad.hs 607
 -; let (offset, entry) = mkEntry (mkBlockId $ uniqFromSupply us) 
 conv args
 -  blks = initUs_ us $ lgraphOfAGraph $ entry * blocks
 +; let (uniq, us') = takeUniqFromSupply us
 +  (offset, entry) = mkEntry (mkBlockId uniq) conv args
 +  blks = initUs_ us' $ lgraphOfAGraph $ entry * blocks
 }
 
 The new codegen has this hunk instead:
 
 ; let (offset, entry) = mkCallEntry conv args
   blks = initUs_ us $ lgraphOfAGraph $ entry * blocks
 
 and it's not clear to me if this circumvents the previous bug
 or mkCallEntry needs to be modified to expose the new supply.

The problem was that us was being used twice. If it's now only used
once then no problem.


Thanks
Ian


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


Re: [darcs-users] How to develop on a (GHC) branch with darcs

2010-12-09 Thread Ganesh Sittampalam

On Thu, 9 Dec 2010, Simon Marlow wrote:


On 08/12/2010 17:39, Yitzchak Gale wrote:


Some of those are already in the works, and all except possibly
(5) are known to be within reach. So the answer is yes, this
problem is now on the verge of being solved in Darcs.


I think that might be a little overoptimistic.  The fundamental problem with 
darcs is that nobody understands the semantics.  Until there's a proper 
semantics that people can understand, I don't think the problems with merging 
and conflicts can really be fixed.  Even if the semantics can be nailed down, 
there are some difficult UI issues to solve.


We're not moving to v2 patches right now because we have enough experience 
with v1 to know how to avoid the bugs, but I'm less sure we could avoid the 
bugs in v2.  To the darcs folk: do you think this is unfounded paranoia?


Sadly, no.


On the other hand, I suppose GHC HQ can't afford to have
a revolt on their hands. So if the majority of people doing the
actual work on GHC want to change to git and are willing to put
in the effort to make the change, it will probably happen regardless.


Opinion on whether we should switch seems to be pretty evenly split at the 
moment (personally I'm agnostic).  Besides that, the main stumbling block is 
that the GHC tree consists of about 20 repos, with different maintainers, so 
making it so that a GHC developer only needs to use one VC tool could be 
tricky.


My feeling is that a bridge should be quite feasible and would offer those 
contributors who want it the opportunity to do their GHC development in 
git and only use darcs when submitting their final changes or when working 
in unbridged repos. I'm not too familiar with the structure of the GHC 
repo but I suspect that only a few of the subrepos are big or active 
enough that darcs is really painful.


Cheers,

Ganesh

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


Re: New codegen failing test-cases

2010-12-09 Thread Edward Z. Yang
Here is the new set of failing test-cases on the shiny new branch.
I should stick the merged branch somewhere; any suggestions?

4030(normal)
4221(normal)
IndTypesPerf(normal)
T1969(normal)
T3064(normal)
T3294(normal)
T3736(normal)
T3807(normal)
T4003(normal)
cgrun016(normal)
cgrun045(normal)
cgrun051(normal)
dph-primespj-fast(normal)
dph-quickhull-fast(normal)
dsrun005(normal)
dsrun007(normal)
dsrun008(normal)
exceptionsrun001(normal)
exceptionsrun002(normal)
ffi021(normal)
simplrun010(optc)
strun002(optc)

Edward

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


Re: New codegen failing test-cases

2010-12-09 Thread Edward Z. Yang
Ok, looking at 4030, which is this simple program:

main = do tid - block $ forkIO $ let x = x in x
  killThread tid

It segfaults in stg_BLACKHOLE_info when attempting to
dereference... something (I haven't quite figured out
what yet; what's usually stored in 0x4(%esi) on 32-bit x86
when entering _info blocks?)

0x822a6e0 stg_CAF_BLACKHOLE_info:  jmp0x822a620 stg_BLACKHOLE_info
0x822a620 stg_BLACKHOLE_info:  mov0x4(%esi),%eax
0x822a623 stg_BLACKHOLE_info+3:test   $0x3,%eax
0x822a628 stg_BLACKHOLE_info+8:jne0x822a663 
stg_BLACKHOLE_info+67
0x822a62a stg_BLACKHOLE_info+10:   mov(%eax),%ecx -- SEGFAULT!

Registers right at the segfault:

eax0x0  0
ecx0x28 40
edx0xb7a7e008   -1213734904
ebx0x8289acc136878796
esp0xbfffcd98   0xbfffcd98
ebp0xb7a808f8   0xb7a808f8
esi0xb7a7f108   -1213730552
edi0xb7a7f10c   -1213730548
eip0x822a62a0x822a62a stg_BLACKHOLE_info+10

I believe this is because the code generator didn't write
out the value to the heap, as seen comparing the correct and incorrect
C-- (irrelevant stack/heap overflow checks elided):

Correct:

Hp = Hp + 8;
if (Hp  I32[BaseReg + 92]) goto coY;
I32[Hp - 4] = stg_CAF_BLACKHOLE_info;
I32[Hp + 0] = I32[BaseReg + 96];
foreign ccall
  newCAF((BaseReg, PtrHint), (R1, PtrHint))[_unsafe_call_];
I32[R1 + 4] = Hp - 4;
I32[R1] = stg_IND_STATIC_info;
I32[Sp - 8] = stg_bh_upd_frame_info;
I32[Sp - 4] = Hp - 4;

Incorrect:

_r7::I32 = R1;
Sp = Sp + 4;
Hp = Hp + 8;
// outOfLine should follow:
// allocDynClosure
I32[Hp - 4] = stg_CAF_BLACKHOLE_info;
_cpa::I32 = Hp - 4;
// XXX: I32[Hp + 0] is never written!!
I32[Sp - 16] = _cpa::I32;
foreign ccall
  newCAF((BaseReg, PtrHint), (R1, PtrHint))[_unsafe_call_];
_cpa::I32 = I32[Sp - 16];
I32[R1 + 4] = _cpa::I32;
I32[R1] = stg_IND_STATIC_info;
_cpa::I32 = I32[Sp - 16]; // Hp - 4
I32[Sp - 8] = _cpa::I32;
I32[Sp - 12] = stg_upd_frame_info;

It's not clear to me where in the code generator to look to fix this though.
Any pointers?

Cheers,
Edward

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


Re: How to use llvm with ghc7?

2010-12-09 Thread Magicloud Magiclouds
On Wed, Dec 8, 2010 at 7:14 PM, Max Bolingbroke
batterseapo...@hotmail.com wrote:
 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 release onwards. Try upgrading LLVM to
 2.7 and see if it helps.

 Cheers,
 Max


Oh, yes. 2.8 works fine. Thank you.

-- 
竹密岂妨流水过
山高哪阻野云飞

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


Re: [darcs-users] How to develop on a (GHC) branch with darcs

2010-12-09 Thread Ganesh Sittampalam

On Wed, 8 Dec 2010, Stephen J. Turnbull wrote:


Ganesh Sittampalam writes:

 I think there are three things that can help with this problem:

 1) a darcs rebase command. This will give you a nice way to manage the
 workflow already discussed, and you won't have to squish everything
 through into a mega-patch. You'll still have to periodically abandon one
 branch for another though (but I think that's also the case with git
 rebase).

I'm not sure what you mean by abandon.


I mean the same as in the git world. The rebased patches have new 
identities, and if my ideas for tracking the relationship don't work out, 
they will have no relationship to the old patches.


[your very clear explanation of that snipped]


 I also have some hope, though this is more speculative, of offering
 a clean way of tracking the relationship between the old branch and
 the new branch so that any stray patches against the old branch can
 be cleanly rebased to the new branch later on.

As explained above, DAG-based VCSes like git can't do this cleanly
(that is one way of expressing the reason why rebase is severely
deprecated in some circles), and I don't think git will be able to do
so in the near future.  OTOH, if Darcs gets rebase but can't handle
this, I'd have to count that as a net minus.  Recombinant patching is
really what Darcs is all about IMO.


darcs rebase is essentially about giving up on the recombinant patching 
because that's not working out for whatever reason. It's primarily 
intended as an alternative to manually reapplying patches to new branches 
using diff-and-patch, which is something significant numbers of people 
have ended up having to do. People generally want/need to do this to avoid 
conflicts, because:


(a) darcs conflict handling can blow up, both because of exponential 
merges (primarily with v1 patches) and because of bugs


(b) the UI for dealing with conflicts isn't really that pleasant and in 
particular once you've resolved a conflict it's a little painful to see 
the overall effect of the conflict resolution together with the underlying 
patch



In practice, git rebase needs to be kept private to a single user, and
is impractical even if private, if the user has propagated the branch
to other local repositories.  Because git branching is so lightweight,
nobody really sees this as a big problem; throwaway branches are used
all the time as interim steps in many operations (eg, git stash).
Darcs branches, on the other hand, are much more heavyweight (modulo
the work you propose on colocated branches, but that's farther away
than rebase is).

IMHO YMMV.  But I strongly recommend you think carefully about this.
Analogies to git rebase are a trap here.  It's implemented differently
and used to solve different problems from the way rebase is proposed
for use in Darcs.


My understanding is that one of the main uses for git rebase is for 
cleaning up history prior to submission. In that regard I think there's 
a substantial overlap with what darcs rebase is intended for.


Thanks for the detailed comments.

Ganesh

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