Re: instances for closed type families

2016-05-25 Thread Alan & Kim Zimmerman
Ryan

The discussion was in this thread [1], but went off list at some point.

The relevant part of the off-list discussion, quoting Philip Hölzenspies  is

"UndecidableInstances comes from having to constrain the type that the
PostTcType-family projects to, besides the arguments of the AST-types;

instance (Data (PostTcType id), Data id) => Data (HsIPBinds id) where ...

If we could derive that from the definition of PostTcType (and I don't see
why we couldn't from a closed family; not sure about the open ones), we
would only need to constrain "id" and, thus, we could actually just use
"deriving".

Of the diff, btw, I don't get why PendingRnSplice is suddenly
parameterised... Thoughts?

Ph."

and SimonPJ responded

"

Why do we need UndecidableInstances?



I still (currently) think we can use open type families perfectly well.
Why won’t that work?  (Could switch to closed after GHC’s bootstrap caught
up.)



Simon

 "

So basically there is a mention that it may be possible.

Alan





[1] https://mail.haskell.org/pipermail/ghc-devs/2014-July/005808.html

On Wed, May 25, 2016 at 9:09 PM, Ryan Scott  wrote:

> > I recall there was some discussion when the PostRn/PostTc stuff went in
> around the closed type family solution being better, and I thought it was
> that the Data instances would be more easy to define.
>
> Do you happen to know where this discussion can be found online? To be
> honest, I'm not sure whether closed vs. open type families is even a
> relevant distinction in this case. Regardless of where NameOrRdrName
> is open or closed, the following code won't compile:
>
> data Foo a = Foo (NameOrRdrName a) deriving Data
>
> And that's simply because GHC hasn't enough information to know
> whether Foo a will always resolve to something that's a Data instance.
> Even if NameOrRdrName is closed, someone could still use types like
> NameOrRdrName Char.
>
> If NameOrRdrName were somehow made to be injective, then it'd be a
> different story. But I doubt that such a thing is possible in this
> case (based on the definition of NameOrRdrName you gave), so I think
> we'll just have to settle for turning on UndecidableInstances and
> writing code that we know won't throw the typechecker into a loop.
>
> Ryan S.
>
> On Wed, May 25, 2016 at 2:52 PM, Alan & Kim Zimmerman
>  wrote:
> > Ryan / Simon, thanks.
> >
> > I have been working it in the way the PostRn stuff was done, but then it
> > struck me there may be an easier way.
> >
> > I recall there was some discussion when the PostRn/PostTc stuff went in
> > around the closed type family solution being better, and I thought it was
> > that the Data instances would be more easy to define.
> >
> > And I also seem to recall that the closed type families should be able to
> > get rid of the UndecidableInstances pragma, but I do not recall the
> details.
> >
> > We are now able to use closed type families in GHC source, as it is
> > supported from GHC 7.8 onwards
> >
> > Regards
> >   Alan
> >
> >
> > On Wed, May 25, 2016 at 8:42 PM, Ryan Scott 
> wrote:
> >>
> >> Simon is right, you cannot use a type family as an instance head. But
> why
> >> do you need to? Typically, if you're deriving a Data instance that
> involves
> >> type families, the type families would be inside another data type. A
> >> real-world example is HsBindLR [1]:
> >>
> >> data HsBindLR idL idR
> >>   = FunBind {
> >>   ...
> >>   bind_fvs :: PostRn idL NameSet,
> >>   ...
> >> } | ...
> >>
> >> where PostRn is a type family [2]. Now, you can't simply derive Data for
> >> HsBindLR, because GHC has no way of knowing what PostRn will evaluate
> to!
> >> But you can use standalone deriving to get what you want:
> >>
> >> deriving instance (Data (PostRn idL NameSet), ...) => Data (HsBindLR
> >> idL idR)
> >>
> >> And in fact, this is what GHC does [3], using a convenient type synonyms
> >> for the long, sprawling context you need [4].
> >>
> >> So in your example, while you can't directly create a Data instance for
> >> NameOrRdrName itself, you can quite easily create Data instances for
> >> anything that might use NameOrRdrName. Does that work for your use
> cases?
> >>
> >> Ryan S.
> >> -
> >> [1]
> >>
> http://git.haskell.org/ghc.git/blob/bdc555885b8898684549eca70053c9ce0ec7fa39:/compiler/hsSyn/HsBinds.hs#l111
> >> [2]
> >>
> http://git.haskell.org/ghc.git/blob/bdc555885b8898684549eca70053c9ce0ec7fa39:/compiler/hsSyn/PlaceHolder.hs#l47
> >> [3]
> >>
> http://git.haskell.org/ghc.git/blob/bdc555885b8898684549eca70053c9ce0ec7fa39:/compiler/hsSyn/HsBinds.hs#l264
> >> [4]
> >>
> http://git.haskell.org/ghc.git/blob/bdc555885b8898684549eca70053c9ce0ec7fa39:/compiler/hsSyn/PlaceHolder.hs#l102
> >>
> >> ___
> >> ghc-devs mailing list
> >> ghc-devs@haskell.org
> >> http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs
> >>
> >
>
___
ghc-devs mailing list
ghc-

Re: instances for closed type families

2016-05-25 Thread Ryan Scott
> I recall there was some discussion when the PostRn/PostTc stuff went in 
> around the closed type family solution being better, and I thought it was 
> that the Data instances would be more easy to define.

Do you happen to know where this discussion can be found online? To be
honest, I'm not sure whether closed vs. open type families is even a
relevant distinction in this case. Regardless of where NameOrRdrName
is open or closed, the following code won't compile:

data Foo a = Foo (NameOrRdrName a) deriving Data

And that's simply because GHC hasn't enough information to know
whether Foo a will always resolve to something that's a Data instance.
Even if NameOrRdrName is closed, someone could still use types like
NameOrRdrName Char.

If NameOrRdrName were somehow made to be injective, then it'd be a
different story. But I doubt that such a thing is possible in this
case (based on the definition of NameOrRdrName you gave), so I think
we'll just have to settle for turning on UndecidableInstances and
writing code that we know won't throw the typechecker into a loop.

Ryan S.

On Wed, May 25, 2016 at 2:52 PM, Alan & Kim Zimmerman
 wrote:
> Ryan / Simon, thanks.
>
> I have been working it in the way the PostRn stuff was done, but then it
> struck me there may be an easier way.
>
> I recall there was some discussion when the PostRn/PostTc stuff went in
> around the closed type family solution being better, and I thought it was
> that the Data instances would be more easy to define.
>
> And I also seem to recall that the closed type families should be able to
> get rid of the UndecidableInstances pragma, but I do not recall the details.
>
> We are now able to use closed type families in GHC source, as it is
> supported from GHC 7.8 onwards
>
> Regards
>   Alan
>
>
> On Wed, May 25, 2016 at 8:42 PM, Ryan Scott  wrote:
>>
>> Simon is right, you cannot use a type family as an instance head. But why
>> do you need to? Typically, if you're deriving a Data instance that involves
>> type families, the type families would be inside another data type. A
>> real-world example is HsBindLR [1]:
>>
>> data HsBindLR idL idR
>>   = FunBind {
>>   ...
>>   bind_fvs :: PostRn idL NameSet,
>>   ...
>> } | ...
>>
>> where PostRn is a type family [2]. Now, you can't simply derive Data for
>> HsBindLR, because GHC has no way of knowing what PostRn will evaluate to!
>> But you can use standalone deriving to get what you want:
>>
>> deriving instance (Data (PostRn idL NameSet), ...) => Data (HsBindLR
>> idL idR)
>>
>> And in fact, this is what GHC does [3], using a convenient type synonyms
>> for the long, sprawling context you need [4].
>>
>> So in your example, while you can't directly create a Data instance for
>> NameOrRdrName itself, you can quite easily create Data instances for
>> anything that might use NameOrRdrName. Does that work for your use cases?
>>
>> Ryan S.
>> -
>> [1]
>> http://git.haskell.org/ghc.git/blob/bdc555885b8898684549eca70053c9ce0ec7fa39:/compiler/hsSyn/HsBinds.hs#l111
>> [2]
>> http://git.haskell.org/ghc.git/blob/bdc555885b8898684549eca70053c9ce0ec7fa39:/compiler/hsSyn/PlaceHolder.hs#l47
>> [3]
>> http://git.haskell.org/ghc.git/blob/bdc555885b8898684549eca70053c9ce0ec7fa39:/compiler/hsSyn/HsBinds.hs#l264
>> [4]
>> http://git.haskell.org/ghc.git/blob/bdc555885b8898684549eca70053c9ce0ec7fa39:/compiler/hsSyn/PlaceHolder.hs#l102
>>
>> ___
>> 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: instances for closed type families

2016-05-25 Thread Alan & Kim Zimmerman
Ryan / Simon, thanks.

I have been working it in the way the PostRn stuff was done, but then it
struck me there may be an easier way.

I recall there was some discussion when the PostRn/PostTc stuff went in
around the closed type family solution being better, and I thought it was
that the Data instances would be more easy to define.

And I also seem to recall that the closed type families should be able to
get rid of the UndecidableInstances pragma, but I do not recall the details.

We are now able to use closed type families in GHC source, as it is
supported from GHC 7.8 onwards

Regards
  Alan


On Wed, May 25, 2016 at 8:42 PM, Ryan Scott  wrote:

> Simon is right, you cannot use a type family as an instance head. But why
> do you need to? Typically, if you're deriving a Data instance that involves
> type families, the type families would be inside another data type. A
> real-world example is HsBindLR [1]:
>
> data HsBindLR idL idR
>   = FunBind {
>   ...
>   bind_fvs :: PostRn idL NameSet,
>   ...
> } | ...
>
> where PostRn is a type family [2]. Now, you can't simply derive Data for
> HsBindLR, because GHC has no way of knowing what PostRn will evaluate to!
> But you can use standalone deriving to get what you want:
>
> deriving instance (Data (PostRn idL NameSet), ...) => Data (HsBindLR
> idL idR)
>
> And in fact, this is what GHC does [3], using a convenient type synonyms
> for the long, sprawling context you need [4].
>
> So in your example, while you can't directly create a Data instance for
> NameOrRdrName itself, you can quite easily create Data instances for
> anything that might use NameOrRdrName. Does that work for your use cases?
>
> Ryan S.
> -
> [1]
> http://git.haskell.org/ghc.git/blob/bdc555885b8898684549eca70053c9ce0ec7fa39:/compiler/hsSyn/HsBinds.hs#l111
> [2]
> http://git.haskell.org/ghc.git/blob/bdc555885b8898684549eca70053c9ce0ec7fa39:/compiler/hsSyn/PlaceHolder.hs#l47
> [3]
> http://git.haskell.org/ghc.git/blob/bdc555885b8898684549eca70053c9ce0ec7fa39:/compiler/hsSyn/HsBinds.hs#l264
> [4]
> http://git.haskell.org/ghc.git/blob/bdc555885b8898684549eca70053c9ce0ec7fa39:/compiler/hsSyn/PlaceHolder.hs#l102
>
> ___
> 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: instances for closed type families

2016-05-25 Thread Ryan Scott
Simon is right, you cannot use a type family as an instance head. But why
do you need to? Typically, if you're deriving a Data instance that involves
type families, the type families would be inside another data type. A
real-world example is HsBindLR [1]:

data HsBindLR idL idR
  = FunBind {
  ...
  bind_fvs :: PostRn idL NameSet,
  ...
} | ...

where PostRn is a type family [2]. Now, you can't simply derive Data for
HsBindLR, because GHC has no way of knowing what PostRn will evaluate to!
But you can use standalone deriving to get what you want:

deriving instance (Data (PostRn idL NameSet), ...) => Data (HsBindLR
idL idR)

And in fact, this is what GHC does [3], using a convenient type synonyms
for the long, sprawling context you need [4].

So in your example, while you can't directly create a Data instance for
NameOrRdrName itself, you can quite easily create Data instances for
anything that might use NameOrRdrName. Does that work for your use cases?

Ryan S.
-
[1]
http://git.haskell.org/ghc.git/blob/bdc555885b8898684549eca70053c9ce0ec7fa39:/compiler/hsSyn/HsBinds.hs#l111
[2]
http://git.haskell.org/ghc.git/blob/bdc555885b8898684549eca70053c9ce0ec7fa39:/compiler/hsSyn/PlaceHolder.hs#l47
[3]
http://git.haskell.org/ghc.git/blob/bdc555885b8898684549eca70053c9ce0ec7fa39:/compiler/hsSyn/HsBinds.hs#l264
[4]
http://git.haskell.org/ghc.git/blob/bdc555885b8898684549eca70053c9ce0ec7fa39:/compiler/hsSyn/PlaceHolder.hs#l102
___
ghc-devs mailing list
ghc-devs@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs


Re: instances for closed type families

2016-05-25 Thread Alan & Kim Zimmerman
There is an example at http://lpaste.net/164532 (attached as well)

The derived Data instance fails with

/home/alanz/Example.hs:19:19:
Illegal type synonym family application in instance:
  NameOrRdrName id
In the stand-alone deriving instance for ‘Data (NameOrRdrName id)’

And how would an instance for Outputable be defined in terms of the
existing ones?

Alan


On Wed, May 25, 2016 at 8:03 PM, Simon Peyton Jones 
wrote:

> Can you give a small example? Certainly any instance like
>
> instance Data x => Data (F x)
>
> is not allowed, of course, if F is a type function. It’s like not allowing
>
>
>
> f (g x) = x
>
>
>
> in the term language.  Only constructors in patterns!
>
>
> S
>
>
>
> *From:* ghc-devs [mailto:ghc-devs-boun...@haskell.org] *On Behalf Of *Alan
> & Kim Zimmerman
> *Sent:* 25 May 2016 18:39
> *To:* ghc-devs@haskell.org
> *Subject:* instances for closed type families
>
>
>
> I am working on https://ghc.haskell.org/trac/ghc/ticket/12105, and have a
> type to ensure that the `HsMatchContext` has either a `RdrName` or a
> `Name`, not an `Id`.
>
> type family NameOrRdrName id where
>   NameOrRdrName Id  = Name
>   NameOrRdrName Name= Name
>   NameOrRdrName RdrName = RdrName
>
> Is there any way to declare `Data` and `OutputableBndr` instances for this?
>
> Without it I am having to do something like
>
> instance (OutputableBndr name, OutputableBndr (NameOrRdrName name))
>  => Outputable (HsDecl name) where
>
> which requires UndecidableInstances.
>
> I get
>
> compiler/hsSyn/PlaceHolder.hs:114:19:
> Illegal type synonym family application in instance:
>   NameOrRdrName id
> In the stand-alone deriving instance for ‘Data (NameOrRdrName id)’
>
> for the parameterised version and
>
> compiler/hsSyn/PlaceHolder.hs:115:19:
> Illegal type synonym family application in instance:
>   NameOrRdrName RdrName
> In the stand-alone deriving instance for
>   ‘Data (NameOrRdrName RdrName)’
>
> for the one specific to `RdrName`.
>
> Regards
>
>   Alan
>
{-# LANGUAGE DeriveDataTypeable #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE ConstraintKinds #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE StandaloneDeriving #-}

import Data.Data hiding ( Fixity )

data Name= Namederiving Data
data Id  = Id  deriving Data
data RdrName = RdrName deriving Data

class Outputable a where
  ppr :: a -> String

instance Outputable Name where
  ppr _ = "Name"

instance Outputable RdrName where
  ppr _ = "RdrName"

type family NameOrRdrName id where
  NameOrRdrName Id  = Name
  NameOrRdrName Name= Name
  NameOrRdrName RdrName = RdrName


deriving instance Data (NameOrRdrName id)

instance Outputable (NameOrRdrName id) where
  ppr = undefined -- what should this be?

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


RE: instances for closed type families

2016-05-25 Thread Simon Peyton Jones
Can you give a small example? Certainly any instance like
instance Data x => Data (F x)
is not allowed, of course, if F is a type function. It’s like not allowing

f (g x) = x

in the term language.  Only constructors in patterns!

S

From: ghc-devs [mailto:ghc-devs-boun...@haskell.org] On Behalf Of Alan & Kim 
Zimmerman
Sent: 25 May 2016 18:39
To: ghc-devs@haskell.org
Subject: instances for closed type families

I am working on https://ghc.haskell.org/trac/ghc/ticket/12105, and have a type 
to ensure that the `HsMatchContext` has either a `RdrName` or a `Name`, not an 
`Id`.

type family NameOrRdrName id where
  NameOrRdrName Id  = Name
  NameOrRdrName Name= Name
  NameOrRdrName RdrName = RdrName
Is there any way to declare `Data` and `OutputableBndr` instances for this?
Without it I am having to do something like

instance (OutputableBndr name, OutputableBndr (NameOrRdrName name))
 => Outputable (HsDecl name) where
which requires UndecidableInstances.
I get

compiler/hsSyn/PlaceHolder.hs:114:19:
Illegal type synonym family application in instance:
  NameOrRdrName id
In the stand-alone deriving instance for ‘Data (NameOrRdrName id)’
for the parameterised version and

compiler/hsSyn/PlaceHolder.hs:115:19:
Illegal type synonym family application in instance:
  NameOrRdrName RdrName
In the stand-alone deriving instance for
  ‘Data (NameOrRdrName RdrName)’
for the one specific to `RdrName`.
Regards
  Alan
___
ghc-devs mailing list
ghc-devs@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs


instances for closed type families

2016-05-25 Thread Alan & Kim Zimmerman
I am working on https://ghc.haskell.org/trac/ghc/ticket/12105, and have a
type to ensure that the `HsMatchContext` has either a `RdrName` or a
`Name`, not an `Id`.

type family NameOrRdrName id where
  NameOrRdrName Id  = Name
  NameOrRdrName Name= Name
  NameOrRdrName RdrName = RdrName

Is there any way to declare `Data` and `OutputableBndr` instances for this?

Without it I am having to do something like

instance (OutputableBndr name, OutputableBndr (NameOrRdrName name))
 => Outputable (HsDecl name) where

which requires UndecidableInstances.

I get

compiler/hsSyn/PlaceHolder.hs:114:19:
Illegal type synonym family application in instance:
  NameOrRdrName id
In the stand-alone deriving instance for ‘Data (NameOrRdrName id)’

for the parameterised version and

compiler/hsSyn/PlaceHolder.hs:115:19:
Illegal type synonym family application in instance:
  NameOrRdrName RdrName
In the stand-alone deriving instance for
  ‘Data (NameOrRdrName RdrName)’

for the one specific to `RdrName`.

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