Building dictionary terms in Core?

2019-01-06 Thread Ömer Sinan Ağacan
Hi,

In #15646 (recent discussion in Gitlab MR 55) we need dictionary arguments in
Core (in desugarer) to apply to functions like `fromRational :: Fractional a =>
Rational -> a`, but we don't know how to build the dictionary term (`Fractional
a`) in Core. Can anyone who know help us in the MR?

Thanks,

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


GitLab forks and submodules

2019-01-06 Thread Moritz Angermann
Hi *,

so what do we do with submodules? If you point someone to a fork of ghc, say:

  gitlab.haskell.org/foo/ghc

and they try to check it out, they will run into issues because foo didn't 
clone all the
submodules.  So how is one supposed to clone a forked ghc repository?

Cheers,
 Moritz


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


Re: How to use Data.Compact.Serialize

2019-01-06 Thread Edward Z. Yang
Yes this looks good to me.

It is NOT necessary to statically link libc, since the only pointers
embedded in compact regions are only ever info table pointers, e.g.,
stuff that GHC generated, not arbitrary functions in libc.

Edward

Excerpts from Christopher Done's message of 2018-12-19 10:31:28 +:
> Hi,
> 
> On the docs for Data.Compact.Serialize it says:
> 
> http://hackage.haskell.org/package/compact-0.1.0.1/docs/Data-Compact-Serialize.html
> > Our binary representation contains direct pointers to the info tables
> > of objects in the region. This means that the info tables of the
> > receiving process must be laid out in exactly the same way as from the
> > original process; in practice, this means using static linking, using
> > the exact same binary and turning off ASLR.
> 
> It seems to me that in order to use this module in any practical way
> (i.e. write to file from one process, and then a later run of the
> process reads it), you need to know a special way to build your binary
> which isn't fully described here. What flags, for example, should be
> passed to GHC to make this viable?
> 
> * Turning off ASLR on Linux is done by writing 0 to
>   /proc/sys/kernel/randomize_va_space, which applies to all
>   programs. That's not the most isolated way to deploy an app, but I
>   discovered that you can set this per process here:
>   https://askubuntu.com/a/507954
> * To compile GHC programs statically, use -optl-static -optl-pthread.
> 
> So in total the example would be:
> 
> $ stack build compact
> compact-0.1.0.1: download
> compact-0.1.0.1: configure
> compact-0.1.0.1: build
> compact-0.1.0.1: copy/register
> 
> Example file from docs:
> 
> $ cat main.hs
> {-# LANGUAGE TypeApplications #-}
> import System.Environment
> import Data.Compact
> import Data.Compact.Serialize
> main = do
>   arg:_ <- getArgs
>   case arg of
> "write" -> do
>   orig_c <- compact ("I want to serialize this", True)
>   writeCompact @(String, Bool) "somefile" orig_c
> "read" -> do
>   res <- unsafeReadCompact @(String, Bool) "somefile"
>   case res of
> Left err -> fail err
> Right c -> print (getCompact c)
> 
> Compiling statically:
> 
> $ stack ghc -- -optl-static -optl-pthread main.hs
> [1 of 1] Compiling Main ( main.hs, main.o )
> Linking main ...
> [...hundred more warnings like this ...]
> 
> Check that it's static:
> 
> $ ldd main
> not a dynamic executable
> 
> Write the file:
> 
> $ setarch `uname -m` -R ./main write
> 
> Read the file:
> 
> $ setarch `uname -m` -R ./main read
> ("I want to serialize this",True)
> 
> Can a GHC dev confirm that this is the proper way to do this? If so,
> I'll contribute this little example as documentation to the compact package.
> 
> Cheers
___
ghc-devs mailing list
ghc-devs@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs


Re: Blocking a task indefinitely in the RTS

2019-01-06 Thread John Lato
Can you use an os-level structure? E.g. block on a file descriptor, socket,
or something like that?

On Sun, Jan 6, 2019, 10:37 Phyx  Hi All,
>
> I'm looking for a way to block a task indefinitely until it is woken up by
> an external event in both the threaded and non-threaded RTS and returns a
> value that was stored/passed. MVar works great for the threaded RTS, but
> for the non-threaded there's a bunch of deadlock detection in the scheduler
> that would forcibly free the lock and resume the task with an opaque
> exception. This means that MVar and anything derived from it is not usable.
>
> STMs are more expensive but also have the same deadlock code. So again no
> go. The reason it looks like a deadlock to the RTS is that the "Wake-up"
> call in the non-threaded rts will come from C code running inside the RTS.
> The RTS essentially just sees all tasks blocked on it's main capability and
> (usually rightly so) assumes a deadlock occurred.
>
> You have other states like BlockedOnForeign etc but those are not usable
> as a primitive. Previous iterations of I/O managers have each invented
> primitives for this such as asyncRead#, but they are not general and can't
> be re-used, and requires a different solution for threaded and non-threaded.
>
> I have started making a new primitive IOPort for this, based on the MVar
> code, but this is not trivial... (currently I'm getting a segfault
> *somewhere* in the primitive's cmm code). The reason is that the semantics
> are decidedly different from what MVars guarantee. I should also mention
> that this is meant to be internal to base (i.e no exported).
>
> So before I continue down this path and some painful debugging..., does
> anyone know of a way to block a task, unblock it later and pass a value
> back? It does not need to support anything complicated such as multiple
> take/put requests etc.
>
> Cheers,
> Tamar
> ___
> 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: Blocking a task indefinitely in the RTS

2019-01-06 Thread Phil Ruffwind
What if you wrap the MVar in a foreign closure?

import Control.Concurrent.MVar (newEmptyMVar, putMVar, takeMVar)
import Control.Exception (bracket)
import Foreign.Ptr (FunPtr, freeHaskellFunPtr)

foreign import ccall "wrapper" wrapAwaken :: IO () -> IO (FunPtr (IO ()))

main = do
  mvar <- newEmptyMVar
  bracket (wrapAwaken (putMVar mvar ())) freeHaskellFunPtr $ \ awaken -> do
-- giveToExternalCode awaken
takeMVar mvar

On Sun, Jan 6, 2019, at 10:37, Phyx wrote:
> Hi All,
> 
> I'm looking for a way to block a task indefinitely until it is woken up by
> an external event in both the threaded and non-threaded RTS and returns a
> value that was stored/passed. MVar works great for the threaded RTS, but
> for the non-threaded there's a bunch of deadlock detection in the scheduler
> that would forcibly free the lock and resume the task with an opaque
> exception. This means that MVar and anything derived from it is not usable.
> 
> STMs are more expensive but also have the same deadlock code. So again no
> go. The reason it looks like a deadlock to the RTS is that the "Wake-up"
> call in the non-threaded rts will come from C code running inside the RTS.
> The RTS essentially just sees all tasks blocked on it's main capability and
> (usually rightly so) assumes a deadlock occurred.
> 
> You have other states like BlockedOnForeign etc but those are not usable as
> a primitive. Previous iterations of I/O managers have each invented
> primitives for this such as asyncRead#, but they are not general and can't
> be re-used, and requires a different solution for threaded and non-threaded.
> 
> I have started making a new primitive IOPort for this, based on the MVar
> code, but this is not trivial... (currently I'm getting a segfault
> *somewhere* in the primitive's cmm code). The reason is that the semantics
> are decidedly different from what MVars guarantee. I should also mention
> that this is meant to be internal to base (i.e no exported).
> 
> So before I continue down this path and some painful debugging..., does
> anyone know of a way to block a task, unblock it later and pass a value
> back? It does not need to support anything complicated such as multiple
> take/put requests etc.
> 
> Cheers,
> Tamar
> ___
> 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: GitLab CI for patches across submodules

2019-01-06 Thread Simon Jakobi via ghc-devs
Am Sa., 5. Jan. 2019 um 22:18 Uhr schrieb Ben Gamari :

However, we can certainly use the upstream repo during CI builds.



I have opened !78 which should hopefully fix this. Perhaps you could

rebase on topp of this and check?
>

Thanks, Ben, that works for me.

What I hadn't realized before, is that having my haddock commit in my
Gitlab fork (sjakobi/haddock) apparently also makes it accessible through
ghc/haddock.
What is my-branch in sjakobi/haddock is sjakobi/my-branch in ghc/haddock.

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


Re: Glasgow Haskell Compiler | Fix #16133 by checking for TypeApplications in rnExpr (!77)

2019-01-06 Thread Brandon Allbery
For what it's worth, the !77 seems to mean
https://gitlab.haskell.org/ghc/ghc/merge_requests/77 which is also the
"View it on GitLab" link target. And in general the "!" seems to indicate a
merge request, per reference to "!82" mentioning this one. So this does
seem to be a new merge request, and presumably the third part is the
requested merge from a personal WIP branch to master.

On Sun, Jan 6, 2019 at 4:19 PM Simon Peyton Jones via ghc-devs <
ghc-devs@haskell.org> wrote:

> I am now getting lots of email from GitLab, and I’m trying to figure out
> what they all mean.  They come in various forms.
>
>
>
> Here’s one puzzler:
>
>- what does the email below mean?  Is it a new merge request?
>- what is the “!77”?
>- What does “*RyanGlScott/ghc:wip/T16133 → ghc/ghc:master” *mean?
>
>
>
> Simon
>
>
>
> *From:* Ryan Scott 
> *Sent:* 05 January 2019 17:46
> *To:* Simon Peyton Jones 
> *Subject:* Glasgow Haskell Compiler | Fix #16133 by checking for
> TypeApplications in rnExpr (!77)
>
>
>
> *Project:Branches: RyanGlScott/ghc:wip/T16133 → ghc/ghc:master *
>
> We had a validity check, typeAppErr, for visible *kind* applications (in
> rnHsTyKi), but didn't extend the same treatment to visible *type*
> applications (in rnExpr). Easily fixed by also invoking typeAppErr from
> rnExpr.
>
> Fixes https://ghc.haskell.org/trac/ghc/ticket/16133
> 
> .
>
> —
> View it on GitLab
> .
>
> You're receiving this email because of your account on gitlab.haskell.org.
> If you'd like to receive fewer emails, you can unsubscribe
> 
> from this thread or adjust your notification settings.
> ___
> ghc-devs mailing list
> ghc-devs@haskell.org
> http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs
>


-- 
brandon s allbery kf8nh
allber...@gmail.com
___
ghc-devs mailing list
ghc-devs@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs


RE: Glasgow Haskell Compiler | Fix #16133 by checking for TypeApplications in rnExpr (!77)

2019-01-06 Thread Simon Peyton Jones via ghc-devs
I am now getting lots of email from GitLab, and I’m trying to figure out what 
they all mean.  They come in various forms.

Here’s one puzzler:

  *   what does the email below mean?  Is it a new merge request?
  *   what is the “!77”?
  *   What does “RyanGlScott/ghc:wip/T16133 → ghc/ghc:master” mean?

Simon

From: Ryan Scott 
Sent: 05 January 2019 17:46
To: Simon Peyton Jones 
Subject: Glasgow Haskell Compiler | Fix #16133 by checking for TypeApplications 
in rnExpr (!77)


Project:Branches: RyanGlScott/ghc:wip/T16133 → ghc/ghc:master

We had a validity check, typeAppErr, for visible kind applications (in 
rnHsTyKi), but didn't extend the same treatment to visible type applications 
(in rnExpr). Easily fixed by also invoking typeAppErr from rnExpr.

Fixes 
https://ghc.haskell.org/trac/ghc/ticket/16133.

—
View it on 
GitLab.
You're receiving this email because of your account on gitlab.haskell.org. If 
you'd like to receive fewer emails, you can 
unsubscribe
 from this thread or adjust your notification settings.
___
ghc-devs mailing list
ghc-devs@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs


Blocking a task indefinitely in the RTS

2019-01-06 Thread Phyx
Hi All,

I'm looking for a way to block a task indefinitely until it is woken up by
an external event in both the threaded and non-threaded RTS and returns a
value that was stored/passed. MVar works great for the threaded RTS, but
for the non-threaded there's a bunch of deadlock detection in the scheduler
that would forcibly free the lock and resume the task with an opaque
exception. This means that MVar and anything derived from it is not usable.

STMs are more expensive but also have the same deadlock code. So again no
go. The reason it looks like a deadlock to the RTS is that the "Wake-up"
call in the non-threaded rts will come from C code running inside the RTS.
The RTS essentially just sees all tasks blocked on it's main capability and
(usually rightly so) assumes a deadlock occurred.

You have other states like BlockedOnForeign etc but those are not usable as
a primitive. Previous iterations of I/O managers have each invented
primitives for this such as asyncRead#, but they are not general and can't
be re-used, and requires a different solution for threaded and non-threaded.

I have started making a new primitive IOPort for this, based on the MVar
code, but this is not trivial... (currently I'm getting a segfault
*somewhere* in the primitive's cmm code). The reason is that the semantics
are decidedly different from what MVars guarantee. I should also mention
that this is meant to be internal to base (i.e no exported).

So before I continue down this path and some painful debugging..., does
anyone know of a way to block a task, unblock it later and pass a value
back? It does not need to support anything complicated such as multiple
take/put requests etc.

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


Re: Better DWARF info for Cmm procedures?

2019-01-06 Thread Ömer Sinan Ağacan
> However, there is also a slightly more fundamental issue here: GHC's NCG
> handles DWARF information with block granularity. Fixing this will be a
> bit more involved. See compiler/nativeGen/Dwarf.hs for details.
>
> One alternative would be to just finish debug information in the LLVM
> backend and use this instead (originally D2343, although mpickering has
> a newer version).

But LLVM backend also uses the same debug info we generate for NCG, no? So I
think debug info would still be in block granularity?

How hard do you think it would be to do the refactoring to generate debug info
for each Cmm source line, instead of each RawCmm block?

Ömer

Ben Gamari , 6 Oca 2019 Paz, 14:47 tarihinde şunu yazdı:
>
> Ömer Sinan Ağacan  writes:
>
> > Hi,
> >
> > Currently debugging Cmm is a bit painful because we don't have enough debug
> > information to map assembly to Cmm lines, so I have do the mapping manually.
> > However I realized that when building .cmm files we actually generates some
> > debug information, in form of "ticks":
> >
> > //tick src
> > _c2e::I64 = I64[R1 + 32];
> >
> > Here the tick says that this assignment is for this Cmm line in Apply.cmm:
> >
> > Words = StgAP_STACK_size(ap);
> >
> > I was wondering what needs to be done to generate DWARF information from 
> > those
> > so that gdb can show Cmm line we're executing, and gdb commands like `next`,
> > `break` etc. work.
> >
> The DWARF information that we produce are indeed derived from these
> source notes. If you compile a C-- module with -g3 you will find the
> resulting object file should have line number information.
>
> > I also realize that we don't consistently generate these ticks for all Cmm
> > lines, for example, in the same Cmm dump there isn't a tick before this 
> > line:
> >
> Indeed the C-- parser doesn't produce as many source notes
> as you might find in C-- from the STG pipeline. Essentially it only adds
> source notes on flow control constructs and assignments (see uses of
> withSourceNote in CmmParse.y).
>
> However, there is also a slightly more fundamental issue here: GHC's NCG
> handles DWARF information with block granularity. Fixing this will be a
> bit more involved. See compiler/nativeGen/Dwarf.hs for details.
>
> One alternative would be to just finish debug information in the LLVM
> backend and use this instead (originally D2343, although mpickering has
> a newer version).
>
> Cheers,
>
> - Ben
___
ghc-devs mailing list
ghc-devs@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs


Re: Better DWARF info for Cmm procedures?

2019-01-06 Thread Ben Gamari
Ömer Sinan Ağacan  writes:

> Hi,
>
> Currently debugging Cmm is a bit painful because we don't have enough debug
> information to map assembly to Cmm lines, so I have do the mapping manually.
> However I realized that when building .cmm files we actually generates some
> debug information, in form of "ticks":
>
> //tick src
> _c2e::I64 = I64[R1 + 32];
>
> Here the tick says that this assignment is for this Cmm line in Apply.cmm:
>
> Words = StgAP_STACK_size(ap);
>
> I was wondering what needs to be done to generate DWARF information from those
> so that gdb can show Cmm line we're executing, and gdb commands like `next`,
> `break` etc. work.
>
The DWARF information that we produce are indeed derived from these
source notes. If you compile a C-- module with -g3 you will find the
resulting object file should have line number information.

> I also realize that we don't consistently generate these ticks for all Cmm
> lines, for example, in the same Cmm dump there isn't a tick before this line:
>
Indeed the C-- parser doesn't produce as many source notes
as you might find in C-- from the STG pipeline. Essentially it only adds
source notes on flow control constructs and assignments (see uses of
withSourceNote in CmmParse.y).

However, there is also a slightly more fundamental issue here: GHC's NCG
handles DWARF information with block granularity. Fixing this will be a
bit more involved. See compiler/nativeGen/Dwarf.hs for details.

One alternative would be to just finish debug information in the LLVM
backend and use this instead (originally D2343, although mpickering has
a newer version).

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