Re: Illegal type synonym family application in instance (Was: Breakage with 6.10)

2008-10-14 Thread Manuel M T Chakravarty

Niklas Broberg:

On 10/11/08, David Menendez <[EMAIL PROTECTED]> wrote:

On Fri, Oct 10, 2008 at 8:40 PM, Niklas Broberg
<[EMAIL PROTECTED]> wrote:

src\HSX\XMLGenerator.hs:71:0
  Illegal type synonym family application in instance: XML m
  In the instance declaration for `EmbedAsChild m (XML m)´
---

Could someone help me point out the problem here? The relevant  
code is:


instance XMLGen m => EmbedAsChild m (XML m) where
asChild = return . return . xmlToChild

class XMLGen m => EmbedAsChild m c where
asChild :: c -> GenChildList m

class Monad m => XMLGen m where
type XML m


This works fine with 6.8.3, so what's new in 6.10, and what would  
I do

to solve it?



I'm guessing there was a bug in 6.8.3 that allowed this. (The
implementation of type families is present but not supported in 6.8,
presumably because of problems like this.)

I don't have 6.10, so I can't test anything, but you might try
rewriting the EmbedAsChild instances like so:

   instance (XMLGen m, XML m ~ x) => EmbedAsChild m x where ...


Thanks a lot David, that's indeed what I needed.

I'm not sure I see why the style I used previously was illegal though,
it seemed perfectly natural to me. And it works that way for
`EmbedAsChild m (Child m)´, where `Child m´ is a data type family and
not a synonym, so why not for a synonym too? But hey, as long as
there's a way to do what I want. :-)


As suggested, it was a bug in 6.8.3 that you could make a class  
instance where the head involved a type synonym family.  We cannot  
allow synonym families in class instances heads as it is impossible to  
check for overlap of such instances; eg, consider


  type family F a
  type instance F Bool = Int

  class C a

  instance C Int
  instance C (F a)

Now a context (C (F Bool)) would match both instances.  This is  
especially bad, as the type instance for F Bool may be defined in a  
different module as the instances for C; so, it is even in principle  
impossible to check for such overlap.


The situation is different for data families as they are data types  
and not type synonyms.


Moreover,

  instance (XMLGen m, XML m ~ x) => EmbedAsChild m x where ...

is fine as it clearly overlaps with any other instance of EmbedAsChild.

I hope that clarifies the situation.

Manuel

___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: gadt changes in ghc 6.10

2008-10-14 Thread Jason Dagit
On Tue, Oct 14, 2008 at 6:37 PM, Daniel Gorín <[EMAIL PROTECTED]> wrote:

>
> On Oct 14, 2008, at 10:19 PM, Jason Dagit wrote:
>
>
> On Tue, Oct 14, 2008 at 7:27 AM, Daniel Gorín <[EMAIL PROTECTED]> wrote:
>
>> Hi
>>
>> After installing ghc 6.10-rc, I have a program that no longer compiles. I
>> get the dreaded "GADT pattern match" error, instead :)
>>
>> Here is a boiled-down example:
>
> [...]
>
>
> I don't have 6.10 handy to try out your program, but in 6.8 and older the
> type error message you're getting means that the compiler needs more
> "outside in" help with type checking this.
>
> Usually this means adding type more type signatures on the outside.  For
> example, maybe you need to give the type signatures inside the case to make
> the types inside the pattern matches of the case more rigid.  That probably
> didn't make a lot of sense :(  So here is an example,
>
> case wit :: {- Try adding a signature here -} of ...
>
> Given that your code has such deep pattern nesting I would argue that it is
> in your best interest to add local functions (in a where clause) along with
> their explicit type signatures.  Start with the inner most case expressions
> and convert those to local functions and work your way out.
>
> I've tried adding some signatures (together with -XScopedTypeVariables),
>> but with no luck. Why is it that this no longer compiles? More importantly,
>> how can I make it compile again? :)
>
>
> I think adding local functions is easier than randomly sprinkling in the
> type signatures.  It has a nice side-effect that your new code is often
> easier to read as well.
>
> Good luck!
> Jason
>
>
> Thanks for the advice!
>
> By using some auxiliary functions I can now compile an alternative version
> of the program. And although the resulting program is more clear, I'd still
> like to know if this can be achieved be adding only annotations to the
> original program. The reason for this is that, for performance reasons,  I
> depend on the case-of-case transformation removing every possible case
> construct. I already verified this is happening for the original program and
> I rather keep the code as is than browse through the generated core again :)
>

It's unfortunate that you have such a situation with the optimizer.  How
often do you check that the optimizer is still smart enough?  It seems like
the sort of thing that could easily break between compiler releases.  If you
are going to depend on, I wonder if you could write a test to ensure that it
is happening every time.


>
> I must say that I also found this thread to be very helpful:
>
> http://thread.gmane.org/gmane.comp.lang.haskell.glasgow.user/15153
>

That is a good thread and it helped me a lot in the past too.  One of the
most important bits is when Simon says this:

GHC now enforces the rule that in a GADT pattern match
- the type of the scrutinee must be rigid
- the result type must be rigid
- the type of any variable free in the case branch must be rigid

I would hypothesize that most people who encounter the message you're
getting fall into the last case, but I may be biased by my own experiences.


> 
>
> I'll make sure the wiki points to it.
>

Oh, good idea!  Thanks!


>
> For the record the resulting code is this:
>
> {-# LANGUAGE GADTs, EmptyDataDecls #-}
> module T where
>
> data S
> data M
>
> data Wit t where
> S :: Wit S
> M :: Wit M
>
> data Impl t a where
> I1 :: Maybe a -> Impl S a
> I2 :: [a] -> Impl M a
>
> type W_ t a = Wit t -> Impl t a
>
> newtype W t a = Wrap (W_ t a)
>
> unWrap1 :: Impl S a -> Maybe a
> unWrap1 (I1 m) = m
>
> unWrap2 :: Impl M a -> [a]
> unWrap2 (I2 m) = m
>
> bind :: W t a -> (a -> W t b) -> W_ t b
> bind (Wrap w) f = \wit ->
> case wit of
>   S -> I1 $ do a <- unWrap1 (w S)
>case (f a) of
>   Wrap w' -> unWrap1 (w' S)
>   M -> I2 $ do a <- unWrap2 (w M)
>case (f a) of
>   Wrap w' -> unWrap2 (w' M)
>
>
My (untested) hunch is that, Wrap w', needs a type signature in your
original version.  I think this because of the 3rd case I mentioned above.
It would seem that your unWrap1 and unWrap2 fix the witness type, either S
or M.  Without playing with it (and again I don't have 6.10 handy), I'm not
sure which side of the arrow needs the type signature.  It could be that you
need something like:
Wrap (w' :: A type signature fixing M or S)

Or, you need it on the other side:
Wrap w' -> (w' :: some type sig) M

Either way, I think think the type t needs to be mentioned somewhere.

Good luck and let me know what you figure out, I'm quite curious now.
Jason
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: gadt changes in ghc 6.10

2008-10-14 Thread Daniel Gorín


On Oct 14, 2008, at 10:19 PM, Jason Dagit wrote:


On Tue, Oct 14, 2008 at 7:27 AM, Daniel Gorín <[EMAIL PROTECTED]>  
wrote:

Hi

After installing ghc 6.10-rc, I have a program that no longer  
compiles. I get the dreaded "GADT pattern match" error, instead :)


Here is a boiled-down example:
[...]

I don't have 6.10 handy to try out your program, but in 6.8 and  
older the type error message you're getting means that the compiler  
needs more "outside in" help with type checking this.


Usually this means adding type more type signatures on the outside.   
For example, maybe you need to give the type signatures inside the  
case to make the types inside the pattern matches of the case more  
rigid.  That probably didn't make a lot of sense :(  So here is an  
example,


case wit :: {- Try adding a signature here -} of ...

Given that your code has such deep pattern nesting I would argue  
that it is in your best interest to add local functions (in a where  
clause) along with their explicit type signatures.  Start with the  
inner most case expressions and convert those to local functions and  
work your way out.


I've tried adding some signatures (together with - 
XScopedTypeVariables), but with no luck. Why is it that this no  
longer compiles? More importantly, how can I make it compile again? :)


I think adding local functions is easier than randomly sprinkling in  
the type signatures.  It has a nice side-effect that your new code  
is often easier to read as well.


Good luck!
Jason


Thanks for the advice!

By using some auxiliary functions I can now compile an alternative  
version of the program. And although the resulting program is more  
clear, I'd still like to know if this can be achieved be adding only  
annotations to the original program. The reason for this is that, for  
performance reasons,  I depend on the case-of-case transformation  
removing every possible case construct. I already verified this is  
happening for the original program and I rather keep the code as is  
than browse through the generated core again :)


I must say that I also found this thread to be very helpful:

http://thread.gmane.org/gmane.comp.lang.haskell.glasgow.user/15153

I'll make sure the wiki points to it.

For the record the resulting code is this:

{-# LANGUAGE GADTs, EmptyDataDecls #-}
module T where

data S
data M

data Wit t where
S :: Wit S
M :: Wit M

data Impl t a where
I1 :: Maybe a -> Impl S a
I2 :: [a] -> Impl M a

type W_ t a = Wit t -> Impl t a

newtype W t a = Wrap (W_ t a)

unWrap1 :: Impl S a -> Maybe a
unWrap1 (I1 m) = m

unWrap2 :: Impl M a -> [a]
unWrap2 (I2 m) = m

bind :: W t a -> (a -> W t b) -> W_ t b
bind (Wrap w) f = \wit ->
case wit of
  S -> I1 $ do a <- unWrap1 (w S)
   case (f a) of
  Wrap w' -> unWrap1 (w' S)
  M -> I2 $ do a <- unWrap2 (w M)
   case (f a) of
  Wrap w' -> unWrap2 (w' M)


Bye
Daniel


___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: gadt changes in ghc 6.10

2008-10-14 Thread Jason Dagit
On Tue, Oct 14, 2008 at 7:27 AM, Daniel Gorín <[EMAIL PROTECTED]> wrote:

> Hi
>
> After installing ghc 6.10-rc, I have a program that no longer compiles. I
> get the dreaded "GADT pattern match" error, instead :)
>
> Here is a boiled-down example:
>
> {-# OPTIONS_GHC -XGADTs -XEmptyDataDecls #-}
> module T where
>
> data S
> data M
>
> data Wit t where
>S :: Wit S
>M :: Wit M
>
> data Impl t a where
>I1 :: Maybe a -> Impl S a
>I2 :: [a] -> Impl M a
>
> type W_ t a = Wit t -> Impl t a
>
> newtype W t a = Wrap (W_ t a)
>
> bind :: W t a -> (a -> W t b) -> W_ t b
> bind (Wrap w) f = \wit ->
>case wit of
>  S -> case w S of
>  I1 m -> I1 $ do a <- m
>  case f a of
>Wrap w' -> case w' S of
>  I1 m' -> m'
>  M-> case w M of
>  I2 m -> I2 $ do a <- m
>  case f a of
>Wrap w' -> case w' M of
>  I2 m' -> m'
>
> While in ghc 6.8.3 this compiles fine, with ghc 6.10 i get:
>
> $ ghc --make T.hs
> [1 of 1] Compiling T( T.hs, T.o )
>
> T.hs:26:57:
>GADT pattern match with non-rigid result type `Maybe a'
>  Solution: add a type signature
>In a case alternative: I1 m' -> m'
>In the expression: case w' S of { I1 m' -> m' }
>In a case alternative: Wrap w' -> case w' S of { I1 m' -> m' }


I don't have 6.10 handy to try out your program, but in 6.8 and older the
type error message you're getting means that the compiler needs more
"outside in" help with type checking this.

Usually this means adding type more type signatures on the outside.  For
example, maybe you need to give the type signatures inside the case to make
the types inside the pattern matches of the case more rigid.  That probably
didn't make a lot of sense :(  So here is an example,

case wit :: {- Try adding a signature here -} of ...

Given that your code has such deep pattern nesting I would argue that it is
in your best interest to add local functions (in a where clause) along with
their explicit type signatures.  Start with the inner most case expressions
and convert those to local functions and work your way out.

I've tried adding some signatures (together with -XScopedTypeVariables), but
> with no luck. Why is it that this no longer compiles? More importantly, how
> can I make it compile again? :)


I think adding local functions is easier than randomly sprinkling in the
type signatures.  It has a nice side-effect that your new code is often
easier to read as well.

Good luck!
Jason
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: gadt changes in ghc 6.10

2008-10-14 Thread Daniel Gorín

On Oct 14, 2008, at 7:48 PM, Don Stewart wrote:


dgorin:

I've tried adding some signatures (together with -
XScopedTypeVariables), but with no luck. Why is it that this no  
longer

compiles? More importantly, how can I make it compile again? :)



If you work out how to make it compile, can you document the soln.  
here,


   http://haskell.org/haskellwiki/Upgrading_packages#Changes_to_GADT_matching

Cheers,
   Don


Sure, but I must say I'm still kind of lost, here
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: gadt changes in ghc 6.10

2008-10-14 Thread Don Stewart
dgorin:
> I've tried adding some signatures (together with - 
> XScopedTypeVariables), but with no luck. Why is it that this no longer  
> compiles? More importantly, how can I make it compile again? :)
> 

If you work out how to make it compile, can you document the soln. here,

http://haskell.org/haskellwiki/Upgrading_packages#Changes_to_GADT_matching

Cheers,
Don
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


gadt changes in ghc 6.10

2008-10-14 Thread Daniel Gorín

Hi

After installing ghc 6.10-rc, I have a program that no longer  
compiles. I get the dreaded "GADT pattern match" error, instead :)


Here is a boiled-down example:

{-# OPTIONS_GHC -XGADTs -XEmptyDataDecls #-}
module T where

data S
data M

data Wit t where
S :: Wit S
M :: Wit M

data Impl t a where
I1 :: Maybe a -> Impl S a
I2 :: [a] -> Impl M a

type W_ t a = Wit t -> Impl t a

newtype W t a = Wrap (W_ t a)

bind :: W t a -> (a -> W t b) -> W_ t b
bind (Wrap w) f = \wit ->
case wit of
  S -> case w S of
  I1 m -> I1 $ do a <- m
  case f a of
Wrap w' -> case w' S of
  I1 m' -> m'
  M-> case w M of
  I2 m -> I2 $ do a <- m
  case f a of
Wrap w' -> case w' M of
  I2 m' -> m'

While in ghc 6.8.3 this compiles fine, with ghc 6.10 i get:

$ ghc --make T.hs
[1 of 1] Compiling T( T.hs, T.o )

T.hs:26:57:
GADT pattern match with non-rigid result type `Maybe a'
  Solution: add a type signature
In a case alternative: I1 m' -> m'
In the expression: case w' S of { I1 m' -> m' }
In a case alternative: Wrap w' -> case w' S of { I1 m' -> m' }

I've tried adding some signatures (together with - 
XScopedTypeVariables), but with no luck. Why is it that this no longer  
compiles? More importantly, how can I make it compile again? :)


Thanks!

Daniel
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: Re[2]: [Haskell-cafe] I do not want to be a bitch, but ghc-6.8.3 and haskell binary policy are really horrible.

2008-10-14 Thread Thomas Schilling
2008/10/14 Bulat Ziganshin <[EMAIL PROTECTED]>:
> Hello Thomas,
>
> Tuesday, October 14, 2008, 2:46:45 PM, you wrote:
>
>> The issue is binary compatibility.  At the moment, GHC cannot make
>> sure that a library compiled with an older GHC can work with a newer
>> GHC.  GHC does many cross-module optimisations, and its runtime system
>> changes occasionally, so it is very pessimistic in that regard.  This
>> becomes an issue for packages that GHC has been build with itself
>> (like base, process, array), since these cannot be upgraded without
>> recompiling GHC (hence requiring recompiling every other package).
>
> is this correct? i was under impression that upgrading packages never
> require to recompile GHC itself. it just happen that we have only one
> version of base or array shipped with each GHC and at least with array
> this can be changed easily (and for base too - just noone plans to do
> it)

Well, I was a bit imprecise.  You can install a new array, but if you
have a transitive dependency on the old array, this won't help.  I'm
not sure, but AFAIK the only thing that can introduce such a
transitive dependency is the GHC API.  So if you want to use the GHC
API and a newer version of array in your program then you need to
recompile ghc against the new array package.

If you don't use the GHC API but want to use another package that has
been compiled against array, you need to upgrade that other package,
too.  Modern versions of cabal-install should be able to do this where
possible, but older ones (< 0.5, I think, Duncan knows) had problems
with this.

P.S.: I guess the moral of the story is that while cabal upgrade (no
args) seems like a reasonable thing to do it is not yet very
realiable.  Many of these issues only became urgent because we now
have such a powerful tool like cabal-install and we now have to add
features to GHC, Cabal, and cabal-install to solve them.  So, despite
these unfortunate (and understandably frustrating) issues, we've come
a long way since only 2 years ago, where every package had to be
downloaded and installed manually using runghc Setup.

P.P.S: Again, to the OP, please help us find out what exactly went
wrong, so we can try to make sure that it won't happen again to you or
anyone else.
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re[2]: [Haskell-cafe] I do not want to be a bitch, but ghc-6.8.3 and haskell binary policy are really horrible.

2008-10-14 Thread Bulat Ziganshin
Hello Thomas,

Tuesday, October 14, 2008, 2:46:45 PM, you wrote:

> The issue is binary compatibility.  At the moment, GHC cannot make
> sure that a library compiled with an older GHC can work with a newer
> GHC.  GHC does many cross-module optimisations, and its runtime system
> changes occasionally, so it is very pessimistic in that regard.  This
> becomes an issue for packages that GHC has been build with itself
> (like base, process, array), since these cannot be upgraded without
> recompiling GHC (hence requiring recompiling every other package).

is this correct? i was under impression that upgrading packages never
require to recompile GHC itself. it just happen that we have only one
version of base or array shipped with each GHC and at least with array
this can be changed easily (and for base too - just noone plans to do
it)


-- 
Best regards,
 Bulatmailto:[EMAIL PROTECTED]

___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: ANNOUNCE: GHC 6.10.1 RC 1

2008-10-14 Thread Jules Bean

Simon Marlow wrote:

Judah Jacobson wrote:


Once small thing I've noticed: UserInterrupt (ctr-c) exceptions are
not thrown in ghci, probably because it installs its own signal
handlers:

Prelude Control.Exception Control.Concurrent> handle (\UserInterrupt
-> putStrLn "Caught!") (threadDelay 200)
^CInterrupted.

For consistency between the compiled and interpreted environments, it
would be nice if the above could catch the ctrl-c.  But maybe there's
a reason not to do this?  If this change sounds OK, I can take a look
at this and try to put together a patch over the weekend.


Hmm, tricky one.  I agree with the argument for consistency, but on the 
other hand you might also want a way to interrupt a computation 
regardless, and that almost works - as long as the program isn't 
discarding exceptions it knows nothing about.


In my mind this is, at least thematically, related to

http://hackage.haskell.org/trac/ghc/ticket/1399

that is, it relates to the various ways that running in ghci is 
different from running independently.


To get a really good answer I think we need a couple of RTS 
enhancements, the ability to have a kind 'supervisor' mode etc...


Jules
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users