Re: Missing definitions of associated types

2016-02-18 Thread David Feuer
You make a good point about people who use overlapping instances deserving
whatever they get (I'd personally love to see that whole mess removed and
replaced with something less intrusive). The bit that most severely breaks
my intuition here is that under normal, well-behaved circumstances, every
instance of a class with associated data has its own distinct associated
type(s). That is, there is a one-to-many relationship between instances and
types. When a definition is missing, that breaks, and the relationship may
become many-to-many. I suppose we may need to settle for this as long as
overlapping instances in their present form are around.

On Feb 18, 2016 12:49 PM, "Reid Barton"  wrote:

> Well, I see your point; but you also can't define a
>
> On Thu, Feb 18, 2016 at 12:00 PM, David Feuer 
> wrote:
>
>> It seems to be that a missing associated type definition should be an
>> error, by default, rather than a warning. The current behavior under those
>> circumstances strikes me as very strange, particularly for data families
>> and particularly in the presence of overlapping.
>>
>
>> This compiles with just a warning because Assoc Char *falls through* to
>> the general case. WAT? This breaks all my intuition about what associated
>> types are supposed to be about.
>>
>>
> Well, I see your point; but you also can't give a definition for Assoc
> Char in the Foo Char instance, because open data family instances are not
> allowed to overlap. So if failing to give a definition for an associated
> data family is an error, then it's impossible to use overlapping instances
> with classes that have associated data families. Is that your intention?
>
> I don't have a strong opinion here. I'm mildly inclined to say that people
> using overlapping instances have already signed themselves up for weird
> things happening, and we may as well let them do whatever other weird
> things they want.
>
> Regards,
> Reid Barton
>
___
ghc-devs mailing list
ghc-devs@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs


RE: Build failures with -DDEBUG

2016-02-18 Thread Simon Peyton Jones
Very helpful thanks.  TcCoercibleFail is known to time out (for decent reasons) 
with –DDEBUG (see comments in the dsource file)

I’l look into the PatSyn thing

Simon

From: Thomas Miedema [mailto:thomasmied...@gmail.com]
Sent: 18 February 2016 18:41
To: Simon Peyton Jones ; ghc-devs@haskell.org
Subject: Build failures with -DDEBUG

Simon,

the commits you pushed today don't validate with -DDEBUG.

Unexpected failures:

   patsyn/should_compile  MoreEx [exit code non-0] (normal)

   patsyn/should_compile  T11224b [exit code non-0] (normal)

   polykinds  MonoidsTF [exit code non-0] (normal)

   polykinds  T11480b [exit code non-0] (normal)

   polykinds  T11523 [exit code non-0] (normal)

   typecheck/should_fail  TcCoercibleFail [stderr mismatch] (normal)



TcCoercibleFail timed out, and the others all hit the following debug assert:


=> T11224b(normal) 2510 of 5029 [0, 0, 0]
Compile failed (status 256) errors were:
ghc-stage2: panic! (the 'impossible' happened)
  (GHC version 8.1.20160218 for x86_64-unknown-linux):
  ASSERT failed!
  CallStack (from HasCallStack):
  assertPprPanic, called at compiler/types/TyCoRep.hs:1932:56 in ghc:TyCoRep
  checkValidSubst, called at compiler/types/TyCoRep.hs:1991:17 in ghc:TyCoRep
  substTys, called at compiler/types/TyCoRep.hs:2012:14 in ghc:TyCoRep
  substTheta, called at compiler/typecheck/TcPatSyn.hs:255:20 in ghc:TcPatSyn
  in_scope InScope {d_ap0 c_apv}
  tenv [ap1 :-> c_apv[tau:5]]
  tenvFVs [aps :-> t_aps[tau:1], apv :-> c_apv[tau:5]]
  cenv []
  cenvFVs []
  tys []
  cos []


Complete log from Travis: 
https://s3.amazonaws.com/archive.travis-ci.org/jobs/110115377/log.txt

-- Thomas
___
ghc-devs mailing list
ghc-devs@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs


Build failures with -DDEBUG

2016-02-18 Thread Thomas Miedema
Simon,

the commits you pushed today don't validate with -DDEBUG.

