Re: When does GHC produce unlifted `let` bindings?

2017-10-29 Thread Ben Gamari


Sebastian Graf  writes:

> Hi folks,
>
> I was debugging a Core-to-Core transform for TEST=spec-inline
> 
> and
> was wondering (yet again) why GHC produces unlifted `let` bindings in Core
> like it seems supposed to be doing
> 
> .
>
>- Why doesn't this use `case` instead?
>- Is there a semantic difference?

My understanding is that we use `case` in this case since there is no
thunk evaluation necessary. Recall that operationally (under STG) `case`
is what drives evaluation whereas `let` is simply allocation. In a
sense, bringing an unlifted binding into scope is closer to the latter
than the former, being a simple register assignment.

>- Can `case` be used with unlifted types?

I'm honestly not sure what would happen in this case. It may work fine
or something may explode. I suspect CoreToStg will lower a case with an
unlifted scrutinee to a let, but perhaps not. If not then things likely
will blow up since, according to Note [Types in StgConApp], unlifted
values can't be let-bound in STG.

Cheers,

- Ben


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


Re: Q: Types in GADT pattern match

2017-10-29 Thread Richard Eisenberg
Hi Gabor,

Oleg is right that the re-use of type variables obscures the error, but it's 
not quite a scoping error under the hood. The problem is that GHC type-checks 
type signatures on patterns *before* type-checking the pattern itself. That 
means that when GHC checks your `Foo [a]` type signature, we haven't yet 
learned that `a1` (the type variable used in the type signature of foo) equals 
`[a]`. This makes it hard to bind a variable to `a`. Here's what I've done:

> foo :: Foo a -> ()
> foo b@Bar = case b of
>   (_ :: Foo [c]) -> quux b
> where
>   quux :: Foo [c] -> ()
>   quux Bar = ()

It's gross, but it works, and I don't think there's a better way at the moment. 
A collaborator of mine is working on a proposal (and implementation) of binding 
existentials in patterns (using similar syntax to visible type application), 
but that's still a few months off, at best.

Richard

> On Oct 29, 2017, at 1:42 PM, Gabor Greif  wrote:
> 
> Hi Devs!
> 
> I encountered a curious restriction with type signatures (tyvar bindings) in 
> GADT pattern matches.
> 
> GHC won't let me directly capture the refined type structure of GADT 
> constructors like this:
> 
> 
> {-# Language GADTs, ScopedTypeVariables #-}
> 
> data Foo a where
>   Bar :: Foo [a]
> 
> foo :: Foo a -> ()
> foo b@(Bar :: Foo [a]) = quux b
>   where quux :: Foo [b] -> ()
> quux Bar = ()
> 
> 
> I get:
> 
> 
> test.hs:7:8: error:
> • Couldn't match type ‘a1’ with ‘[a]’
>   ‘a1’ is a rigid type variable bound by
> the type signature for:
>   foo :: forall a1. Foo a1 -> ()
> at test.hs:6:1-18
>   Expected type: Foo a1
> Actual type: Foo [a]
> 
> 
> To me it appears that the type refinement established by the GADT pattern 
> match is not accounted for.
> 
> Of course I can write:
> 
> foo :: Foo a -> ()
> foo b@Bar | (c :: Foo [a]) <- b = quux c
>   where quux :: Foo [b] -> ()
> quux Bar = ()
> 
> but it feels like a complicated way to do it...
> 
> My question is whether this is generally seen as the way to go or whether 
> ScopedTypeVariables coming from a GADT pattern match should be able to 
> capture the refined type. To me the latter seems more useful.
> 
> Just wanted to feel the waters before writing a ticket about this.
> 
> Cheers and thanks,
> 
> Gabor
> ___
> 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: perf.haskell.org functional again

2017-10-29 Thread Joachim Breitner
Hi,

Am Sonntag, den 29.10.2017, 23:58 +0100 schrieb Sebastian Graf:
> Hi,
> 
> just wanted to throw in the idea of parallelising the benchmark suite
> (hurts to even write that, but cachegrind) to speed up the build, if
> ever need be.

https://github.com/nomeata/gipeda/blob/master/ghc/run-speed.sh#L143

good idea indeed – I’ve been doing that since I started running
cachegrind ;-)


Joachim

-- 
Joachim Breitner
  m...@joachim-breitner.de
  http://www.joachim-breitner.de/


signature.asc
Description: This is a digitally signed message part
___
ghc-devs mailing list
ghc-devs@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs


Re: perf.haskell.org functional again

2017-10-29 Thread Sebastian Graf
Hi,

just wanted to throw in the idea of parallelising the benchmark suite
(hurts to even write that, but cachegrind) to speed up the build, if ever
need be.

Cheers,
Sebastian

On Wed, Oct 25, 2017 at 2:13 AM, Manuel M T Chakravarty <
c...@justtesting.org> wrote:

> Am 24.10.2017 um 14:46 schrieb Joachim Breitner  >:
>
> Is CircleCI the future now?
>
>
> Yes, as per
>
>   https://ghc.haskell.org/trac/ghc/wiki/ContinuousIntegration
>
> In general, yes. But it’s running fine for now, so I would not
> prematurely throw it over.
>
> My requirements are:
>
> * needs to run on every commit (not just every push), including
>   branches.
> * needs to be able to push to a repository¹, so it needs access to
>   some secret token for depolyment.
>   Alternatively, the CI could simply keep track of the build log
>   and the perf.haskell.org dashboard scrapes it from there.
> * Occasionally, I find that I want to rebuild a fair number of commits
>   that are already in the repository. So a good way to trigger
>   rebuilds would be nice.
>
>
> No need to mess with a working system, but as long as performance counters
> are the basis, I think, these constraints can all be met. In particular,
> CircleCI has facilities to allow deployments including managing of secrets.
> (That is a pretty common requirements for CIs.)
>
> Cheers,
> Manuel
>
>
> Greetings,
> Joachim
>
> ¹ https://github.com/nomeata/ghc-speed-logs/commits/master
>
> Am Dienstag, den 24.10.2017, 12:18 +1100 schrieb Manuel M T
> Chakravarty:
>
> Hi Joachim,
>
> Great! Just because you mention CI infrastructure and our effort around
> GHC CI at the moment, do you think, it would make sense to move this to
> CircleCI eventually?
>
> Cheers,
> Manuel
>
> Am 24.10.2017 um 11:02 schrieb Joachim Breitner  >:
>
> Hi,
>
> after a system upgrade to avoid weird linker errors, and after some fixes
> in the nofib submodule, http://perf.haskell.org/ghc is running again.
>
> I am collecting instruction counts instead of runtime, because the latter
> was just too often varying too wildly. I hope this will yield less false
> alarms.
>
> I am also running nofib with mode=fast. This way, building GHC, running
> the testsuite and nofib takes a bit over one hour. I hope this can keep up
> with y'all's commits (when it took 2h it couldn't).
>
> Now nothing of the setup requires a quiet dedicated machine, so if there
> is a need, we could move these builds into the cloud or into some CI
> infrastructure - but no changes are immediately planned.
>
> Enjoy, Joachim
>
> --
> Joachim Breitner
>  m...@joachim-breitner.de
>  http://www.joachim-breitner.de/
> ___
> 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
>
>
___
ghc-devs mailing list
ghc-devs@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs


Re: Bringing some observable sharing to GHCi

2017-10-29 Thread Joachim Breitner
Hi,



Am Sonntag, den 29.10.2017, 16:40 -0400 schrieb David Feuer:
> 1. To be able to display cyclical data in some sensible way.
> 
> > x = "hi" : x
> > x `seq` ()
> > :print x
> 
> should print some useful representation of x.

the best that I know for this is the hack that calls itself ghc-heap-
view:

~ $ cabal install ghc-heap-view 
~ $ ghci
GHCi, version 8.0.2: http://www.haskell.org/ghc/  :? for help
Prelude> :script .cabal/share/x86_64-linux-ghc-8.0.2/ghc-heap-view-0.5.10/ghci
Prelude> x = "hi" : x
Prelude> take 2 x
["hi","hi"]
Prelude> :printHeap x
let x1 = _bh (C# 'h' : _bh (C# 'i' : _bh [])) : _bh x1
in x1
Prelude> System.Mem.performGC
Prelude> :printHeap x
let x1 = "hi" : x1
in x1

A graphical front-end is ghc-vis:
http://felsin9.de/nnis/ghc-vis/

But it is mostly a hack and you should not expect a lot of reliability
of it. I’d love to see it supported by GHC proper. Erik de Castro Lopo
tried to merge it into GHC, but it seems to be very hard.

> 2. To be able to force cyclical data without looping.
> 
> > x = "hi" : x
> > :force x
> 

That could be implemented on top of ghc-heap-view.

Greetings,
Joachim

-- 
Joachim Breitner
  m...@joachim-breitner.de
  http://www.joachim-breitner.de/


signature.asc
Description: This is a digitally signed message part
___
ghc-devs mailing list
ghc-devs@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs


When does GHC produce unlifted `let` bindings?

2017-10-29 Thread Sebastian Graf
Hi folks,

I was debugging a Core-to-Core transform for TEST=spec-inline

and
was wondering (yet again) why GHC produces unlifted `let` bindings in Core
like it seems supposed to be doing

.

   - Why doesn't this use `case` instead?
   - Is there a semantic difference?
   - Can `case` be used with unlifted types?
   - And if not, why can `let`?

Unlifted `let` seems much close to `case` than to `let`. Some GHC passes
seem to agree.


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


Bringing some observable sharing to GHCi

2017-10-29 Thread David Feuer
The :sprint, :print, and :force commands in GHCi fall into infinite
loops when confronted by cyclical data. This bit me hard in
https://phabricator.haskell.org/D4085 because that produces cyclical
TypeReps, which is trouble for (e.g.) the test break011 which tries to
:force a SomeException (which wraps an Exception dictionary, which has
a Typeable constraint). I could try coming up with a fix myself, but
I'm rather curious whether some of the work you (or others) have
already done on observing GHC data graphs could be yanked into GHCi
itself for this purpose. We want

1. To be able to display cyclical data in some sensible way.

> x = "hi" : x
> x `seq` ()
> :print x

should print some useful representation of x.

2. To be able to force cyclical data without looping.

> x = "hi" : x
> :force x

should print a useful representation of x.
___
ghc-devs mailing list
ghc-devs@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs


Re: Q: Types in GADT pattern match

2017-10-29 Thread Oleg Grenrus
The problem is scoping. The problem is more obvious if you don't reuse
type-variables:

    {-# Language GADTs, ScopedTypeVariables #-}

    data Foo a where
  Bar :: Foo [x]

    foo :: Foo a -> ()
    foo b@(Bar :: Foo [c]) = quux b
  where quux :: Foo [b] -> ()
    quux Bar = ()

Then you'll get an:

   Couldn't match type ‘a’ with ‘[c]’

error.

I.e. GHC tries to match `foo`s type signatures, with annotation on
variable `b`.
But you don't need it. If you remove it, everything works fine:


    {-# Language GADTs, ScopedTypeVariables #-}

    data Foo a where
    Bar :: Foo [x]

    foo :: Foo a -> ()
    foo b@Bar = quux b
  where quux :: Foo [b] -> ()
    quux Bar = ()

Cheers, Oleg.

On 29.10.2017 19:42, Gabor Greif wrote:
> Hi Devs!
>
> I encountered a curious restriction with type signatures (tyvar
> bindings) in GADT pattern matches.
>
> GHC won't let me directly capture the refined type structure of GADT
> constructors like this:
>
>
> {-# Language GADTs, ScopedTypeVariables #-}
>
> data Foo a where
>   Bar :: Foo [a]
>
> foo :: Foo a -> ()
> foo b@(Bar :: Foo [a]) = quux b
>   where quux :: Foo [b] -> ()
>         quux Bar = ()
>
>
> I get:
>
>
> *test.hs:7:8: **error:*
>
> *    • Couldn't match type ‘a1’ with ‘[a]’*
>
> *      ‘a1’ is a rigid type variable bound by*
>
> *        the type signature for:*
>
> *          foo :: forall a1. Foo a1 -> ()*
>
> *        at test.hs:6:1-18*
>
> *      Expected type: Foo a1*
>
> *        Actual type: Foo [a]*
>
> *
> *
>
> To me it appears that the type refinement established by the GADT
> pattern match is not accounted for.
>
> Of course I can write:
>
> foo :: Foo a -> ()
> foo b@Bar | (c :: Foo [a]) <- b = quux c
>   where quux :: Foo [b] -> ()
>         quux Bar = ()
>
> but it feels like a complicated way to do it...
>
> My question is whether this is generally seen as the way to go or
> whether ScopedTypeVariables coming from a GADT pattern match should be
> able to capture the refined type. To me the latter seems more useful.
>
> Just wanted to feel the waters before writing a ticket about this.
>
> Cheers and thanks,
>
>     Gabor
>
>
> ___
> ghc-devs mailing list
> ghc-devs@haskell.org
> http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs



signature.asc
Description: OpenPGP digital signature
___
ghc-devs mailing list
ghc-devs@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs


Q: Types in GADT pattern match

2017-10-29 Thread Gabor Greif
Hi Devs!

I encountered a curious restriction with type signatures (tyvar bindings)
in GADT pattern matches.

GHC won't let me directly capture the refined type structure of GADT
constructors like this:


{-# Language GADTs, ScopedTypeVariables #-}

data Foo a where
  Bar :: Foo [a]

foo :: Foo a -> ()
foo b@(Bar :: Foo [a]) = quux b
  where quux :: Foo [b] -> ()
quux Bar = ()


I get:


*test.hs:7:8: **error:*

*• Couldn't match type ‘a1’ with ‘[a]’*

*  ‘a1’ is a rigid type variable bound by*

*the type signature for:*

*  foo :: forall a1. Foo a1 -> ()*

*at test.hs:6:1-18*

*  Expected type: Foo a1*

*Actual type: Foo [a]*


To me it appears that the type refinement established by the GADT pattern
match is not accounted for.

Of course I can write:

foo :: Foo a -> ()
foo b@Bar | (c :: Foo [a]) <- b = quux c
  where quux :: Foo [b] -> ()
quux Bar = ()

but it feels like a complicated way to do it...

My question is whether this is generally seen as the way to go or whether
ScopedTypeVariables coming from a GADT pattern match should be able to
capture the refined type. To me the latter seems more useful.

Just wanted to feel the waters before writing a ticket about this.

Cheers and thanks,

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