Re: OVERLAPPABLE/OVERLAPPING/OVERLAPS pragmas are confusing

2015-08-25 Thread Iavor Diatchki
Johan,

to summarize:

1. If an instance is marked as OVERLAPPABLE, then clients may overlap it
without having any pragmas
2. If an instance is NOT marked OVERLAPPABLE, then clients may still
overlap it, but then they have to use an explicit OVERLAPPING pragma.

So you should either add OVERLAPPABLE to your library, and then clients
don't need to do anything, or
you should remove it, and require that clients add OVERLAPPING.

Note that using this mechanism across modules can be quite error prone.
For example, you have to be very careful
not to use an OVERLAPPABLE instance in your library, as if you do parts of
the program might end up using
one instance, and other parts may end up using another instance---GHC has
no way of knowing about overlapping
instance in client libraries, so it will simply use the best possible
*local* instance.

-Iavor













On Tue, Aug 25, 2015 at 8:46 AM, Mikhail Glushenkov 
the.dead.shall.r...@gmail.com wrote:

 Hi,

 On 25 August 2015 at 14:18, Johan Tibell johan.tib...@gmail.com wrote:
  The proposed change to my library is here:
  https://github.com/tibbe/cassava/pull/95/files
 
  We remove the OverlappingInstances pragma and instead add an OVERLAPPABLE
  pragma like so:
 
  instance {-# OVERLAPPABLE #-} FromField a = FromField (Maybe a)
 where
 
  This causes clients of the library that previously compiled (e.g. the
  music-parts package) to no longer compile, due to a now lacking
 OVERLAPPING
  pragma in their code.

 No, it's not quite like that. Client code can start to break when {-#
 LANGUAGE OverlappingInstances #-} is removed, as happened with the
 music-parts package. Adding an OVERLAPPABLE pragma to cassava's code
 made that error go away.

 Client code can usually work around the problem of missing
 OVERLAPPABLE pragmas in the library by adding OVERLAPPING pragmas to
 their instances. The reason I suggested bumping cassava's version is
 that there may be some places in cassava that still need new pragmas
 that I've overlooked.

 If GHC had an option for detecting overlapping instances at definition
 site, that'd help, I think, since then it'd be easier to find
 instances that need new pragmas.
 ___
 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: OVERLAPPABLE/OVERLAPPING/OVERLAPS pragmas are confusing

2015-08-25 Thread Mikhail Glushenkov
Hi,

On 25 August 2015 at 14:18, Johan Tibell johan.tib...@gmail.com wrote:
 The proposed change to my library is here:
 https://github.com/tibbe/cassava/pull/95/files

 We remove the OverlappingInstances pragma and instead add an OVERLAPPABLE
 pragma like so:

 instance {-# OVERLAPPABLE #-} FromField a = FromField (Maybe a) where

 This causes clients of the library that previously compiled (e.g. the
 music-parts package) to no longer compile, due to a now lacking OVERLAPPING
 pragma in their code.

No, it's not quite like that. Client code can start to break when {-#
LANGUAGE OverlappingInstances #-} is removed, as happened with the
music-parts package. Adding an OVERLAPPABLE pragma to cassava's code
made that error go away.

Client code can usually work around the problem of missing
OVERLAPPABLE pragmas in the library by adding OVERLAPPING pragmas to
their instances. The reason I suggested bumping cassava's version is
that there may be some places in cassava that still need new pragmas
that I've overlooked.

If GHC had an option for detecting overlapping instances at definition
site, that'd help, I think, since then it'd be easier to find
instances that need new pragmas.
___
ghc-devs mailing list
ghc-devs@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs


www.haskell.org/ghc

2015-08-25 Thread Richard Eisenberg
Hi all,

I want to write a URL to represent GHC. It seems that www.haskell.org/ghc is 
the right one. But that page is quite ugly! A full redesign is always a 
challenge, so I'll make a simple request: remove announcements of old releases, 
for some definition of old. (I suggest: all releases from current major version 
+ last release from previous major version.) Right now, I have to scroll down 
to get to What is GHC? and it's a little embarrassing.

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


Re: www.haskell.org/ghc

2015-08-25 Thread David Laing
Hi,

A low-effort alternative would be to swap the order of the 'Latest News'
and 'What is GHC?' sections.

Cheers,

Dave

On Wed, Aug 26, 2015 at 2:21 PM, dongen don...@cs.ucc.ie wrote:

 * Richard Eisenberg e...@cis.upenn.edu [2015-08-25 22:34:16 -0400]:

 : I want to write a URL to represent GHC. It seems that
 : www.haskell.org/ghc is the right one. But that page is quite ugly!
 : A full redesign is always a challenge, so I'll make a simple request:
 : remove announcements of old releases, for some definition of old.
 : (I suggest: all releases from current major version + last release
 : from previous major version.) Right now, I have to scroll down to
 : get to What is GHC? and it's a little embarrassing.

 Thanks Richard. You could also put in a _release history_ hyperlink
 to a separate page.

 Regards,


 Marc van Dongen
 ___
 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: question about GHC API on GHC plugin

2015-08-25 Thread Ömer Sinan Ağacan
It seems like in your App syntax you're having a non-function in function
position. You can see this by looking at what failing function
(splitFunTy_maybe) is doing:

splitFunTy_maybe :: Type - Maybe (Type, Type)
-- ^ Attempts to extract the argument and result types from a type
... (definition is not important) ...

Then it's used like this at the error site:

(arg_ty, res_ty) = expectJust cpeBody:collect_args $
   splitFunTy_maybe fun_ty

In your case this function is returning Nothing and then exceptJust is
signalling the panic.

Your code looked correct to me, I don't see any problems with that. Maybe you're
using something wrong as selectors. Could you paste CoreExpr representation of
your program?

It may also be the case that the panic is caused by something else, maybe your
syntax is invalidating some assumptions/invariants in GHC but it's not
immediately checked etc. Working at the Core level is frustrating at times.

Can I ask what kind of plugin are you working on?

(Btw, how did you generate this representation of AST? Did you write it
manually? If you have a pretty-printer, would you mind sharing it?)

2015-08-25 18:50 GMT-04:00 Mike Izbicki m...@izbicki.me:
 Thanks Ömer!

 I'm able to get dictionaries for the superclasses of a class now, but
 I get an error whenever I try to get a dictionary for a
 super-superclass.  Here's the Haskell expression I'm working with:

 test1 :: Floating a = a - a
 test1 x1 = x1+x1

 The original core is:

 + @ a $dNum_aJu x1 x1

 But my plugin is replacing it with the core:

 + @ a ($p1Fractional ($p1Floating $dFloating_aJq)) x1 x1

 The only difference is the way I'm getting the Num dictionary.  The
 corresponding AST (annotated with variable names and types) is:

 App
 (App
 (App
 (App
 (Var +::forall a. Num a = a - a - a)
 (Type a)
 )
 (App
 (Var $p1Fractional::forall a. Fractional a = Num a)
 (App
 (Var $p1Floating::forall a. Floating a = Fractional a)
 (Var $dFloating_aJq::Floating a)
 )
 )
 )
 (Var x1::'a')
 )
 (Var x1::'a')

 When I insert, GHC gives the following error:

 ghc: panic! (the 'impossible' happened)
   (GHC version 7.10.1 for x86_64-unknown-linux):
 expectJust cpeBody:collect_args

 What am I doing wrong with extracting these super-superclass
 dictionaries?  I've looked up the code for cpeBody in GHC, but I can't
 figure out what it's trying to do, so I'm not sure why it's failing on
 my core.

 On Mon, Aug 24, 2015 at 7:10 PM, Ömer Sinan Ağacan omeraga...@gmail.com 
 wrote:
 Mike, here's a piece of code that may be helpful to you:

 https://github.com/osa1/sc-plugin/blob/master/src/Supercompilation/Show.hs

 Copy this module to your plugin, it doesn't have any dependencies other than
 ghc itself. When your plugin is initialized, update `dynFlags_ref` with your
 DynFlags as first thing to do. Then use Show instance to print AST directly.

 Horrible hack, but very useful for learning purposes. In fact, I don't know 
 how
 else we can learn what Core is generated for a given code, and 
 reverse-engineer
 to figure out details.

 Hope it helps.

 2015-08-24 21:59 GMT-04:00 Ömer Sinan Ağacan omeraga...@gmail.com:
 Lets say I'm running the plugin on a function with signature `Floating a 
 = a
 - a`, then the plugin has access to the `Floating` dictionary for the 
 type.
 But if I want to add two numbers together, I need the `Num` dictionary.  I
 know I should have access to `Num` since it's a superclass of `Floating`.
 How can I get access to these superclass dictionaries?

 I don't have a working code for this but this should get you started:

 let ord_dictionary :: Id = ...
 ord_class  :: Class  = ...
  in
 mkApps (Var (head (classSCSels ord_class))) [Var ord_dictionary]

 I don't know how to get Class for Ord. I do `head` here because in the case 
 of
 Ord we only have one superclass so `classSCSels` should have one Id. Then I
 apply ord_dictionary to this selector and it should return dictionary for 
 Eq.

 I assumed you already have ord_dictionary, it should be passed to your 
 function
 already if you had `(Ord a) = ` in your function.


 Now I realized you asked for getting Num from Floating. I think you should
 follow a similar path except you need two applications, first to get 
 Fractional
 from Floating and second to get Num from Fractional:

 mkApps (Var (head (classSCSels fractional_class)))
[mkApps (Var (head (classSCSels floating_class)))
[Var floating_dictionary]]

 Return value should be a Num dictionary.
___
ghc-devs mailing list
ghc-devs@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs


Re: www.haskell.org/ghc

2015-08-25 Thread dongen
* Richard Eisenberg e...@cis.upenn.edu [2015-08-25 22:34:16 -0400]:

: I want to write a URL to represent GHC. It seems that
: www.haskell.org/ghc is the right one. But that page is quite ugly!
: A full redesign is always a challenge, so I'll make a simple request:
: remove announcements of old releases, for some definition of old.
: (I suggest: all releases from current major version + last release
: from previous major version.) Right now, I have to scroll down to
: get to What is GHC? and it's a little embarrassing.

Thanks Richard. You could also put in a _release history_ hyperlink
to a separate page.

Regards,


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


Re: question about GHC API on GHC plugin

2015-08-25 Thread Mike Izbicki
The purpose of the plugin is to automatically improve the numerical
stability of Haskell code.  It is supposed to identify numeric
expressions, then use Herbie (https://github.com/uwplse/herbie) to
generate a numerically stable version, then rewrite the numerically
stable version back into the code.  The first two steps were really
easy.  It's the last step of inserting back into the code that I'm
having tons of trouble with.  Core is a lot more complicated than I
thought :)

I'm not sure what you mean by the CoreExpr representation?  Here's the
output of the pretty printer you gave:
 App (App (App (App (Var Id{+,r2T,ForAllTy TyVar{a} (FunTy (TyConApp
Num [TyVarTy TyVar{a}]) (FunTy (TyVarTy TyVar{a}) (FunTy (TyVarTy
TyVar{a}) (TyVarTy TyVar{a},VanillaId,Info{0,SpecInfo []
UniqFM,NoUnfolding,MayHaveCafRefs,NoOneShotInfo,InlinePragma
{inl_src = {-# INLINE, inl_inline = EmptyInlineSpec, inl_sat =
Nothing, inl_act = AlwaysActive, inl_rule =
FunLike},NoOccInfo,StrictSig (DmdType UniqFM [] (Dunno NoCPR)),JD
{strd = Lazy, absd = Use Many Used},0}}) (Type (TyVarTy TyVar{a})))
(App (Var Id{$p1Fractional,rh3,ForAllTy TyVar{a} (FunTy (TyConApp
Fractional [TyVarTy TyVar{a}]) (TyConApp Num [TyVarTy
TyVar{a}])),ClassOpId Class,Info{1,SpecInfo [BuiltinRule {ru_name =
Class op $p1Fractional, ru_fn = $p1Fractional, ru_nargs = 2, ru_try
= RuleFun}] UniqFM,NoUnfolding,NoCafRefs,NoOneShotInfo,InlinePragma
{inl_src = {-# INLINE, inl_inline = EmptyInlineSpec, inl_sat =
Nothing, inl_act = AlwaysActive, inl_rule =
FunLike},NoOccInfo,StrictSig (DmdType UniqFM [JD {strd = Str (SProd
[Str HeadStr,Lazy,Lazy,Lazy]), absd = Use Many (UProd [Use Many
Used,Abs,Abs,Abs])}] (Dunno NoCPR)),JD {strd = Lazy, absd = Use Many
Used},0}}) (App (Var Id{$p1Floating,rh2,ForAllTy TyVar{a} (FunTy
(TyConApp Floating [TyVarTy TyVar{a}]) (TyConApp Fractional [TyVarTy
TyVar{a}])),ClassOpId Class,Info{1,SpecInfo [BuiltinRule {ru_name =
Class op $p1Floating, ru_fn = $p1Floating, ru_nargs = 2, ru_try =
RuleFun}] UniqFM,NoUnfolding,NoCafRefs,NoOneShotInfo,InlinePragma
{inl_src = {-# INLINE, inl_inline = EmptyInlineSpec, inl_sat =
Nothing, inl_act = AlwaysActive, inl_rule =
FunLike},NoOccInfo,StrictSig (DmdType UniqFM [JD {strd = Str (SProd
[Str 
HeadStr,Lazy,Lazy,Lazy,Lazy,Lazy,Lazy,Lazy,Lazy,Lazy,Lazy,Lazy,Lazy,Lazy,Lazy,Lazy,Lazy,Lazy,Lazy]),
absd = Use Many (UProd [Use Many
Used,Abs,Abs,Abs,Abs,Abs,Abs,Abs,Abs,Abs,Abs,Abs,Abs,Abs,Abs,Abs,Abs,Abs,Abs])}]
(Dunno NoCPR)),JD {strd = Lazy, absd = Use Many Used},0}}) (Var
Id{$dFloating,aBM,TyConApp Floating [TyVarTy
TyVar{a}],VanillaId,Info{0,SpecInfo []
UniqFM,NoUnfolding,MayHaveCafRefs,NoOneShotInfo,InlinePragma
{inl_src = {-# INLINE, inl_inline = EmptyInlineSpec, inl_sat =
Nothing, inl_act = AlwaysActive, inl_rule =
FunLike},NoOccInfo,StrictSig (DmdType UniqFM [] (Dunno NoCPR)),JD
{strd = Lazy, absd = Use Many Used},0}} (Var Id{x1,anU,TyVarTy
TyVar{a},VanillaId,Info{0,SpecInfo []
UniqFM,NoUnfolding,MayHaveCafRefs,NoOneShotInfo,InlinePragma
{inl_src = {-# INLINE, inl_inline = EmptyInlineSpec, inl_sat =
Nothing, inl_act = AlwaysActive, inl_rule =
FunLike},NoOccInfo,StrictSig (DmdType UniqFM [] (Dunno NoCPR)),JD
{strd = Lazy, absd = Use Many Used},0}})) (Var Id{x1,anU,TyVarTy
TyVar{a},VanillaId,Info{0,SpecInfo []
UniqFM,NoUnfolding,MayHaveCafRefs,NoOneShotInfo,InlinePragma
{inl_src = {-# INLINE, inl_inline = EmptyInlineSpec, inl_sat =
Nothing, inl_act = AlwaysActive, inl_rule =
FunLike},NoOccInfo,StrictSig (DmdType UniqFM [] (Dunno NoCPR)),JD
{strd = Lazy, absd = Use Many Used},0}})

You can find my pretty printer (and all the other code for the plugin)
at: https://github.com/mikeizbicki/herbie-haskell/blob/master/src/Herbie.hs#L627

The function getDictMap
(https://github.com/mikeizbicki/herbie-haskell/blob/master/src/Herbie.hs#L171)
is where I'm constructing the dictionaries that are getting inserted
back into the Core.

On Tue, Aug 25, 2015 at 7:17 PM, Ömer Sinan Ağacan omeraga...@gmail.com wrote:
 It seems like in your App syntax you're having a non-function in function
 position. You can see this by looking at what failing function
 (splitFunTy_maybe) is doing:

 splitFunTy_maybe :: Type - Maybe (Type, Type)
 -- ^ Attempts to extract the argument and result types from a type
 ... (definition is not important) ...

 Then it's used like this at the error site:

 (arg_ty, res_ty) = expectJust cpeBody:collect_args $
splitFunTy_maybe fun_ty

 In your case this function is returning Nothing and then exceptJust is
 signalling the panic.

 Your code looked correct to me, I don't see any problems with that. Maybe 
 you're
 using something wrong as selectors. Could you paste CoreExpr representation of
 your program?

 It may also be the case that the panic is caused by something else, maybe your
 syntax is invalidating some assumptions/invariants in GHC but it's not
 immediately checked etc. Working at the Core level is frustrating at times.

 Can I ask what kind of 

Re: OVERLAPPABLE/OVERLAPPING/OVERLAPS pragmas are confusing

2015-08-25 Thread Johan Tibell
The proposed change to my library is here:
https://github.com/tibbe/cassava/pull/95/files

We remove the OverlappingInstances pragma and instead add an OVERLAPPABLE
pragma like so:

instance {-# OVERLAPPABLE #-} FromField a = FromField (Maybe a) where

This causes clients of the library that previously compiled (e.g.
the music-parts package) to no longer compile, due to a now
lacking OVERLAPPING pragma in their code.

The issue here is I'm trying to the right thing (move to new pragmas), but
that causes clients to fail to compile. My question is: how do we avoid
that? Would it be OK if they added the OVERLAPPING pragma first and then I
change my library to use OVERLAPPABLE?

On Tue, Aug 25, 2015 at 1:25 PM, Simon Peyton Jones simo...@microsoft.com
wrote:

 What's the right way to migrate code? Just switching my library to the new
 pragmas breaks code, so that doesn't seem very attractive.



 I don’t understand.  Can you describe the problem more precisely, perhaps
 with an example?



 S





 *From:* ghc-devs [mailto:ghc-devs-boun...@haskell.org] *On Behalf Of *Johan
 Tibell
 *Sent:* 25 August 2015 10:42
 *To:* ghc-devs@haskell.org
 *Subject:* OVERLAPPABLE/OVERLAPPING/OVERLAPS pragmas are confusing



 It was brought to my attention that cassava, my library,
 uses OverlappingInstances, which is now deprecated. There's a suggested fix
 here: https://github.com/tibbe/cassava/pull/95.



 The fix seems correct but, as Mikhail points out, makes some client code
 no longer compile (due to a now missing OVERLAPPABLE pragma).



 What's the right way to migrate code? Just switching my library to the new
 pragmas breaks code, so that doesn't seem very attractive. Do clients have
 to migrate before the libraries they use?



 -- Johan





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


RE: OVERLAPPABLE/OVERLAPPING/OVERLAPS pragmas are confusing

2015-08-25 Thread Simon Peyton Jones
Would it be OK if they added the OVERLAPPING pragma first and then I change my 
library to use OVERLAPPABLE?

I think so, yes.  Does that not work? Is it bad?  Do you think the semantics is 
wrong?

Simon

From: Johan Tibell [mailto:johan.tib...@gmail.com]
Sent: 25 August 2015 13:19
To: Simon Peyton Jones
Cc: ghc-devs@haskell.org
Subject: Re: OVERLAPPABLE/OVERLAPPING/OVERLAPS pragmas are confusing

The proposed change to my library is here: 
https://github.com/tibbe/cassava/pull/95/files

We remove the OverlappingInstances pragma and instead add an OVERLAPPABLE 
pragma like so:

instance {-# OVERLAPPABLE #-} FromField a = FromField (Maybe a) where

This causes clients of the library that previously compiled (e.g. the 
music-parts package) to no longer compile, due to a now lacking OVERLAPPING 
pragma in their code.

The issue here is I'm trying to the right thing (move to new pragmas), but that 
causes clients to fail to compile. My question is: how do we avoid that? Would 
it be OK if they added the OVERLAPPING pragma first and then I change my 
library to use OVERLAPPABLE?

On Tue, Aug 25, 2015 at 1:25 PM, Simon Peyton Jones 
simo...@microsoft.commailto:simo...@microsoft.com wrote:
What's the right way to migrate code? Just switching my library to the new 
pragmas breaks code, so that doesn't seem very attractive.

I don’t understand.  Can you describe the problem more precisely, perhaps with 
an example?

S


From: ghc-devs 
[mailto:ghc-devs-boun...@haskell.orgmailto:ghc-devs-boun...@haskell.org] On 
Behalf Of Johan Tibell
Sent: 25 August 2015 10:42
To: ghc-devs@haskell.orgmailto:ghc-devs@haskell.org
Subject: OVERLAPPABLE/OVERLAPPING/OVERLAPS pragmas are confusing

It was brought to my attention that cassava, my library, uses 
OverlappingInstances, which is now deprecated. There's a suggested fix here: 
https://github.com/tibbe/cassava/pull/95.

The fix seems correct but, as Mikhail points out, makes some client code no 
longer compile (due to a now missing OVERLAPPABLE pragma).

What's the right way to migrate code? Just switching my library to the new 
pragmas breaks code, so that doesn't seem very attractive. Do clients have to 
migrate before the libraries they use?

-- Johan



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