7.6.1 RC1 panic "coVarsOfTcCo:Bind"

2012-08-21 Thread Ganesh Sittampalam
Hi,

I'm getting the panic below when building darcs 2.8 with GHC 7.6. It'll
take some effort to cut it down or give repro instructions for an
uncut-down version (I needed to hack a lot of underlying packages to be
able to even get as far as doing this build), so could someone confirm
that it's worth it before I do so? I can't spot anything already
reporting this in trac.

Cheers,

Ganesh

ghc.exe: panic! (the 'impossible' happened)
  (GHC version 7.6.0.20120810 for i386-unknown-mingw32):
coVarsOfTcCo:Bind
cobox{v a6Czs} [lid]
  = cobox{v a6CTr} [lid] `cast`
({tc r1Dyc}
main:Darcs.Witnesses.Ordered.FL{tc r1Dy1}


prim{tv ty} [tv])>
 ghc-prim:GHC.Types.~{(w) tc 31Q}
main:Darcs.Test.Patch.WithState.WithState{tc r1LL8}
   
(Sym cobox{v a6CSH} [lid])
   
{tc r1Dyc} main:Darcs.Witnesses.Order
ed.FL{tc r1Dy1}


prim{tv ty} [tv]>)

Please report this as a GHC bug:  http://www.haskell.org/ghc/reportabug

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


Long compilation times when profiling a large CAF

2012-08-21 Thread Conal Elliott
I'm looking for help with crazy-long compile times when using GHC with
profiling. A source file at work has a single 10k line top-level
definition, which is a CAF. With -prof auto-all or an explicit SCC,
compilation runs for 8 hours on a fast machine with the heap growing to
13GB before being killed. Without profiling, it compiles in a few minutes.

The big CAFs are auto-generated and not of my making, so I'm hoping for a
solution other than "stop making big CAFs".

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


Re: ANNOUNCE: GHC 7.6.1 Release Candidate 1

2012-08-21 Thread Páli Gábor János
Hi there,

On Sun, Aug 12, 2012 at 8:57 PM, Ian Lynagh  wrote:
> We are pleased to announce the first release candidate for GHC 7.6.1:
>
> http://www.haskell.org/ghc/dist/7.6.1-rc1/
>
> This includes the source tarball, installers for 32bit and 64bit
> Windows, and bindists for amd64/Linux, i386/Linux, amd64/OSX and
> i386/OSX.

Could somebody please apply my patch (see attached) so the FreeBSD
builder clients could produce working binaries again?


Thanks,
Gabor


0001-Fix-build-with-FreeBSD-versions-earlier-than-9.0-as-.patch
Description: Binary data
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


RE: Holes in GHC

2012-08-21 Thread Simon Peyton-Jones
Can you give me read/write access to your github repo?  I'm simonpj on github.  
That way I can add comments/questions in code, and generally clean up.
It would make things easier if you could merge with HEAD so that I don't have 
to mess around moving libraries back in time.

--
You've put "LANGUAGE Holes" in TcErrors which means I can't bootstrap.

--
You have this in your patch file, which can't be right
+  | CHoleCan {
+  cc_ev   :: CtEvidence,
+  cc_hole_ty  :: TcTauType, -- Not a Xi! See same not as above
+  cc_depth:: SubGoalDepth-- See Note [WorkList]
+}
+
 \end{code}
 
 \begin{code}
@@ -933,6 +940,9 @@ ctPred (CTyEqCan { cc_tyvar = tv, cc_rhs = xi })
 ctPred (CFunEqCan { cc_fun = fn, cc_tyargs = xis1, cc_rhs = xi2 }) 
   = mkTcEqPred (mkTyConApp fn xis1) xi2
 ctPred (CIrredEvCan { cc_ty = xi }) = xi
+ctPred (CHoleCan { cc_flavor = fl, cc_hole_ty = xi })
+  = xi
+

since c_flavor isn't a field of CHoleCan.

---

| The 3 currently remaining issues:
| 
| - Free type variables are not tidied consistently. For every one of
| these hole warnings, the same TidyEnv is reused, without taking the
| updates from the other holes into account. I'm pretty sure I know where
| this happens and how I could fix it.

This should be easy.
* TcErrors.reportUnsolved uses tyVarsOfWC to find the free type variables
  of unsolved constraints
* It then uses tidyFreeTyVars to assign them names
* And that gives an env used in tidying.

So it should just work.  I hope you are letting the various 'tidy' calls in 
TcErrors do the work.

| - What I thought would be the local environment doesn't actually seem
| to be it. The holes store in their origin the result of `getLclTypeEnv'
| at their location, but as the Note [Bindings with closed types] says,
| the TopLevelFlag of these don't actually differentiate the top level
| from the non-top level bindings. I think it would be more helpful to
| only show the non-top level bindings at the hole's location, any hints
| about how to obtain just these would be appreciated.

In this context "local" means "this module" rather than "not top level".  Use 
isExternalName to distinguish top-level things from nested things.




| - The holes do not have very accurate source location information, like
| some other errors have. The hole has its origin, ("test2.hs:3:16"), but
| somehow not something like: "In the expression: folder _ x _, In an
| equation for `test': test x = foldr _ x _". Help with how that is
| supposed to work would also be appreciated.

That's odd.  Every Wanted constraint has a WantedLoc (TcRnTypes), which 
includes a [ErrCtxt], which is that stack of "In ..; In... " stuff you see.

Code looks plausible.  



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


Re: Request for comments on proposal for literate programming using markdown

2012-08-21 Thread Edward Kmett
Ultimately your best bet to actually get something integrated will be to
find something that minimizes the amount of work on the part of GHC HQ.

I don't think *anybody* there is interested in picking up a lot of fiddly
formatting logic and carving it into stone.

They might be slightly less inclined to shut the door in your face if the
proposal only involved adding a few hooks in the AST for exposing
alternative documentation formats, which would enable you to hook in via a
custom unlit or do something like how haddock hooks in, but overall, if it
involves folks at GHC HQ maintaining a full markdown parser I think they
will (and should) just shrug and move on.

The resulting system would be slightly less work for you, but would only
see any improvements delayed a year between GHC releases, and then the
community can't adopt the improvements in earnest for another year after
that. This is *not* an encouraging development cycle, and doesn't strike me
as a recipe for a successful project.

As proposed, this would distract some pretty core resources from working on
core functionality and I for one am heavily against it as I understand what
has been proposed so far.

Haddock works with some fairly simple extensions to GHC's syntax tree. If
your proposal was modified so that it just requires a few hooks or worked
with the existing haddock hooks in the syntax tree, then while I would
hardly be a huge proponent due the fragmentation issues about how to deal
with documentation, I would at least cease to be actively opposed.

-Edward

On Tue, Aug 21, 2012 at 7:45 AM, Philip Holzenspies
wrote:

> On 14 Aug 2012, at 07:48, Simon Hengel wrote:
> > Personally, still do not see the big benefit for all that work, and I'm
> > still somewhat worried that a mechanism that is not used by default (I'm
> > talking about unliting with an external command) may start to bit rot.
> > But as long as you are commit to keep `-pgmL` intact, I'm ok ;).
>
> A biggy that I had left out has just reoccurred to me. The very first
> reason for me to look at how unlitting and preprocessing is done in GHC
> was, because I was looking into what would be required for a refactoring
> engine (like haRe) to be based on the GHC API. Of course, at the moment,
> the API doesn't do anything with unlitting and preprocessing.
>
> > I think in the end it's best to go with the solution that works best for
> > GHC-HQ.
>
> Still hoping to hear from them ;)
>
> Regards,
> Philip
> ___
> Glasgow-haskell-users mailing list
> Glasgow-haskell-users@haskell.org
> http://www.haskell.org/mailman/listinfo/glasgow-haskell-users
>
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: Request for comments on proposal for literate programming using markdown

2012-08-21 Thread Philip Holzenspies
On 14 Aug 2012, at 07:48, Simon Hengel wrote:
> Personally, still do not see the big benefit for all that work, and I'm
> still somewhat worried that a mechanism that is not used by default (I'm
> talking about unliting with an external command) may start to bit rot.
> But as long as you are commit to keep `-pgmL` intact, I'm ok ;).

A biggy that I had left out has just reoccurred to me. The very first reason 
for me to look at how unlitting and preprocessing is done in GHC was, because I 
was looking into what would be required for a refactoring engine (like haRe) to 
be based on the GHC API. Of course, at the moment, the API doesn't do anything 
with unlitting and preprocessing.

> I think in the end it's best to go with the solution that works best for
> GHC-HQ.

Still hoping to hear from them ;)

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


Problem with default signatures

2012-08-21 Thread Jeroen Weijers
Hello,

I am trying to create some code involving type families and default signatures. 
I am getting a type error that I do not understand (as far as I can see the 
error is wrong).

I removed all code that doesn't contribute to the error:

> {-# LANGUAGE DeriveGeneric, UndecidableInstances, DefaultSignatures, 
> TypeOperators, GADTs, FlexibleContexts, TypeFamilies, FlexibleInstances #-}
> module Database.DSH.Problem where
> 
> import GHC.Generics
> 
> data Exp a where
>  UnitE :: Exp ()
>  ListE :: [Exp a] -> Exp [Exp a]
> 
> class GenericQA f where
>  type GRep f
>  type AltGRep f
>  type AltGRep f = [Exp (GRep f)]
>  gToExp :: f a -> Exp (GRep f)
>  emptyAlt :: Exp (AltGRep f)
>  default emptyAlt :: (AltGRep f ~ [Exp (GRep f)]) => Exp (AltGRep f)
>  emptyAlt = ListE [] 
> 
> instance GenericQA U1 where
>  type GRep U1 = ()
>  gToExp U1 = UnitE


This gives me the following type errors:

> Problem.hs:19:10:
>Couldn't match type `AltGRep f0' with `[Exp ()]'
>Expected type: AltGRep U1
>  Actual type: AltGRep f0
>Expected type: Exp (AltGRep U1)
>  Actual type: Exp (AltGRep f0)
>In the expression: (Database.DSH.Problem.$gdmemptyAlt)
>In an equation for `emptyAlt':
>emptyAlt = (Database.DSH.Problem.$gdmemptyAlt)
> 
> Problem.hs:19:10:
>Couldn't match type `GRep f0' with `()'
>Expected type: [Exp (GRep f0)]
>  Actual type: AltGRep f0
>In the expression: (Database.DSH.Problem.$gdmemptyAlt)
>In an equation for `emptyAlt':
>emptyAlt = (Database.DSH.Problem.$gdmemptyAlt)
>In the instance declaration for `GenericQA U1'

In this error the type variable f0 is mentioned but as far as I understand it f 
should have been instantiated to U1 and not to a variable f0. I've tried many 
variations on the default type signature for emptyAlt but haven't found any 
that doesn't result in this error. Can somebody explain what is going wrong 
here? 

Cheers,

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


RE: build failures when hiding non-visible imports

2012-08-21 Thread Simon Peyton-Jones
OK we're doing this for 7.6.  See 
http://hackage.haskell.org/trac/ghc/ticket/7167

| -Original Message-
| From: glasgow-haskell-users-boun...@haskell.org [mailto:glasgow-
| haskell-users-boun...@haskell.org] On Behalf Of Conrad Parker
| Sent: 21 August 2012 01:02
| To: John Lato
| Cc: glasgow-haskell-users@haskell.org
| Subject: Re: build failures when hiding non-visible imports
| 
| On 21 August 2012 07:36, John Lato  wrote:
| >> From: Brandon Allbery 
| >>
| >> On Sat, Aug 18, 2012 at 9:10 PM, Carter Schonwald <
| >> carter.schonw...@gmail.com> wrote:
| >>
| >>> meaning: flags for treating it as a warning vs as an error?
| >>> (pardon, i'm over thinking ambiguity in phrasing).
| >>> if thats the desired difference, that sounds good to me!
| >>>
| >>
| >> I would expect it means that, having demoted it to a warning, we
| >> would have -fwarn-hiding-no-target / -fno-warn-hiding-no-target (or
| >> whatever we call
| >> it) as with all other warnings.
| >>
| >> For warning vs. error, it seems to me that should be more general:
| >> perhaps taking any of the -f[no-]warn-* options and replacing "warn"
| with "err".
| >
| > Yes.  To be concrete, this is what I would like to see.
| >
| > In a statement of the form:
| >
| >   import Module hiding (x)
| > where Module doesn't export x, ghc should report a warning instead of
| > an error
| >
| > This warning would be enabled/disabled by the usual flags (I like
| > -fwarn-unused-import-hiding, but -fwarn-hiding-no-target is good
| too).
| >
| > The warning would be on by default.
| >
| > If a user wants this to be an error, I think -Werror should be
| > sufficient.  I am unable to think of any case where hiding a
| > non-visible symbol would lead to errors on its own, and any errors
| > likely to occur in tandem with this issue already have their own,
| more
| > helpful, error conditions (e.g. symbols not in scope, symbols in a
| > qualified import list not visible).
| >
| > I agree with Ganesh's point that it would be beneficial to have this
| > available for ghc-7.6.1 if possible.
| 
| +1
| 
| and it must be a warning (not error) by default, or else we will need
| to tell everyone to use "cabal install --ghc-option=-fwarn-unused-
| import-hiding" to install lots of packages on hackage (currently
| including things like HTTP and gtk2hs-buildtools, which are pulled in
| by many packages).
| 
| Also, if this remains an error by default then it will become a
| sensible coding style to simply avoid using import hiding, to avoid
| build errors that will occur when some other library removes an
| interface (that you have explicitly marked as unused ...)
| 
| Conrad.
| 
| ___
| Glasgow-haskell-users mailing list
| Glasgow-haskell-users@haskell.org
| http://www.haskell.org/mailman/listinfo/glasgow-haskell-users



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