Re: Remote GHCi

2015-11-17 Thread Simon Marlow

CC Daniel Corin, maintainer of hint.

On 17/11/2015 11:49, Luite Stegeman wrote:

I like this idea, and it overlaps very much with the work that still
needs to be done for GHCJSi. I think that for Template Haskell, the
restriction that everything has to be marshalled via Binary is not too
problematic, although it'd require a bit of care if Richard's
pre-proposal to expose more GHC types to TH ( #11081 ) is to be
implemented. In particular, the API for querying the type environment
would have to remain implementable via message passing, so we can't
expose the full TcRn there.

compileExpr / dynCompileExpr seem to get some use, perhaps mostly
through the hint package:

http://packdeps.haskellers.com/reverse/hint

But I think the most common use case is just compiling and running
Haskell expressions, without any specific need for interpreted code. The
machinery behind hint could be reworked to have the GHC API produce a
dynamic library for the compiled expression, which could then be loaded
into the current process with the system linker. Or is there some reason
that  this approach would be unusable?


I don't think that simplifies the problem, we would still be dynamically 
loading and running code in the current process, which is exactly what 
we do now.


The issue is with

  interpret :: (MonadInterpreter m, Typeable a) => String -> a -> m a

which would need to become

 interpret :: (MonadInterpreter m, Typeable a, Binary a) => String -> a 
-> m a


or else we have to keep the current single-process mechanism for this 
use case.


Cheers,
Simon




luite

On Tue, Nov 17, 2015 at 10:10 AM Simon Marlow > wrote:

Hi folks - I've been thinking about changing the way we run interpreted
code so that it would be run in a separate process.  It turns out this
has quite a few benefits, and would let us kill some of the really
awkward hacks we have in GHC to work around problems that arise because
we're running interpreted code and the compiler on the same runtime.

I summarised the idea here:
https://ghc.haskell.org/trac/ghc/wiki/RemoteGHCi

I'd be interested to hear if anyone has any thoughts around this,
particularly if doing this would make your life difficult in some way.
Are people relying on dynCompileExpr for anything?

Cheers,
Simon


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


Re: Remote GHCi

2015-11-17 Thread Simon Marlow
I think there will be ways to do what you want in the context of a 
remote interpreter, but I'll need to understand more about the way in 
which you use dynCompileExpr.


What do you do with the result of dynCompileExpr?  Can you run that code 
in the context of the interpreter instead?


Cheers
Simon

On 17/11/2015 10:47, Sumit Sahrawat, Maths & Computing, IIT (BHU) wrote:

Hi Simon,

IHaskell  makes use of
dynCompileExpr to evaluate code provided by the user, so that the result
can be sent to the frontend to be displayed.

I don't think we can make it work without using dynCompileExpr, Andrew
would have more to say about this.

On 17 November 2015 at 16:10, Alan & Kim Zimmerman > wrote:

This fits in directly with what I am trying to do for the
haskell-ide-engine, where the intention is to expose ghci via an
asynchronous process with communication via message passing.

A bonus would be to have two separate interfaces, one for REPL
interaction for the user, the other to be able to query properties
of the loaded code.

I am currently investigating exposing Behavior and RunTerm from
haskeline to create a message passing backend instead.

Alan

On 17 Nov 2015 12:11 PM, "Simon Marlow" > wrote:

Hi folks - I've been thinking about changing the way we run
interpreted code so that it would be run in a separate process.
It turns out this has quite a few benefits, and would let us
kill some of the really awkward hacks we have in GHC to work
around problems that arise because we're running interpreted
code and the compiler on the same runtime.

I summarised the idea here:
https://ghc.haskell.org/trac/ghc/wiki/RemoteGHCi

I'd be interested to hear if anyone has any thoughts around
this, particularly if doing this would make your life difficult
in some way. Are people relying on dynCompileExpr for anything?

Cheers,
Simon
___
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




--
Regards

Sumit Sahrawat

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


RE: Further custom type error questions

2015-11-17 Thread Simon Peyton Jones
So perhaps you can update the wiki page to give an example like this, and 
thereby explain the design choice?  Or have a FAQ: “why not give TypeErorr the 
kind String -> Constraint?”.

The thought will be lost in email!

Simon

From: Iavor Diatchki [mailto:iavor.diatc...@gmail.com]
Sent: 17 November 2015 00:10
To: Ben Gamari
Cc: Simon Peyton Jones; Richard Eisenberg; Dominique Devriese; 
ghc-devs@haskell.org
Subject: Re: Further custom type error questions

Hello,

I imagine people wanting to do things as in the example below.  If we were to 
use only `TypeError` constraints, then we'd have to mostly use the class system 
to do type-level evaluation.  It doesn't seem obvious how to do that with just 
`TypeError` of kind constraint, unless all evaluation was to happen using the 
class system.

-Iavor
PS: Interestingly, this example reveals a bug with GHC's new warning about 
unused constraints, where the `OffsetOf` constant on `get` is reported as 
unnecessary...  I'll file a bug.


{-# LANGUAGE TypeFamilies, TypeOperators, UndecidableInstances, DataKinds #-}
{-# LANGUAGE ScopedTypeVariables #-}

import GHC.TypeLits
import Data.Proxy
import Data.Word
import Foreign.Ptr

type OffsetOf l xs = GetOffset 0 l xs

type family ByteSize x where
  ByteSize Word64   = 8
  ByteSize Word32   = 4
  ByteSize Word16   = 2
  ByteSize Word8= 1
  ByteSize a= TypeError (Text "The type " :<>: ShowType a :<>:
 Text " is not exportable.")

type family GetOffset n (l :: Symbol) xs where
  GetOffset n l ( '(l,a) ': xs) = '(n,a)
  GetOffset n l ( '(x,a)  : xs) = GetOffset (n+ByteSize a) l xs
  GetOffset n l '[] = TypeError (Text "Missing field: " :<>:
ShowType l)

newtype Struct (a :: [(Symbol,*)]) = Struct (Ptr ())


get :: forall l fs n a.
  (OffsetOf l fs ~ '(n,a), KnownNat n) =>
  Struct fs ->
  Proxy l   ->
  Ptr a
get (Struct p) _ = plusPtr p (fromInteger (natVal (Proxy :: Proxy n)))


type MyStruct = [ '("A",Word8), '("B",Word8), '("C",Int) ]

testOk :: Struct MyStruct -> Ptr Word8
testOk s = get s (Proxy :: Proxy "B")


{-
testNotOk :: Struct MyStruct -> Ptr Word8
testNotOk s = get s (Proxy :: Proxy "X")
--}

{-
type MyOtherStruct = [ '("A",Int), '("B",Word8) ]

testNotOk :: Struct MyOtherStruct -> Ptr Word8
testNotOk s = get s (Proxy :: Proxy "B")
--}







On Mon, Nov 16, 2015 at 1:21 PM, Ben Gamari 
> wrote:

While preparing some additional documentation for Iavor's custom type
errors work (which has been merged; thanks Iavor!) I noticed that
Dominique Devriese has raised some additional questions on the proposal
[1].

In particular, Dominique suggests that perhaps TypeError should simply
be of kind `ErrorMessage -> Constraint`. My understanding of the
proposal is that the intention is that `TypeError`s should be usable on
the RHS of type functions, like `error` on the term level. However, is
this strictly necessary? Is there any place where you couldn't just as
easily express the `TypeError` as a constraint?

If not, it seems like this may be substantially simpler approach and
totally side-steps the detection of `TypeError` in inappropriate places
on the RHS.

Regardless, it seems like this (and the other questions) is worth
addressing in the proposal.

Cheers,

- Ben


[1] 
https://ghc.haskell.org/trac/ghc/wiki/Proposal/CustomTypeErrors#SomedesignquestionsDominiqueDevriese:

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


Re: Remote GHCi

2015-11-17 Thread Sumit Sahrawat, Maths & Computing, IIT (BHU)
Hi Simon,

IHaskell  makes use of
dynCompileExpr to evaluate code provided by the user, so that the result
can be sent to the frontend to be displayed.

I don't think we can make it work without using dynCompileExpr, Andrew
would have more to say about this.

On 17 November 2015 at 16:10, Alan & Kim Zimmerman 
wrote:

> This fits in directly with what I am trying to do for the
> haskell-ide-engine, where the intention is to expose ghci via an
> asynchronous process with communication via message passing.
>
> A bonus would be to have two separate interfaces, one for REPL interaction
> for the user, the other to be able to query properties of the loaded code.
>
> I am currently investigating exposing Behavior and RunTerm from haskeline
> to create a message passing backend instead.
>
> Alan
> On 17 Nov 2015 12:11 PM, "Simon Marlow"  wrote:
>
>> Hi folks - I've been thinking about changing the way we run interpreted
>> code so that it would be run in a separate process.  It turns out this has
>> quite a few benefits, and would let us kill some of the really awkward
>> hacks we have in GHC to work around problems that arise because we're
>> running interpreted code and the compiler on the same runtime.
>>
>> I summarised the idea here:
>> https://ghc.haskell.org/trac/ghc/wiki/RemoteGHCi
>>
>> I'd be interested to hear if anyone has any thoughts around this,
>> particularly if doing this would make your life difficult in some way. Are
>> people relying on dynCompileExpr for anything?
>>
>> Cheers,
>> Simon
>> ___
>> 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
>
>


-- 
Regards

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


Re: Further custom type error questions

2015-11-17 Thread Dominique Devriese
FWIW: I didn't realise that this kind of example was the point of
TypeError being kind-polymorphic, thanks for the clarification.I
don't see an easy way of encoding this using the simpler alternative I
suggested, so my question is answered.  In hindsight, the wiki does
already show an example like this, so I must have missed this, sorry.

Thanks, see you,
Dominique

PS: I would still be interested if anyone has thoughts about the
TypeWarning thing I suggested...

2015-11-17 12:31 GMT+01:00 Roman Cheplyaka :
> Iavor, Ben, et al.:
>
> How about much simpler
>
> type family Head (a :: [k]) :: k where
>   Head (x ': xs) = x
>   Head '[] = Error "Empty list"
>
> Can this be expressed through Error-as-constraint?
>
> On 11/17/2015 02:09 AM, Iavor Diatchki wrote:
>> Hello,
>>
>> I imagine people wanting to do things as in the example below.  If we
>> were to use only `TypeError` constraints, then we'd have to mostly use
>> the class system to do type-level evaluation.  It doesn't seem obvious
>> how to do that with just `TypeError` of kind constraint, unless all
>> evaluation was to happen using the class system.
>>
>> -Iavor
>> PS: Interestingly, this example reveals a bug with GHC's new warning
>> about unused constraints, where the `OffsetOf` constant on `get` is
>> reported as unnecessary...  I'll file a bug.
>>
>>
>> {-# LANGUAGE TypeFamilies, TypeOperators, UndecidableInstances,
>> DataKinds #-}
>> {-# LANGUAGE ScopedTypeVariables #-}
>>
>> import GHC.TypeLits
>> import Data.Proxy
>> import Data.Word
>> import Foreign.Ptr
>>
>> type OffsetOf l xs = GetOffset 0 l xs
>>
>> type family ByteSize x where
>>   ByteSize Word64   = 8
>>   ByteSize Word32   = 4
>>   ByteSize Word16   = 2
>>   ByteSize Word8= 1
>>   ByteSize a= TypeError (Text "The type " :<>: ShowType a :<>:
>>  Text " is not exportable.")
>>
>> type family GetOffset n (l :: Symbol) xs where
>>   GetOffset n l ( '(l,a) ': xs) = '(n,a)
>>   GetOffset n l ( '(x,a)  : xs) = GetOffset (n+ByteSize a) l xs
>>   GetOffset n l '[] = TypeError (Text "Missing field: " :<>:
>>
>> ShowType l)
>>
>> newtype Struct (a :: [(Symbol,*)]) = Struct (Ptr ())
>>
>>
>> get :: forall l fs n a.
>>   (OffsetOf l fs ~ '(n,a), KnownNat n) =>
>>   Struct fs ->
>>   Proxy l   ->
>>   Ptr a
>> get (Struct p) _ = plusPtr p (fromInteger (natVal (Proxy :: Proxy n)))
>>
>>
>> type MyStruct = [ '("A",Word8), '("B",Word8), '("C",Int) ]
>>
>> testOk :: Struct MyStruct -> Ptr Word8
>> testOk s = get s (Proxy :: Proxy "B")
>>
>>
>> {-
>> testNotOk :: Struct MyStruct -> Ptr Word8
>> testNotOk s = get s (Proxy :: Proxy "X")
>> --}
>>
>> {-
>> type MyOtherStruct = [ '("A",Int), '("B",Word8) ]
>>
>> testNotOk :: Struct MyOtherStruct -> Ptr Word8
>> testNotOk s = get s (Proxy :: Proxy "B")
>> --}
>>
>>
>>
>>
>>
>>
>>
>> On Mon, Nov 16, 2015 at 1:21 PM, Ben Gamari > > wrote:
>>
>>
>> While preparing some additional documentation for Iavor's custom type
>> errors work (which has been merged; thanks Iavor!) I noticed that
>> Dominique Devriese has raised some additional questions on the proposal
>> [1].
>>
>> In particular, Dominique suggests that perhaps TypeError should simply
>> be of kind `ErrorMessage -> Constraint`. My understanding of the
>> proposal is that the intention is that `TypeError`s should be usable on
>> the RHS of type functions, like `error` on the term level. However, is
>> this strictly necessary? Is there any place where you couldn't just as
>> easily express the `TypeError` as a constraint?
>>
>> If not, it seems like this may be substantially simpler approach and
>> totally side-steps the detection of `TypeError` in inappropriate places
>> on the RHS.
>>
>> Regardless, it seems like this (and the other questions) is worth
>> addressing in the proposal.
>>
>> Cheers,
>>
>> - Ben
>>
>>
>> [1]
>> 
>> https://ghc.haskell.org/trac/ghc/wiki/Proposal/CustomTypeErrors#SomedesignquestionsDominiqueDevriese:
>>
>>
>>
>>
>> ___
>> 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: Remote GHCi

2015-11-17 Thread Simon Marlow
So the remote GHCi server I had in mind would be too dumb to support 
this - it would be at a much lower level, with support for linking 
object code and bytecode and evaluation only.  What you probably want 
for this is a remote interface to the GHC API, similar to what 
ide-backend provides.


Cheers,
Simon

On 17/11/2015 10:40, Alan & Kim Zimmerman wrote:

This fits in directly with what I am trying to do for the
haskell-ide-engine, where the intention is to expose ghci via an
asynchronous process with communication via message passing.

A bonus would be to have two separate interfaces, one for REPL
interaction for the user, the other to be able to query properties of
the loaded code.

I am currently investigating exposing Behavior and RunTerm from
haskeline to create a message passing backend instead.

Alan

On 17 Nov 2015 12:11 PM, "Simon Marlow" > wrote:

Hi folks - I've been thinking about changing the way we run
interpreted code so that it would be run in a separate process.  It
turns out this has quite a few benefits, and would let us kill some
of the really awkward hacks we have in GHC to work around problems
that arise because we're running interpreted code and the compiler
on the same runtime.

I summarised the idea here:
https://ghc.haskell.org/trac/ghc/wiki/RemoteGHCi

I'd be interested to hear if anyone has any thoughts around this,
particularly if doing this would make your life difficult in some
way. Are people relying on dynCompileExpr for anything?

Cheers,
Simon
___
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: Further custom type error questions

2015-11-17 Thread Roman Cheplyaka
Iavor, Ben, et al.:

How about much simpler

type family Head (a :: [k]) :: k where
  Head (x ': xs) = x
  Head '[] = Error "Empty list"

Can this be expressed through Error-as-constraint?

On 11/17/2015 02:09 AM, Iavor Diatchki wrote:
> Hello,
> 
> I imagine people wanting to do things as in the example below.  If we
> were to use only `TypeError` constraints, then we'd have to mostly use
> the class system to do type-level evaluation.  It doesn't seem obvious
> how to do that with just `TypeError` of kind constraint, unless all
> evaluation was to happen using the class system. 
> 
> -Iavor
> PS: Interestingly, this example reveals a bug with GHC's new warning
> about unused constraints, where the `OffsetOf` constant on `get` is
> reported as unnecessary...  I'll file a bug.
> 
> 
> {-# LANGUAGE TypeFamilies, TypeOperators, UndecidableInstances,
> DataKinds #-}
> {-# LANGUAGE ScopedTypeVariables #-}
> 
> import GHC.TypeLits
> import Data.Proxy
> import Data.Word
> import Foreign.Ptr
> 
> type OffsetOf l xs = GetOffset 0 l xs
> 
> type family ByteSize x where
>   ByteSize Word64   = 8
>   ByteSize Word32   = 4
>   ByteSize Word16   = 2
>   ByteSize Word8= 1
>   ByteSize a= TypeError (Text "The type " :<>: ShowType a :<>:
>  Text " is not exportable.")
> 
> type family GetOffset n (l :: Symbol) xs where
>   GetOffset n l ( '(l,a) ': xs) = '(n,a)
>   GetOffset n l ( '(x,a)  : xs) = GetOffset (n+ByteSize a) l xs
>   GetOffset n l '[] = TypeError (Text "Missing field: " :<>:
>
> ShowType l)
> 
> newtype Struct (a :: [(Symbol,*)]) = Struct (Ptr ())
> 
> 
> get :: forall l fs n a.
>   (OffsetOf l fs ~ '(n,a), KnownNat n) =>
>   Struct fs ->
>   Proxy l   ->
>   Ptr a
> get (Struct p) _ = plusPtr p (fromInteger (natVal (Proxy :: Proxy n)))
> 
> 
> type MyStruct = [ '("A",Word8), '("B",Word8), '("C",Int) ]
> 
> testOk :: Struct MyStruct -> Ptr Word8
> testOk s = get s (Proxy :: Proxy "B")
> 
> 
> {-
> testNotOk :: Struct MyStruct -> Ptr Word8
> testNotOk s = get s (Proxy :: Proxy "X")
> --}
> 
> {-
> type MyOtherStruct = [ '("A",Int), '("B",Word8) ]
> 
> testNotOk :: Struct MyOtherStruct -> Ptr Word8
> testNotOk s = get s (Proxy :: Proxy "B")
> --}
> 
> 
> 
> 
> 
> 
> 
> On Mon, Nov 16, 2015 at 1:21 PM, Ben Gamari  > wrote:
> 
> 
> While preparing some additional documentation for Iavor's custom type
> errors work (which has been merged; thanks Iavor!) I noticed that
> Dominique Devriese has raised some additional questions on the proposal
> [1].
> 
> In particular, Dominique suggests that perhaps TypeError should simply
> be of kind `ErrorMessage -> Constraint`. My understanding of the
> proposal is that the intention is that `TypeError`s should be usable on
> the RHS of type functions, like `error` on the term level. However, is
> this strictly necessary? Is there any place where you couldn't just as
> easily express the `TypeError` as a constraint?
> 
> If not, it seems like this may be substantially simpler approach and
> totally side-steps the detection of `TypeError` in inappropriate places
> on the RHS.
> 
> Regardless, it seems like this (and the other questions) is worth
> addressing in the proposal.
> 
> Cheers,
> 
> - Ben
> 
> 
> [1]
> 
> https://ghc.haskell.org/trac/ghc/wiki/Proposal/CustomTypeErrors#SomedesignquestionsDominiqueDevriese:
> 
> 
> 
> 
> ___
> 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


Re: [ANNOUNCE] GHC 7.10.3 release candidate 1

2015-11-17 Thread Ben Gamari
Richard Eisenberg  writes:

> On Nov 4, 2015, at 11:12 AM, Peter Trommler  
> wrote:
>
>> It looks like a bug to me.
>
> I'm taking your "it" here to mean the fact that GHC is looking for
> readelf on a Mac OS platform. I tend to agree -- I was surprised to
> see this, but I'm almost-totally clueless about these things.
>
> Thanks for the info,
> Richard
>
> PS: There's been much muttering about call stacks and DWARF. I haven't
> a clue what DWARF is, but I always assumed that this nice feature
> would not be available on Macs. What I realized today is that this
> assumption likely stems from the fact that ELF is not for Mac. ELFs
> and DWARFs tend to be found near one another in other settings, but
> perhaps this fact doesn't carry over to computer architectures. :)
>
DWARF is a standard for expressing debug information about compiled
native programs. It is used by almost all modern operating systems
(including OS X; the only notable exception is Windows, naturally).
Indeed the name is a not-so-subtle reference to the fact that DWARF
debug information will often be found within ELF object files.

Recently I have been working on using the mechanisms that came out of
Peter Wortmann's thesis to provide better stack traces and (statistical)
profiling support for Haskell code. While at the moment I am focusing on
Linux, there is little reason why this couldn't (fairly easily, I
suspect) be extended to work on OS X.

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: Implementation idea for unboxed polymorphic types

2015-11-17 Thread Alexey Vagarenko
At the moment, GHC does not support type families over kind #,
but if it did, would this code do the trick
https://gist.github.com/vagarenko/077c6dd73cd610269aa9 ?

2015-11-16 22:32 GMT+05:00 Ömer Sinan Ağacan :

> > But I don't see why you'd need quoting at constructor calls. Couldn't you
> > just have a type class like `PointFamily`?
>
> This is exactly right, my memory has failed me. My initial implementation
> didn't use the type family trick, I had further attempts that use type
> families
> but honestly I don't remember how good it worked. This was quite a while
> ago.
>
> 2015-11-15 19:41 GMT-05:00 Richard Eisenberg :
> > After reading Francesco's original post, I immediately thought of Ömer's
> proposed approach, of using Template Haskell to produce the right data
> family instances. But I don't see why you'd need quoting at constructor
> calls. Couldn't you just have a type class like `PointFamily`? I'd be more
> interested to see client code in Ömer's version than the TH generation code.
> >
> > The TH approach would seem to require having a fixed set of
> specializations, which is a downside. But I'm not sure it's so much of a
> downside that the approach is unusable.
> >
> > Richard
> >
> > On Nov 15, 2015, at 10:08 AM, Ömer Sinan Ağacan 
> wrote:
> >
> >> I had started working on exactly the same thing at some point. I had a
> >> TemplateHaskell-based implementation which _almost_ worked.
> >>
> >> The problem was that the syntax was very, very heavy. Because I had to
> use
> >> quotes for _every_ constructor application(with explicitly passed
> types).
> >> (because I had a specialized constructor for every instantiation of this
> >> generic type)
> >>
> >> Another problem was that because of how TemplateHaskell quotes
> evaluated, I
> >> couldn't use a `List Int` where `List` is a template without first
> manually
> >> adding a line for generating specialized version of `List` on `Int`.
> >>
> >> When all of these combined it became very hard to use. But it was a
> >> proof-of-concept and I think it worked.
> >>
> >> (Code is horrible so I won't share it here :) I had to maintain a state
> shared
> >> with different TH quote evaluations etc.)
> >>
> >> 2015-11-15 5:26 GMT-05:00 Francesco Mazzoli :
> >>> (A nicely rendered version of this email can be found at <
> https://gist.github.com/bitonic/52cfe54a2dcdbee1b7f3>)
> >>>
> >>> ## Macro types
> >>>
> >>> I very often find myself wanting unboxed polymorphic types
> >>> (e.g. types that contain `UNPACK`ed type variables). I find
> >>> it extremely frustrating that it's easier to write fast _and_
> >>> generic code in C++ than in Haskell.
> >>>
> >>> I'd like to submit to the mailing list a very rough proposal
> >>> on how this could be achieved in a pretty straightforward way
> >>> in GHC.
> >>>
> >>> The proposal is meant to be a proof of concept, just to show that
> >>> this could be done rather easily. I did not think about a nice
> >>> interface or the implementation details in GHC. My goal is to
> >>> check the feasibility of this plan with GHC developers.
> >>>
> >>> I'll call such types "macro types", since their effect is similar
> >>> to defining a macro that defines a new type for each type
> >>> variable instantiation.
> >>>
> >>> Consider
> >>>
> >>> ```
> >>> data #Point a = Point
> >>>  { x :: {-# UNPACK #-} !a
> >>>  , y :: {-# UNPACK #-} !a
> >>>  }
> >>> ```
> >>>
> >>> This definition defines the macro type `#Point`, with one parameter
> >>> `a`.
> >>>
> >>> Macro types definition would be allowed only for single-constructor
> >>> records. The intent is that if we mention `#Point Double`, it will
> >>> be equivalent to
> >>>
> >>> ```
> >>> data PointDouble = PointDouble
> >>>  { x :: {-# UNPACK #-} !Double
> >>>  , y :: {-# UNPACK #-} !Double
> >>>  }
> >>> ```
> >>>
> >>> To use `#Point` generically, the following type class would be
> >>> generated:
> >>>
> >>> ```
> >>> class PointFamily a where
> >>>  data #Point a :: * -- Family of types generated by @data #Point a@.
> >>>  #Point :: a -> a -> #Point a -- Constructor.
> >>>  #x :: #Point a -> a -- Projection @x@.
> >>>  #y :: #Point a -> a -- Projection @y@.
> >>> ```
> >>>
> >>> Thi type class lets us work with `#Point`s generically, for example
> >>>
> >>> ```
> >>> distance :: (PointFamily a, Fractional a) => #Point a -> #Point a -> a
> >>> distance p1 p2 =
> >>>  let dx = #x p1 - #x p2
> >>>  dy = #y p1 - #y p2
> >>>  in sqrt (dx*dx + dy*dy)
> >>> ```
> >>>
> >>> Internally, for every type appearing for `a`, e.g. `#Point Double`,
> >>> a new type equivalent to the `PointDouble` above would be generated
> >>> by GHC, with the corresponding instance
> >>>
> >>> ```
> >>> instance PointFamily Double where
> >>>  data #Point Double = PointDouble
> >>>  #x = x
> >>>  #y = x
> >>> ```
> >>>
> >>> If it's not possible to instantiate `#Point` with the provided type
> >>> (for example 

RE: [commit: ghc] master: Remove PatSynBuilderId (2208011)

2015-11-17 Thread Ben Gamari
Simon Peyton Jones  writes:

> |  I don't think this would work in the case where there are no fields
> |  initialised?
>
> Oh yes, silly me. I was thinking that then we wouldn’t need to look at
> 'labels' at all, but that's not true.
>
> Well, at least then I'd replace [PostTc id [FieldLabel] with (PostTc
> ConLike). This makes it like ConPatOut in HsPat. Then the (Located id)
> field is redundant (we can get it from the ConLike), but that’s only
> true after typechecking, so maybe simpler to keep both.
>
> It amounts to moving the call to conLikeFieldLabels from tcExpr
> (RecordCon ...) to dsExpr (RecordCon ...). A small thing but I think
> it'd be better.
>
Mathew, did you ever get to this?

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


Feature status for GHC 8.0

2015-11-17 Thread Ben Gamari

tldr. Please let us know the status of your patches for GHC 8.0.


Hello everyone!

You are receiving this message because you responsible for one of the
in-flight items on the GHC 8.0 roadmap [1].

As you may know, the release is quickly approaching and we'd like to
have final patches up for review in the next week or so. Until then we'd
like to get an idea of how your various projects are progressing.

Below is a list of the projects which we believe are still in progress
along with my understanding of the state of your work. If you see
your name in this list please let us know how things are going.


 * OverloadedRecordFields  Adam Gundry
  Documentation needed
  Full ORF not happening?

 * Kind equality Richard Eisenberg
  Patches coming soon?

 * GADT pattern matching rework George Karachalias
  How is this coming along?

 * LLVM backend   Austin Seipp
  Patches coming

 * Pattern synonyms  Matthew Pickering
  Documentation needed
  (ongoing work in D1325)

 * Backpack workEdward Z. Yang
  How is this coming along?

 * Compact regions   Giovanni Campagna
  Patches need revision Edward Z. Yang

 * Type signature sections  Herbert Valerio Riedel
  Not pushing for 8.0?

 * DWARF-based stack traces and Ben Gamari
   statistical profiling
  Patches slowly being merged
  Documentation needed


Thanks for all of your hard work!

Cheers,

- Ben


[1] https://ghc.haskell.org/trac/ghc/wiki/Status/GHC-8.0.1


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


Re: too many lines too long

2015-11-17 Thread Richard Eisenberg
We have such a thing: 
https://ghc.haskell.org/trac/ghc/wiki/Commentary/CodingStyle

I don't think its widely consulted or respected, though.

Richard

On Nov 17, 2015, at 5:19 AM, Simon Marlow  wrote:

> On 13/11/2015 15:01, Jan Stolarek wrote:
>> My view on this is:
>> 
>> Firstly, I hate explaining myself to Arcanist. When prompted to explain the 
>> reason for too long
>> lines I typically enter "wontfix" without thinking too much.
>> 
>> Secondly, I really don't like how warnings clutter code reviews.
>> 
>> I have my Emacs highlight text beyond 80th column with a really ugly colour, 
>> so I strive real hard
>> to maintain 80-column limit whenever possible. But sometimes fitting in that 
>> limit is nearly
>> impossible: imagine being in a let nested in a do-notation nested in a guard 
>> nested in a where
>> clause. Approx. 15-20 columns are lost for the indentation. Nevertheless I 
>> would support
>> introducing a hard limit on having no more than 80 columns.
>> 
>> Janek
>> 
>> PS. It makes me really sad that we don't have any coding convention for GHC: 
>> we mix camelCase with
>> underscore_case, indentation is inconsistent (good thing we at least got rid 
>> of tabs!),
>> whitespace usage is inconsistent, etc. I could make this list very long.
> 
> Why not write down a set of style guidelines and get everyone to agree to 
> them?  I'd happily compromise my personal stylistic preferences if there was 
> a standard style that we all agreed on and tried to adhere to.
> 
> Personally I think a good starting point is 
> http://chrisdone.github.io/hindent/HIndent-Styles-JohanTibell.html
> 
> Incidentally the mixed camelCase and underscore style is deliberate: 
> underscores for local identifiers, camelCase for exported functions. It's a 
> cute idea I've been using for a long time, but we don't have to do it that 
> way.  At work we use camelCase exclusively and it's fine.
> 
> Cheers,
> Simon
> 
>> ---
>> Politechnika Łódzka
>> Lodz University of Technology
>> 
>> Treść tej wiadomości zawiera informacje przeznaczone tylko dla adresata.
>> Jeżeli nie jesteście Państwo jej adresatem, bądź otrzymaliście ją 
>> przez pomyłkę
>> prosimy o powiadomienie o tym nadawcy oraz trwałe jej usunięcie.
>> 
>> This email contains information intended solely for the use of the 
>> individual to whom it is addressed.
>> If you are not the intended recipient or if you have received this message 
>> in error,
>> please notify the sender and delete it from your system.
>> ___
>> 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: Remote GHCi

2015-11-17 Thread Richard Eisenberg
How does this interact with typechecker plugins? I assume they would still 
happen in GHC's process.

I've also been thinking about designing and implementing a mechanisms where 
programmers could specify custom pretty-printers for their types, and GHC would 
use these pretty-printers in error messages. This action would also probably 
need to be in the same process.

Would either of these ideas be affected? My guess is "no", because we should be 
able to be selective in what gets farmed out to the second process and what 
stays locally.

Richard

On Nov 17, 2015, at 5:10 AM, Simon Marlow  wrote:

> Hi folks - I've been thinking about changing the way we run interpreted code 
> so that it would be run in a separate process.  It turns out this has quite a 
> few benefits, and would let us kill some of the really awkward hacks we have 
> in GHC to work around problems that arise because we're running interpreted 
> code and the compiler on the same runtime.
> 
> I summarised the idea here: https://ghc.haskell.org/trac/ghc/wiki/RemoteGHCi
> 
> I'd be interested to hear if anyone has any thoughts around this, 
> particularly if doing this would make your life difficult in some way. Are 
> people relying on dynCompileExpr for anything?
> 
> Cheers,
> Simon
> ___
> 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: too many lines too long

2015-11-17 Thread Alexander Berntsen
-BEGIN PGP SIGNED MESSAGE-
Hash: SHA512

On 17/11/15 15:15, Richard Eisenberg wrote:
> We have such a thing:
> https://ghc.haskell.org/trac/ghc/wiki/Commentary/CodingStyle
> 
> I don't think its widely consulted or respected, though.
There are several issues here. (Get rid of tabs v. spaces for
instance.) In general it's just too complicated. Successful coding
guidelines are in my experience a line or two to explain each point,
and then an example or two.

Anyway, I read these, but quickly enough found out that the best
strategy was to just try to fit in with the existing code.

We should simplify them and make a more pretty site for them.
Something like [0], although that's a bit wordy for my taste.

Then we need to decide on how to "get there". E.g. do we enforce all
new files to follow it rigorously, but adhere to the dominating style
of the file you are changing? Do we change the function we are
modifying in a patch to adhere to the style? Do we just go through
everything all at once and fix it once and for all, like with tabs?
I'm not voting for any of them right now, but we need to consider them.

[0]  
- -- 
Alexander
alexan...@plaimi.net
https://secure.plaimi.net/~alexander
-BEGIN PGP SIGNATURE-
Version: GnuPG v2

iQIcBAEBCgAGBQJWSzo8AAoJENQqWdRUGk8BuYkQAMVLUfgdYaaduhTCeDBSACjC
9iP8AcmmTsMPbEcSvIA3u2c5wDSxJe1v4kJcglftylcCwLNZQgcVy9k05HlbRbDP
CCUS/Glv1TM+s79xueH3ByispjrhZt7yJgdJ5SJbe43i9KyjAG+TaqfgyJRL5oiw
4VKRAfoT2RYm6cjG1WlnzGzDh4QF3y8F9MCZWVgAMbAIDU0gKyR1Mxpf3xSXb02y
ObbCKiA3qqITqfjs1ZHXwaJqbg/F21uELS+veGZN149ylimm0zpVzolx9mRgYASv
t/b20+qBtDBr/K0BQ/ZPzgx0d9TaYiGF2Jd1AE+m9P9cqPD7qPqljI2/G4Vn0g61
pEburlt4OdSdMlUCmsf3lXBDUMQrXDjBRkh8zMirlt/BzC9a6+9JOfjLixgFlDSV
ohy3XmQVokeDWrcFmxz0FPWinU4P+5uQos0Jp/sO+fukRkormM089UYB7vRZVOn9
GtaBCA5FQSvgqfLbDpPDRHfYka5qLPXo9dKtyjjhqEXggwlVCys5rrF+y1B4qs9A
XgENKexKtsg7aGc99KZh3t2rF7/jwKsdcVnAbEbyEUvZ9fqvtwZO6DN32YLjNLoV
McVeGkLWhtw+ihD/E6VueUxk0ImCr8CpGGMxW7WvyPlQW3v/seU3l7Qezh1PkRZ/
jvj8PUJfGZA/GEZALpIv
=tY36
-END PGP SIGNATURE-
___
ghc-devs mailing list
ghc-devs@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs


Re: Remote GHCi

2015-11-17 Thread Sumit Sahrawat, Maths & Computing, IIT (BHU)
The use-case which I've worked on deals with widget messages. Widgets are
stored inside the kernel, and can recieve signals from user code, frontend
events etc.

To capture messages sent by the user code, the messages are queued in a
TChan inside the interpreter environment. Messages from this TChan are
extracted into the kernel using dynCompileExpr and fromDynamic, and
processed as required.

The user input code is executed in the interpreter context, but we also
need to gather information some more information from the context, which is
why dynCompileExpr is crucial there.

On 17 November 2015 at 19:59, Richard Eisenberg  wrote:

> How does this interact with typechecker plugins? I assume they would still
> happen in GHC's process.
>
> I've also been thinking about designing and implementing a mechanisms
> where programmers could specify custom pretty-printers for their types, and
> GHC would use these pretty-printers in error messages. This action would
> also probably need to be in the same process.
>
> Would either of these ideas be affected? My guess is "no", because we
> should be able to be selective in what gets farmed out to the second
> process and what stays locally.
>
> Richard
>
> On Nov 17, 2015, at 5:10 AM, Simon Marlow  wrote:
>
> > Hi folks - I've been thinking about changing the way we run interpreted
> code so that it would be run in a separate process.  It turns out this has
> quite a few benefits, and would let us kill some of the really awkward
> hacks we have in GHC to work around problems that arise because we're
> running interpreted code and the compiler on the same runtime.
> >
> > I summarised the idea here:
> https://ghc.haskell.org/trac/ghc/wiki/RemoteGHCi
> >
> > I'd be interested to hear if anyone has any thoughts around this,
> particularly if doing this would make your life difficult in some way. Are
> people relying on dynCompileExpr for anything?
> >
> > Cheers,
> > Simon
> > ___
> > 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
>



-- 
Regards

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


Re: Remote GHCi

2015-11-17 Thread Andrew Gibiansky
Simon,

As Sumit said, we use dynCompileExpr for core functionality of IHaskell. I
am not really sure how the change you are proposing affects that, though.

We use dynCompileExpr in several places for evaluation inside the
interpreter context:

1. Evaluating a Haskell expression in the interpreter context, converting
the result to a ByteString, then using fromDynamic to extract the
bytestring and convert it to a value in the compiled context.
2. Getting a file handle from the interpreter context to the compiled
context; this does not actually use dynCompileExpr because there were some
bugs with dynCompileExpr and so I had to literally copy source from
InteractiveEval to reimplement parts of dynCompileExpr (unrelated: the
issue was that dyncompileexpr imported and then unimported Data.Dynamic,
and this messed with data declarations that had already been created in the
interpreter context)
3. Extracting IO a values from the interpreted context to the compiled
context so that they could be run; this is necessary to get displayed
values from the interpreter back to the compiled code.

I think two of our uses, which are both very central to the way IHaskell
works, would be impacted by requiring a Binary instance (or similar), which
is what I think you are proposing (since we have two uses at least where we
marshall `IO x` values via dynCompileExpr, which cannot be serialized, I
believe.)

I am sure that there are alternative ways to do what we are doing, but they
are probably not simple and would take quite a bit of work.

-- Andrew

On Tue, Nov 17, 2015 at 6:29 AM, Richard Eisenberg 
wrote:

> How does this interact with typechecker plugins? I assume they would still
> happen in GHC's process.
>
> I've also been thinking about designing and implementing a mechanisms
> where programmers could specify custom pretty-printers for their types, and
> GHC would use these pretty-printers in error messages. This action would
> also probably need to be in the same process.
>
> Would either of these ideas be affected? My guess is "no", because we
> should be able to be selective in what gets farmed out to the second
> process and what stays locally.
>
> Richard
>
> On Nov 17, 2015, at 5:10 AM, Simon Marlow  wrote:
>
> > Hi folks - I've been thinking about changing the way we run interpreted
> code so that it would be run in a separate process.  It turns out this has
> quite a few benefits, and would let us kill some of the really awkward
> hacks we have in GHC to work around problems that arise because we're
> running interpreted code and the compiler on the same runtime.
> >
> > I summarised the idea here:
> https://ghc.haskell.org/trac/ghc/wiki/RemoteGHCi
> >
> > I'd be interested to hear if anyone has any thoughts around this,
> particularly if doing this would make your life difficult in some way. Are
> people relying on dynCompileExpr for anything?
> >
> > Cheers,
> > Simon
> > ___
> > 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: Remote GHCi

2015-11-17 Thread Alan & Kim Zimmerman
This fits in directly with what I am trying to do for the
haskell-ide-engine, where the intention is to expose ghci via an
asynchronous process with communication via message passing.

A bonus would be to have two separate interfaces, one for REPL interaction
for the user, the other to be able to query properties of the loaded code.

I am currently investigating exposing Behavior and RunTerm from haskeline
to create a message passing backend instead.

Alan
On 17 Nov 2015 12:11 PM, "Simon Marlow"  wrote:

> Hi folks - I've been thinking about changing the way we run interpreted
> code so that it would be run in a separate process.  It turns out this has
> quite a few benefits, and would let us kill some of the really awkward
> hacks we have in GHC to work around problems that arise because we're
> running interpreted code and the compiler on the same runtime.
>
> I summarised the idea here:
> https://ghc.haskell.org/trac/ghc/wiki/RemoteGHCi
>
> I'd be interested to hear if anyone has any thoughts around this,
> particularly if doing this would make your life difficult in some way. Are
> people relying on dynCompileExpr for anything?
>
> Cheers,
> Simon
> ___
> 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: Remote GHCi

2015-11-17 Thread Luite Stegeman
I like this idea, and it overlaps very much with the work that still needs
to be done for GHCJSi. I think that for Template Haskell, the restriction
that everything has to be marshalled via Binary is not too problematic,
although it'd require a bit of care if Richard's pre-proposal to expose
more GHC types to TH ( #11081 ) is to be implemented. In particular, the
API for querying the type environment would have to remain implementable
via message passing, so we can't expose the full TcRn there.

compileExpr / dynCompileExpr seem to get some use, perhaps mostly through
the hint package:

http://packdeps.haskellers.com/reverse/hint

But I think the most common use case is just compiling and running Haskell
expressions, without any specific need for interpreted code. The machinery
behind hint could be reworked to have the GHC API produce a dynamic library
for the compiled expression, which could then be loaded into the current
process with the system linker. Or is there some reason that  this approach
would be unusable?

luite

On Tue, Nov 17, 2015 at 10:10 AM Simon Marlow  wrote:

> Hi folks - I've been thinking about changing the way we run interpreted
> code so that it would be run in a separate process.  It turns out this
> has quite a few benefits, and would let us kill some of the really
> awkward hacks we have in GHC to work around problems that arise because
> we're running interpreted code and the compiler on the same runtime.
>
> I summarised the idea here:
> https://ghc.haskell.org/trac/ghc/wiki/RemoteGHCi
>
> I'd be interested to hear if anyone has any thoughts around this,
> particularly if doing this would make your life difficult in some way.
> Are people relying on dynCompileExpr for anything?
>
> Cheers,
> Simon
>
___
ghc-devs mailing list
ghc-devs@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs


Re: Remote GHCi

2015-11-17 Thread Luite Stegeman
I've been thinking of these applications before, in the context of cross
compilers, and of how to deal with these things as dependencies.

Custom error message formatting could be done in the same way as Template
Haskell I think, since there appears to be a reasonably well-defined place
where these are needed, and the cost of marshalling the data  does not look
prohibitive for this application. It could run in the Quasi monad (which
would perhaps get some extensions) with type similar to

formatError :: Quasi m => TypeError -> m (Maybe Doc)

(IDE people will argue that errors shouldn't be formatted as Doc, some
structured error message format is needed, we could add that later)

Two questions:
- Which formatters would be loaded by GHC? Would libraries supply
formatters that automatically get loaded by everything that depends on the
package?
- How would GHC decide which formatter(s) to call for a specific error?

As for typechecker (and also core-to-core) plugins:

Am I right in thinking that these can usually be treated as a separate
build tool, where having it in a separate package is not too problematic?
This way, plugins could be loaded from dynamic libraries at startup (or for
platforms where this is problematic, GHC could bootstrap itself by linking
the plugins statically). Plugins would be built for the host platform, so
GHC's package database, which lists packages for the target platform, may
not be relevant at all. Cabal would only need to check whether GHC can
somehow load pluginpackage-x.y.z before proceeding with the build.

I like the idea of extending GHC in various places, but for GHCJS I do need
a somewhat workable story for cross-compilation.

(Of course I could make GHCJS a non-crosscompiler, by compiling the whole
compiler to JS and running everything in a JS runtime; everything would
magically work again, but that's a bit too deep down the rabbit-hole for me
at the time...)

luite

Am I right in thinking that typechecker plugins are a special
On Tue, Nov 17, 2015 at 2:30 PM Richard Eisenberg  wrote:

> How does this interact with typechecker plugins? I assume they would still
> happen in GHC's process.
>
> I've also been thinking about designing and implementing a mechanisms
> where programmers could specify custom pretty-printers for their types, and
> GHC would use these pretty-printers in error messages. This action would
> also probably need to be in the same process.
>
> Would either of these ideas be affected? My guess is "no", because we
> should be able to be selective in what gets farmed out to the second
> process and what stays locally.
>
> Richard
>
> On Nov 17, 2015, at 5:10 AM, Simon Marlow  wrote:
>
> > Hi folks - I've been thinking about changing the way we run interpreted
> code so that it would be run in a separate process.  It turns out this has
> quite a few benefits, and would let us kill some of the really awkward
> hacks we have in GHC to work around problems that arise because we're
> running interpreted code and the compiler on the same runtime.
> >
> > I summarised the idea here:
> https://ghc.haskell.org/trac/ghc/wiki/RemoteGHCi
> >
> > I'd be interested to hear if anyone has any thoughts around this,
> particularly if doing this would make your life difficult in some way. Are
> people relying on dynCompileExpr for anything?
> >
> > Cheers,
> > Simon
> > ___
> > 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: Window build broken

2015-11-17 Thread Simon Peyton Jones
It says this:

bash$ file libraries/ghc-prim/dist-install/build/HSghc-prim-0.5.0.0.o 
libraries/ghc-prim/dist-install/build/HSghc-prim-0.5.0.0.o: PE Unknown PE 
signature 0x742e x86-64 (stripped to external PDB), for MS Windows

| -Original Message-
| From: David Macek [mailto:david.mace...@gmail.com]
| Sent: 17 November 2015 22:45
| To: Simon Peyton Jones ; ghc-devs@haskell.org
| Subject: Re: Window build broken
| 
| On 17. 11. 2015 23:31, Simon Peyton Jones wrote:
| > Sigh.  My Windows build is broken.  See below.  Any ideas?  The stage2
| complier in non-interactive mode works ok. It’s just ghci fails.  What does
| “Not x86_64 PEi386” mean?  What can I do to fix?
| 
| Maybe it's obvious and you already checked, but could it be that the object
| file is for a different architecture? What does `file` say about it?
| 
| --
| David Macek

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


Re: Window build broken

2015-11-17 Thread David Macek
On 17. 11. 2015 23:31, Simon Peyton Jones wrote:
> Sigh.  My Windows build is broken.  See below.  Any ideas?  The stage2 
> complier in non-interactive mode works ok. It’s just ghci fails.  What does 
> “Not x86_64 PEi386” mean?  What can I do to fix?

Maybe it's obvious and you already checked, but could it be that the object 
file is for a different architecture? What does `file` say about it?

-- 
David Macek



smime.p7s
Description: S/MIME Cryptographic Signature
___
ghc-devs mailing list
ghc-devs@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs


Re: Window build broken

2015-11-17 Thread Ben Gamari
Simon Peyton Jones  writes:

> Sigh. My Windows build is broken. See below. Any ideas? The stage2
> complier in non-interactive mode works ok. It’s just ghci fails. What
> does “Not x86_64 PEi386” mean? What can I do to fix?
> 
> I should say that my laptop broke so this is a new Windows machine,
> presumably with a slightly different config…
>
Hmm, very interesting. I hope this isn't the result of acce37f38bc3,
which directly touched the Windows linker. Do you have this commit by
any chance?

I'll try to reproduce tomorrow.

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: Window build broken

2015-11-17 Thread lonetiger
Hi Simon,

I’m wondering what environment you’re coming in, is it msys2? The prompt you 
showed earlier
/cygdrive/c/code/HEAD-1$
Looks like cygwin.

Tamar

From: Simon Peyton Jones
Sent: Wednesday, November 18, 2015 00:25
To: David Macek;ghc-devs@haskell.org
Subject: RE: Window build broken


It says this:

bash$ file libraries/ghc-prim/dist-install/build/HSghc-prim-0.5.0.0.o 
libraries/ghc-prim/dist-install/build/HSghc-prim-0.5.0.0.o: PE Unknown PE 
signature 0x742e x86-64 (stripped to external PDB), for MS Windows

| -Original Message-
| From: David Macek [mailto:david.mace...@gmail.com]
| Sent: 17 November 2015 22:45
| To: Simon Peyton Jones ; ghc-devs@haskell.org
| Subject: Re: Window build broken
| 
| On 17. 11. 2015 23:31, Simon Peyton Jones wrote:
| > Sigh.  My Windows build is broken.  See below.  Any ideas?  The stage2
| complier in non-interactive mode works ok. It’s just ghci fails.  What does
| “Not x86_64 PEi386” mean?  What can I do to fix?
| 
| Maybe it's obvious and you already checked, but could it be that the object
| file is for a different architecture? What does `file` say about it?
| 
| --
| David Macek

___
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: Window build broken

2015-11-17 Thread Ryan Scott
Wow, I happened to try building GHC on Windows for the first time ever
today, and I also experienced this error :)

Interestingly, someone reported a very similar error to this on Trac,
but for GHC 7.8.3 [1]. Here's where the error message comes from [2]
in Linker.c:

static int verifyCOFFHeader
(COFF_header *hdr, pathchar *fileName)
{
  if (hdr->Machine != 0x8664) {
errorBelch("%" PATH_FMT ": Not x86_64 PEi386", fileName);
return 0;
  }
  ...
}

Ryan S.
-
[1] https://ghc.haskell.org/trac/ghc/ticket/10437
[2] 
https://github.com/ghc/ghc/blob/233d1312bf15940fca5feca6884f965e7944b555/rts/Linker.c#L3355
___
ghc-devs mailing list
ghc-devs@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs


RE: Window build broken

2015-11-17 Thread lonetiger
Well the error is correct, it’s just checking against the machine type in the 
PE spec:

IMAGE_FILE_MACHINE_AMD64
0x8664
x64
So somewhere along the line an invalid PE file was generated (or for the wrong 
architecture).

From: Ryan Scott
Sent: Wednesday, November 18, 2015 00:44
To: ghc-devs@haskell.org
Subject: Re: Window build broken


Wow, I happened to try building GHC on Windows for the first time ever
today, and I also experienced this error :)

Interestingly, someone reported a very similar error to this on Trac,
but for GHC 7.8.3 [1]. Here's where the error message comes from [2]
in Linker.c:

static int verifyCOFFHeader
(COFF_header *hdr, pathchar *fileName)
{
  if (hdr->Machine != 0x8664) {
errorBelch("%" PATH_FMT ": Not x86_64 PEi386", fileName);
return 0;
  }
  ...
}

Ryan S.
-
[1] https://ghc.haskell.org/trac/ghc/ticket/10437
[2] 
https://github.com/ghc/ghc/blob/233d1312bf15940fca5feca6884f965e7944b555/rts/Linker.c#L3355
___
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: Remote GHCi

2015-11-17 Thread Manuel M T Chakravarty
Hi Simon,

While this is an interesting proposal, Haskell for Mac strongly relies on 
running interpreted code in the same process. I’m using ’dynCompileExpr’ as 
well as ’hscStmtWithLocation’ and some other stuff. This is quite crucial for 
some of the interactive functionality. Imagine a game where the game engine is 
in Swift linked into the main application and the game logic is in 
*interpreted* Haskell code. The engine calls into the Haskell code multiple 
times per frame of the animation and for all keyboard/mouse/etc input (using 
StablePtr and ForeignPtr to construct the scene graph across the Swift and 
Haskell heap).

This is an intricate dance (e.g, exceptions in either language don’t play nice 
across the language boundary and using multi-threading in both worlds adds to 
the fun), but it allows for a very nice interactive and responsive user 
experience.

I actually also might have a use for the architecture that you are proposing. 
However, I really would like to keep the ability to, at least, optionally run 
interpreted code in the same process (without profiling etc). Do you think we 
could have both?

Cheers,
Manuel

> Simon Marlow :
> 
> Hi folks - I've been thinking about changing the way we run interpreted code 
> so that it would be run in a separate process.  It turns out this has quite a 
> few benefits, and would let us kill some of the really awkward hacks we have 
> in GHC to work around problems that arise because we're running interpreted 
> code and the compiler on the same runtime.
> 
> I summarised the idea here: https://ghc.haskell.org/trac/ghc/wiki/RemoteGHCi
> 
> I'd be interested to hear if anyone has any thoughts around this, 
> particularly if doing this would make your life difficult in some way. Are 
> people relying on dynCompileExpr for anything?
> 
> Cheers,
> Simon
> ___
> 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: Remote GHCi

2015-11-17 Thread Edward Z. Yang
I like it.

Let me make sure that I've understand this correctly:

- While GHC doesn't need to be built with profiling if you
  want to use profiling in the interpeter, you will need
  multiple versions of the "server binary" for each way
  you want to implement.  This should be pretty reasonable,
  because the server binary is a lot smaller than GHC.

- It seems that GHC will ship bytecode and object code
  to the server binary.  In this case, the interpeted
  code and compiled code CAN share data among each other;
  it is just when you want to share data with GHC that
  you must implement serialization.  (Also, external
  bytecode format?!)

- Many people have commented that their extensions use
  dynCompileExpr.  I think these cases can be accommodated,
  by making the server binary not a standalone application,
  but a LIBRARY which can be linked against a custom
  application (e.g. IHaskell).  The messages to be sent
  should not be the values/file descriptors, but the
  invocations that are being requested of GHC. Unfortunately,
  this does seem to imply that most things would have to
  be rewritten from scratch to not use the ghc-api, but
  use whatever this new library's interface over the message
  passing is.

Honestly, it seems like the hard part is defining the message-passing
protocol, esp. since the GHC API is as overgrown as it is today.

Edward

Excerpts from Simon Marlow's message of 2015-11-17 02:10:55 -0800:
> Hi folks - I've been thinking about changing the way we run interpreted 
> code so that it would be run in a separate process.  It turns out this 
> has quite a few benefits, and would let us kill some of the really 
> awkward hacks we have in GHC to work around problems that arise because 
> we're running interpreted code and the compiler on the same runtime.
> 
> I summarised the idea here: https://ghc.haskell.org/trac/ghc/wiki/RemoteGHCi
> 
> I'd be interested to hear if anyone has any thoughts around this, 
> particularly if doing this would make your life difficult in some way. 
> Are people relying on dynCompileExpr for anything?
> 
> Cheers,
> Simon
___
ghc-devs mailing list
ghc-devs@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs


Re: [ANNOUNCE] GHC 7.10.3 release candidate 1

2015-11-17 Thread Carter Schonwald
I'd be keen to see Mac support.  How can I help out to test that for 8.0?

On Tuesday, November 17, 2015, Ben Gamari  wrote:

> Richard Eisenberg > writes:
>
> > On Nov 4, 2015, at 11:12 AM, Peter Trommler <
> peter.tromm...@th-nuernberg.de > wrote:
> >
> >> It looks like a bug to me.
> >
> > I'm taking your "it" here to mean the fact that GHC is looking for
> > readelf on a Mac OS platform. I tend to agree -- I was surprised to
> > see this, but I'm almost-totally clueless about these things.
> >
> > Thanks for the info,
> > Richard
> >
> > PS: There's been much muttering about call stacks and DWARF. I haven't
> > a clue what DWARF is, but I always assumed that this nice feature
> > would not be available on Macs. What I realized today is that this
> > assumption likely stems from the fact that ELF is not for Mac. ELFs
> > and DWARFs tend to be found near one another in other settings, but
> > perhaps this fact doesn't carry over to computer architectures. :)
> >
> DWARF is a standard for expressing debug information about compiled
> native programs. It is used by almost all modern operating systems
> (including OS X; the only notable exception is Windows, naturally).
> Indeed the name is a not-so-subtle reference to the fact that DWARF
> debug information will often be found within ELF object files.
>
> Recently I have been working on using the mechanisms that came out of
> Peter Wortmann's thesis to provide better stack traces and (statistical)
> profiling support for Haskell code. While at the moment I am focusing on
> Linux, there is little reason why this couldn't (fairly easily, I
> suspect) be extended to work on OS X.
>
> Cheers,
>
> - Ben
>
___
ghc-devs mailing list
ghc-devs@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs


Remote GHCi

2015-11-17 Thread Simon Marlow
Hi folks - I've been thinking about changing the way we run interpreted 
code so that it would be run in a separate process.  It turns out this 
has quite a few benefits, and would let us kill some of the really 
awkward hacks we have in GHC to work around problems that arise because 
we're running interpreted code and the compiler on the same runtime.


I summarised the idea here: https://ghc.haskell.org/trac/ghc/wiki/RemoteGHCi

I'd be interested to hear if anyone has any thoughts around this, 
particularly if doing this would make your life difficult in some way. 
Are people relying on dynCompileExpr for anything?


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