Unexpected failures:

   patsyn/should_compile  MoreEx [exit code non-0] (normal)
   patsyn/should_compile  T11224b [exit code non-0] (normal)
   polykinds  MonoidsTF [exit code non-0] (normal)
   polykinds  T11480b [exit code non-0] (normal)
   polykinds  T11523 [exit code non-0] (normal)
   typecheck/should_fail  TcCoercibleFail [stderr mismatch] (normal)


TcCoercibleFail timed out, and the others all hit the following debug assert:



=> T11224b(normal) 2510 of 5029 [0, 0, 0]
Compile failed (status 256) errors were:
ghc-stage2: panic! (the 'impossible' happened)
  (GHC version 8.1.20160218 for x86_64-unknown-linux):
ASSERT failed!
  CallStack (from HasCallStack):
  assertPprPanic, called at compiler/types/TyCoRep.hs:1932:56 in ghc:TyCoRep
  checkValidSubst, called at compiler/types/TyCoRep.hs:1991:17 in
ghc:TyCoRep
  substTys, called at compiler/types/TyCoRep.hs:2012:14 in ghc:TyCoRep
  substTheta, called at compiler/typecheck/TcPatSyn.hs:255:20 in
ghc:TcPatSyn
  in_scope InScope {d_ap0 c_apv}
  tenv [ap1 :-> c_apv[tau:5]]
  tenvFVs [aps :-> t_aps[tau:1], apv :-> c_apv[tau:5]]
  cenv []
  cenvFVs []
  tys []
  cos []


Complete log from Travis:
https://s3.amazonaws.com/archive.travis-ci.org/jobs/110115377/log.txt

-- Thomas
___
ghc-devs mailing list
ghc-devs@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs


Re: Missing definitions of associated types

2016-02-18 Thread Reid Barton
Well, I see your point; but you also can't define a

On Thu, Feb 18, 2016 at 12:00 PM, David Feuer  wrote:

> It seems to be that a missing associated type definition should be an
> error, by default, rather than a warning. The current behavior under those
> circumstances strikes me as very strange, particularly for data families
> and particularly in the presence of overlapping.
>

> This compiles with just a warning because Assoc Char *falls through* to
> the general case. WAT? This breaks all my intuition about what associated
> types are supposed to be about.
>
>
Well, I see your point; but you also can't give a definition for Assoc Char
in the Foo Char instance, because open data family instances are not
allowed to overlap. So if failing to give a definition for an associated
data family is an error, then it's impossible to use overlapping instances
with classes that have associated data families. Is that your intention?

I don't have a strong opinion here. I'm mildly inclined to say that people
using overlapping instances have already signed themselves up for weird
things happening, and we may as well let them do whatever other weird
things they want.

Regards,
Reid Barton
___
ghc-devs mailing list
ghc-devs@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs


Missing definitions of associated types

2016-02-18 Thread David Feuer
It seems to be that a missing associated type definition should be an
error, by default, rather than a warning. The current behavior under those
circumstances strikes me as very strange, particularly for data families
and particularly in the presence of overlapping.

{-# LANGUAGE TypeFamilies #-}
class Foo a where
  data Assoc a
  foo :: proxy a -> Assoc a

instance {-# OVERLAPPABLE #-} Foo a where
  data Assoc a = AssocGeneral
  foo _ = AssocGeneral

instance {-# OVERLAPS #-} Foo Char where
  foo _ = AssocGeneral

blah :: Assoc Char
blah = foo (Proxy :: Proxy Char)

This compiles with just a warning because Assoc Char *falls through* to the
general case. WAT? This breaks all my intuition about what associated types
are supposed to be about.
___
ghc-devs mailing list
ghc-devs@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs


RE: Fwd: Is anything being done to remedy the soul crushing compile times of GHC?

2016-02-18 Thread Andrey Mokhov
Thomas Tuegel  writes:

> I think what Andrey meant was, the first time we run the pre-processors,
> cache the locations of all the files that need to be pre-processed. On
> subsequent runs, we only need to check pre-processors the files in the cache.

Yes, something along the lines. Although I don't fully understand Herbert's 
comment, so I decided to open an issue about this so we could discuss this 
without spamming the ghc-devs mailing list:

https://github.com/snowleopard/shaking-up-ghc/issues/210

Herbert, Thomas, and all -- I'd appreciate your input!

Cheers,
Andrey
___
ghc-devs mailing list
ghc-devs@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs


Re: Fwd: Is anything being done to remedy the soul crushing compile times of GHC?

2016-02-18 Thread Thomas Tuegel
On Thu, Feb 18, 2016 at 6:43 AM, Herbert Valerio Riedel
 wrote:
> On 2016-02-18 at 13:32:59 +0100, Andrey Mokhov wrote:
>> Interesting! In the new Shake-based build system we also need to
>> automagically generate .hs files using Alex et al. My first
>> implementation was slow but then I realised that it is possible to
>> scan the source tree only once and remember where all .hs/.x/etc files
>> are. This brought down the complexity from quadratic to linear in my
>> case -- maybe this could be reused in cabal too?
>
> This sounds very risky; are you suggesting to blindly traverse the
> hs-src-dirs *before* you even know what is searched for?
>
> If so, this will cause problems; we're already seeing problems with this
> in the cabal nix-local-branch, which currently (it's a bug) recursively
> traverses the project folder for computing a source-hash over content
> that would not even make it into the source-dist...
>
> There must be a better way to solve this...

I think what Andrey meant was, the first time we run the
pre-processors, cache the locations of all the files that need to be
pre-processed. On subsequent runs, we only need to check
pre-processors the files in the cache. I've been thinking along these
lines, too. This does break if you change what pre-processor is used
to build a file, but I think that's OK because it happens so rarely.
We would give the user a way to invalidate the cache, i.e. run the
pre-processors manually by a `cabal pre-process` command.

- Tom
___
ghc-devs mailing list
ghc-devs@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs


Re: New type of ($) operator in GHC 8.0 is problematic

2016-02-18 Thread Takenobu Tani
Hi,

I know the issue of beginner's Prelude.


But how about "profile"? (like H264/MPEG4-AVC profile [1])

  * Beginner Profile : beginner's Prelude or ghci beginner's
representation mode

  * Main Profile : Haskell 2010 standard

  * Leading edge Profile : set of GHC extensions


If beginners know exist of profile at first, they may avoid to confuse by
step-up?
More confused?

Already we implicitly have at least two profiles (Haskell2010 and GHC
extensions).

[1] https://en.wikipedia.org/wiki/H.264/MPEG-4_AVC#Profiles

Regards,
Takenobu


2016-02-18 16:45 GMT+09:00 Herbert Valerio Riedel :

> On 2016-02-18 at 04:02:24 +0100, Eric Seidel wrote:
> > On Wed, Feb 17, 2016, at 08:09, Christopher Allen wrote:
> >> I have tried a beginner's Prelude with people. I don't have a lot of
> data
> >> because it was clearly a failure early on so I bailed them out into the
> >> usual thing. It's just not worth it and it deprives them of the
> >> preparedness to go write real Haskell code. That's not something I'm
> >> willing to give up just so I can teach _less_.
> >
> > Chris, have you written about your experiences teaching with a
> > beginner's Prelude? I'd be quite interested to read about it, as (1) it
> > seems like a natural thing to do and (2) the Racket folks seem to have
> > had good success with their staged teaching languages.
> >
> > In particular, I'm curious if your experience is in the context of
> > teaching people with no experience programming at all, vs programming
> > experience but no Haskell (or generally FP) experience. The Racket "How
> > to Design Programs" curriculum seems very much geared towards absolute
> > beginners, and that could be a relevant distinction.
>
> Btw, IMHO it's also interesting to distinguish between teaching
> functional programming vs teaching Haskell.
>
> I've noticed that in the former case, instructors would often prefer a
> radically slimmed down standard-library and conceal some of Haskell's
> language features not pertinent to their FP curriculum (e.g. typeclasses
> or record syntax).
>
> --
> ___
> ghc-devs mailing list
> ghc-devs@haskell.org
> http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs
>
___
ghc-devs mailing list
ghc-devs@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs


Re: New type of ($) operator in GHC 8.0 is problematic

2016-02-18 Thread Takenobu Tani
Hi Manuel,

> I do worry about the same thing. The Haskell ecosystem is very much
geared towards experts and tinkerers (with laudable exceptions, such as,
for example, the great work done by Chris Allen). Being an expert and
tinkerer that didn’t worry me too much, but lately I am trying to make
functional programming and Haskell accessible to a broader audience and it
is an uphill battle. Even many professional software developers are put off
even trying to install the toolchain. It is not that they wouldn’t been
able to do it if they wanted. They just can’t be bothered because they are
not convinced of the value of doing so at this stage — exactly as you are
saying.
>
> We should make it easier to get started, not harder.


You are thinking deeply.


We should find approaches that satisfy the follows:

  * No surprise for various beginners

  * No confuse by their step-up

  * No stress for experts

  * No prevent GHC(Haskell)'s evolution


I like diversity of Haskell community =)

Regards,
Takenobu
___
ghc-devs mailing list
ghc-devs@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs


Re: Fwd: Is anything being done to remedy the soul crushing compile times of GHC?

2016-02-18 Thread Herbert Valerio Riedel
On 2016-02-18 at 13:32:59 +0100, Andrey Mokhov wrote:

[...]

> Interesting! In the new Shake-based build system we also need to
> automagically generate .hs files using Alex et al. My first
> implementation was slow but then I realised that it is possible to
> scan the source tree only once and remember where all .hs/.x/etc files
> are. This brought down the complexity from quadratic to linear in my
> case -- maybe this could be reused in cabal too?

This sounds very risky; are you suggesting to blindly traverse the
hs-src-dirs *before* you even know what is searched for?

If so, this will cause problems; we're already seeing problems with this
in the cabal nix-local-branch, which currently (it's a bug) recursively
traverses the project folder for computing a source-hash over content
that would not even make it into the source-dist...

There must be a better way to solve this...
___
ghc-devs mailing list
ghc-devs@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs


Re: Fwd: Is anything being done to remedy the soul crushing compile times of GHC?

2016-02-18 Thread Andrey Mokhov
Thomas Tuegel  writes:

> > What exactly does the pre-process phase do, anyways?

> It runs the appropriate pre-processor (Alex, Happy, c2hs, etc.) for modules
> that require it. It's slow because of the way the process is carried out: For
> each module in the package description, Cabal tries to find an associated .hs
> source file in the hs-source-dirs. If it cannot, it looks for a file with an
> extension matching one of the pre-processors it knows about. If it finds one,
> it runs the corresponding program if the output files are missing or outdated.

Interesting! In the new Shake-based build system we also need to automagically 
generate .hs files using Alex et al. My first implementation was slow but then 
I realised that it is possible to scan the source tree only once and remember 
where all .hs/.x/etc files are. This brought down the complexity from quadratic 
to linear in my case -- maybe this could be reused in cabal too?

By the way, there seem to be a fair amount of code & functionality overlap in 
cabal and the new build system. We might want to look into this once the build 
system becomes more stable.

Cheers,
Andrey
 
___
ghc-devs mailing list
ghc-devs@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs


Strict Haskell

2016-02-18 Thread Simon Peyton Jones
Johan
Consider this with -XStrict

f y = let Just x = blah[y] in body[y,x]
Suppose that in a call to f,

· blah returns Nothing

· but body does not use x
Should f succeed?  For sure, blah will be evaluated to HNF before body is 
started, but is the match against Just done strictly too?
According to our current semantics, in the match against Just is not done 
strictly, so the call should succeed.  I think that’s unexpected and probably 
wrong.
Here’s the semantics 
http://downloads.haskell.org/~ghc/master/users-guide/glasgow_exts.html#recursive-and-polymorphic-let-bindings
The translation for
!(Just x) = blah

ð  (FORCE)   v = blah; Just x = v(and add a seq on v)

ð  (SPLIT) v = blah; x = case v of Just x -> x
So we finish up with

f y = let v = blah[y] in

  let x = case v of Just x -> x in

  v `seq` body[y,x]
I don’t think that’s what you intended.
If the pattern can fail, I think we want the FORCE step to say this:

Replace any binding !p = e with

v = case e of p -> (v1,..,vn); (v1,..,vn) = v

and replace e0 with v seq e0, where v is fresh and v1..vn are the variable(s) 
bound by p
(Compare with the text at the above link.)
Do you agree?
Simon


___
ghc-devs mailing list
ghc-devs@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs