Re: [Haskell-cafe] Multi-parameter type class woes

2008-12-15 Thread Thomas DuBuisson
2008/12/15 Mario Blazevic mblaze...@stilo.com

 Alexander Dunlap wrote:

 The problem is that y is not mentioned in the signature of wrapper.
 When you call wrapper x, there could be many different instances of
 Container x y with the same x, so GHC doesn't know which version to
 call.



I guess I see it now. However, if the explicit 'Container x y ='
 context couldn't fix the y to use for instantiation of Container x y, I
 don't see any way to fix it. And if there is no way to call wrapper in any
 context, the class declaration itself is illegal and GHC should have
 reported the error much sooner. Should I create a ticket?



Please do not create a ticket.  Such a typeclass is legitimate, but not
useful alone or with functional dependencies.  It is useful with Type
Families though, so celebrate!

Thomas

- START CODE 
{-# LANGUAGE TypeFamilies, MultiParamTypeClasses, FlexibleInstances #-}

import Data.Maybe

class Container x where
 type Contains x
 wrapper :: x - Bool
 unwrap :: x - Contains x
 rewrap :: Contains x - x

liftWrap :: Container x = (Contains x - Contains x) - x - x
liftWrap f x = (if wrapper x then rewrap . f . unwrap else id) x

instance Container (Maybe x) where
 type Contains (Maybe x) = x
 wrapper = isJust
 unwrap = fromJust
 rewrap = Just

main = print (liftWrap (succ :: Int - Int) (Just 1 :: Maybe Int))
-
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Multi-parameter type class woes

2008-12-15 Thread Thomas DuBuisson
On Mon, Dec 15, 2008 at 2:15 PM, Thomas DuBuisson 
thomas.dubuis...@gmail.com wrote:

 2008/12/15 Mario Blazevic mblaze...@stilo.com

 Alexander Dunlap wrote:

 The problem is that y is not mentioned in the signature of wrapper.
 When you call wrapper x, there could be many different instances of
 Container x y with the same x, so GHC doesn't know which version to
 call.



I guess I see it now. However, if the explicit 'Container x y ='
 context couldn't fix the y to use for instantiation of Container x y, I
 don't see any way to fix it. And if there is no way to call wrapper in any
 context, the class declaration itself is illegal and GHC should have
 reported the error much sooner. Should I create a ticket?



 Please do not create a ticket.  Such a typeclass is legitimate, but not
 useful alone or with functional dependencies.  It is useful with Type
 Families though, so celebrate!

 Thomas


Ok, now I get to laugh at myself.  Caught up in the type family fun, I
didn't even notice I obliterated the MPTC issue that started the whole
discussion.  Slowing down to think, I can't find an example where the
original MPTC is any good and it should thus receive a compile time error.
Perhaps someone will come along and give a legitimate example.

Thomas
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Multi-parameter type class woes

2008-12-15 Thread Mario Blazevic

Alexander Dunlap wrote:

On Sun, Dec 14, 2008 at 8:10 PM, Mario Blažević mblaze...@stilo.com wrote:

I'll take a swing at this one:

instance Container (Maybe x) [x] where
wrapper = isNothing
. . .

That isn't a sensible definition of 'wrapper', but I believe without
trying to compile it is completely legal.  Which wrapper do you use?

You /don't/ have a different matching Container instance, but without the
functional dependency you /might/, and ghc barfs.


   But liftWrap doesn't require any particular instance, it's a
generic function accepting any pair of types for which there is
an instance of Container. Instance selection (as I understand it)
shouldn't come into play until one applies liftWrap to a
particular type, and indeed it does cause problems there: note
the type annotations on the last line. That part I understand
and accept, or at least have learned to live with.


The problem is that y is not mentioned in the signature of wrapper.
When you call wrapper x, there could be many different instances of
Container x y with the same x, so GHC doesn't know which version to
call.



	I guess I see it now. However, if the explicit 'Container x y =' 
context couldn't fix the y to use for instantiation of Container x y, I 
don't see any way to fix it. And if there is no way to call wrapper in 
any context, the class declaration itself is illegal and GHC should have 
reported the error much sooner. Should I create a ticket?





You can fix this problem either by adding a functional
dependency or by splitting wrapper out into its own class (Wrapper x,
e.g.) so all of the type variables in the class head are mentioned in
its type and the instance can be determined by the call.

Thanks for asking this question, by the way. I had known about this
issue but had never really realized why it happened. Now that I have
thought about it, I understand it too. :)

Hope that helps,
Alex



___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Multi-parameter type class woes

2008-12-15 Thread Alexander Dunlap
2008/12/15 Mario Blazevic mblaze...@stilo.com:
 Alexander Dunlap wrote:

 On Sun, Dec 14, 2008 at 8:10 PM, Mario Blažević mblaze...@stilo.com
 wrote:

 I'll take a swing at this one:

 instance Container (Maybe x) [x] where
 wrapper = isNothing
 . . .

 That isn't a sensible definition of 'wrapper', but I believe without
 trying to compile it is completely legal.  Which wrapper do you use?

 You /don't/ have a different matching Container instance, but without
 the
 functional dependency you /might/, and ghc barfs.

   But liftWrap doesn't require any particular instance, it's a
 generic function accepting any pair of types for which there is
 an instance of Container. Instance selection (as I understand it)
 shouldn't come into play until one applies liftWrap to a
 particular type, and indeed it does cause problems there: note
 the type annotations on the last line. That part I understand
 and accept, or at least have learned to live with.

 The problem is that y is not mentioned in the signature of wrapper.
 When you call wrapper x, there could be many different instances of
 Container x y with the same x, so GHC doesn't know which version to
 call.


I guess I see it now. However, if the explicit 'Container x y ='
 context couldn't fix the y to use for instantiation of Container x y, I
 don't see any way to fix it. And if there is no way to call wrapper in any
 context, the class declaration itself is illegal and GHC should have
 reported the error much sooner. Should I create a ticket?



 You can fix this problem either by adding a functional
 dependency or by splitting wrapper out into its own class (Wrapper x,
 e.g.) so all of the type variables in the class head are mentioned in
 its type and the instance can be determined by the call.

 Thanks for asking this question, by the way. I had known about this
 issue but had never really realized why it happened. Now that I have
 thought about it, I understand it too. :)

 Hope that helps,
 Alex




I think that 
http://www.haskell.org/pipermail/haskell-cafe/2008-April/041461.html
may be relevant. It's a design decision.

Alex
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Multi-parameter type class woes

2008-12-15 Thread Mario Blažević

 I think that 
 http://www.haskell.org/pipermail/haskell-cafe/2008-April/041461.html
 may be relevant. It's a design decision.

Thanks for the link. I've read through the thread, but rather than try to 
figure out if it's the same issue and whether it's a design decision or a 
historical accident, I've decided to create a ticket (#2885) and let GHC 
developers decide if it's valid or not.


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Multi-parameter type class woes

2008-12-14 Thread Mario Blažević
I have, for a change, a relatively simple problem with type classes. Can 
somebody explain to me, or point me to an explanation of the behaviour I see?

Here is a short and useless example:

  {-# LANGUAGE MultiParamTypeClasses, FlexibleInstances #-}

   import Data.Maybe

   class Container x y where
  wrapper :: x - Bool
  unwrap :: x - y
  rewrap :: y - x

   liftWrap :: Container x y = (y - y) - (x - x)
   liftWrap f x = (if wrapper x then rewrap . f . unwrap else id) x

   instance Container (Maybe x) x where
  wrapper = isJust
  unwrap = fromJust
  rewrap = Just

   main = print (liftWrap (succ :: Int - Int) (Just 1 :: Maybe Int))

GHC 6.10.1 refuses to typecheck the 'wrapper' function in definition of 
'liftWrap', with the following error message:

Could not deduce (Container x y) from the context (Container x y1)
  arising from a use of `wrapper' at Test.hs:11:22-30
Possible fix:
  add (Container x y) to the context of
the type signature for `liftWrap'
In the expression: wrapper x
In the expression:
(if wrapper x then rewrap . f . unwrap else id) x
In the definition of `liftWrap':
liftWrap f x = (if wrapper x then rewrap . f . unwrap else id) x

Let me clarify that I'm aware that in this particular example a functional 
dependecy should be used. Also, I can think of a few workarounds for my actual 
problem, so I'm not asking for any solutions. I'm looking for an explanation. 
It bugs me that my intuition of how this type class should have worked is 
completely wrong. The error message does not help, to put it mildly. Where 
should I go, what should I read?



___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Multi-parameter type class woes

2008-12-14 Thread Christopher Lane Hinson


I'll take a swing at this one:

instance Container (Maybe x) [x] where
wrapper = isNothing
. . .

That isn't a sensible definition of 'wrapper', but I believe without 
trying to compile it is completely legal.  Which wrapper do you use?


You /don't/ have a different matching Container instance, but without the 
functional dependency you /might/, and ghc barfs.


--L

On Sun, 14 Dec 2008, Mario Bla?evi? wrote:


I have, for a change, a relatively simple problem with type classes. Can 
somebody explain to me, or point me to an explanation of the behaviour I see?

Here is a short and useless example:

 {-# LANGUAGE MultiParamTypeClasses, FlexibleInstances #-}

  import Data.Maybe

  class Container x y where
 wrapper :: x - Bool
 unwrap :: x - y
 rewrap :: y - x

  liftWrap :: Container x y = (y - y) - (x - x)
  liftWrap f x = (if wrapper x then rewrap . f . unwrap else id) x

  instance Container (Maybe x) x where
 wrapper = isJust
 unwrap = fromJust
 rewrap = Just

  main = print (liftWrap (succ :: Int - Int) (Just 1 :: Maybe Int))

GHC 6.10.1 refuses to typecheck the 'wrapper' function in definition of 
'liftWrap', with the following error message:

   Could not deduce (Container x y) from the context (Container x y1)
 arising from a use of `wrapper' at Test.hs:11:22-30
   Possible fix:
 add (Container x y) to the context of
   the type signature for `liftWrap'
   In the expression: wrapper x
   In the expression:
   (if wrapper x then rewrap . f . unwrap else id) x
   In the definition of `liftWrap':
   liftWrap f x = (if wrapper x then rewrap . f . unwrap else id) x

Let me clarify that I'm aware that in this particular example a functional 
dependecy should be used. Also, I can think of a few workarounds for my actual 
problem, so I'm not asking for any solutions. I'm looking for an explanation. 
It bugs me that my intuition of how this type class should have worked is 
completely wrong. The error message does not help, to put it mildly. Where 
should I go, what should I read?



___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: Re: [Haskell-cafe] Multi-parameter type class woes

2008-12-14 Thread Mario Blažević
 I'll take a swing at this one:
 
 instance Container (Maybe x) [x] where
 wrapper = isNothing
 . . .
 
 That isn't a sensible definition of 'wrapper', but I believe without 
 trying to compile it is completely legal.  Which wrapper do you use?
 
 You /don't/ have a different matching Container instance, but without the 
 functional dependency you /might/, and ghc barfs.


But liftWrap doesn't require any particular instance, it's a 
generic function accepting any pair of types for which there is 
an instance of Container. Instance selection (as I understand it)
shouldn't come into play until one applies liftWrap to a
particular type, and indeed it does cause problems there: note
the type annotations on the last line. That part I understand
and accept, or at least have learned to live with.


 On Sun, 14 Dec 2008, Mario Bla?evi? wrote:
 
 I have, for a change, a relatively simple problem with
 type classes. Can somebody explain to me, or point me to an explanation of
 the behaviour I see?

 Here is a short and useless example:

  {-# LANGUAGE MultiParamTypeClasses, FlexibleInstances #-}

   import Data.Maybe

   class Container x y where
  wrapper :: x - Bool
  unwrap :: x - y
  rewrap :: y - x

   liftWrap :: Container x y = (y - y) - (x - x)
   liftWrap f x = (if wrapper x then rewrap . f . unwrap else id) x

   instance Container (Maybe x) x where
  wrapper = isJust
  unwrap = fromJust
  rewrap = Just

   main = print (liftWrap (succ :: Int - Int) (Just 1 :: Maybe Int))

 GHC 6.10.1 refuses to typecheck the 'wrapper' function
 in definition of 'liftWrap', with the following error message:

Could not deduce (Container x y) from the context (Container x y1)
  arising from a use of `wrapper' at Test.hs:11:22-30
Possible fix:
  add (Container x y) to the context of
the type signature for `liftWrap'
In the expression: wrapper x
In the expression:
(if wrapper x then rewrap . f . unwrap else id) x
In the definition of `liftWrap':
liftWrap f x = (if wrapper x then rewrap . f . unwrap else id) x

 Let me clarify that I'm aware that in this particular
 example a functional dependecy should be used. Also, I can think of a few
 workarounds for my actual problem, so I'm not asking for any solutions. I'm
 looking for an explanation. It bugs me that my intuition of how this type
 class should have worked is completely wrong. The error message does not
 help, to put it mildly. Where should I go, what should I read?
 ___
 Haskell-Cafe mailing list
 Haskell-Cafe@haskell.org
 http://www.haskell.org/mailman/listinfo/haskell-cafe



___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: Re: [Haskell-cafe] Multi-parameter type class woes

2008-12-14 Thread Alexander Dunlap
On Sun, Dec 14, 2008 at 8:10 PM, Mario Blažević mblaze...@stilo.com wrote:
 I'll take a swing at this one:

 instance Container (Maybe x) [x] where
 wrapper = isNothing
 . . .

 That isn't a sensible definition of 'wrapper', but I believe without
 trying to compile it is completely legal.  Which wrapper do you use?

 You /don't/ have a different matching Container instance, but without the
 functional dependency you /might/, and ghc barfs.


But liftWrap doesn't require any particular instance, it's a
 generic function accepting any pair of types for which there is
 an instance of Container. Instance selection (as I understand it)
 shouldn't come into play until one applies liftWrap to a
 particular type, and indeed it does cause problems there: note
 the type annotations on the last line. That part I understand
 and accept, or at least have learned to live with.

The problem is that y is not mentioned in the signature of wrapper.
When you call wrapper x, there could be many different instances of
Container x y with the same x, so GHC doesn't know which version to
call. You can fix this problem either by adding a functional
dependency or by splitting wrapper out into its own class (Wrapper x,
e.g.) so all of the type variables in the class head are mentioned in
its type and the instance can be determined by the call.

Thanks for asking this question, by the way. I had known about this
issue but had never really realized why it happened. Now that I have
thought about it, I understand it too. :)

Hope that helps,
Alex
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: Re: [Haskell-cafe] Multi-parameter type class woes

2008-12-14 Thread Christopher Lane Hinson





On Sun, 14 Dec 2008, Mario Bla?evi? wrote:


I'll take a swing at this one:

instance Container (Maybe x) [x] where
wrapper = isNothing
. . .

That isn't a sensible definition of 'wrapper', but I believe without
trying to compile it is completely legal.  Which wrapper do you use?

You /don't/ have a different matching Container instance, but without the
functional dependency you /might/, and ghc barfs.



   But liftWrap doesn't require any particular instance, it's a
generic function accepting any pair of types for which there is
an instance of Container. Instance selection (as I understand it)
shouldn't come into play until one applies liftWrap to a
particular type, and indeed it does cause problems there: note
the type annotations on the last line. That part I understand
and accept, or at least have learned to live with.


Yes, that is an intuitive understanding to us humans, but the instance 
selection applies seperately for 'wrapper' and 'listWrap'; ghc doesn't 
automatically prefer a particular instance just because it is in the 
context of the calling function.


--L
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe