[Haskell-cafe] Typeclass question

2008-12-27 Thread Andrew Wagner
I'm sure there's a way to do this, but it's escaping me at present. I  
want to do something like this:


data Foo = Bar a = Foo a Bool ...

That is, I want to create a new type, Foo, whose constructor takes  
both a Boolean and a value of a type of class Bar.

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


Re: [Haskell-cafe] Typeclass question

2008-12-27 Thread David Menendez
On Sat, Dec 27, 2008 at 2:24 PM, Andrew Wagner wagner.and...@gmail.com wrote:
 I'm sure there's a way to do this, but it's escaping me at present. I want
 to do something like this:

 data Foo = Bar a = Foo a Bool ...

 That is, I want to create a new type, Foo, whose constructor takes both a
 Boolean and a value of a type of class Bar.

Try this:

{-# LANGUAGE ExistentialQuantification #-}

data Foo = forall a. Bar a = Foo a Bool


-- 
Dave Menendez d...@zednenem.com
http://www.eyrie.org/~zednenem/
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Typeclass question

2008-12-27 Thread Luke Palmer
On Sat, Dec 27, 2008 at 12:44 PM, David Menendez d...@zednenem.com wrote:

 On Sat, Dec 27, 2008 at 2:24 PM, Andrew Wagner wagner.and...@gmail.com
 wrote:
  I'm sure there's a way to do this, but it's escaping me at present. I
 want
  to do something like this:
 
  data Foo = Bar a = Foo a Bool ...
 
  That is, I want to create a new type, Foo, whose constructor takes both a
  Boolean and a value of a type of class Bar.

 Try this:

{-# LANGUAGE ExistentialQuantification #-}

data Foo = forall a. Bar a = Foo a Bool


Though for existentials, I find GADT more natural (actually I find GADT more
natural in most cases):

  data Foo where
  Foo :: Bar a = a - Foo

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


Re: [Haskell-cafe] Typeclass question

2008-12-27 Thread Miguel Mitrofanov

Seems like you want an existential type:

data Foo = forall a. Bar a = Foo a Bool

On 27 Dec 2008, at 22:24, Andrew Wagner wrote:

I'm sure there's a way to do this, but it's escaping me at present.  
I want to do something like this:


data Foo = Bar a = Foo a Bool ...

That is, I want to create a new type, Foo, whose constructor takes  
both a Boolean and a value of a type of class Bar.

___
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: [Haskell-cafe] Typeclass question

2008-12-27 Thread Miguel Mitrofanov

There is a disadvantage in GADTs. They don't work in Hugs.

On 27 Dec 2008, at 22:49, Luke Palmer wrote:

On Sat, Dec 27, 2008 at 12:44 PM, David Menendez d...@zednenem.com  
wrote:
On Sat, Dec 27, 2008 at 2:24 PM, Andrew Wagner wagner.and...@gmail.com 
 wrote:
 I'm sure there's a way to do this, but it's escaping me at  
present. I want

 to do something like this:

 data Foo = Bar a = Foo a Bool ...

 That is, I want to create a new type, Foo, whose constructor takes  
both a

 Boolean and a value of a type of class Bar.

Try this:

   {-# LANGUAGE ExistentialQuantification #-}

   data Foo = forall a. Bar a = Foo a Bool

Though for existentials, I find GADT more natural (actually I find  
GADT more natural in most cases):


  data Foo where
  Foo :: Bar a = a - Foo

Luke

___
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: [Haskell-cafe] Typeclass question

2008-12-27 Thread Andrew Wagner

Hmm, I actually simplified my problem too much. What I actually want is:
data Foo a = forall a. Bar a = Foo a Bool

...except I want the 'a' on the left to match the 'a' on the right, so  
that you can only construct values out of values of the parameterized  
type, which also must be of the Bar class.


On Dec 27, 2008, at 1:44 PM, David Menendez d...@zednenem.com wrote:

On Sat, Dec 27, 2008 at 2:24 PM, Andrew Wagner wagner.and...@gmail.com 
 wrote:
I'm sure there's a way to do this, but it's escaping me at present.  
I want

to do something like this:

data Foo = Bar a = Foo a Bool ...

That is, I want to create a new type, Foo, whose constructor takes  
both a

Boolean and a value of a type of class Bar.


Try this:

   {-# LANGUAGE ExistentialQuantification #-}

   data Foo = forall a. Bar a = Foo a Bool


--
Dave Menendez d...@zednenem.com
http://www.eyrie.org/~zednenem/

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


Re: [Haskell-cafe] Typeclass question

2008-12-27 Thread Miguel Mitrofanov

Oh! That's much simplier:

data Bar a = Foo a = Foo a Bool

On 27 Dec 2008, at 23:09, Andrew Wagner wrote:

Hmm, I actually simplified my problem too much. What I actually want  
is:

data Foo a = forall a. Bar a = Foo a Bool

...except I want the 'a' on the left to match the 'a' on the right,  
so that you can only construct values out of values of the  
parameterized type, which also must be of the Bar class.


On Dec 27, 2008, at 1:44 PM, David Menendez d...@zednenem.com  
wrote:


On Sat, Dec 27, 2008 at 2:24 PM, Andrew Wagner wagner.and...@gmail.com 
 wrote:
I'm sure there's a way to do this, but it's escaping me at  
present. I want

to do something like this:

data Foo = Bar a = Foo a Bool ...

That is, I want to create a new type, Foo, whose constructor takes  
both a

Boolean and a value of a type of class Bar.


Try this:

  {-# LANGUAGE ExistentialQuantification #-}

  data Foo = forall a. Bar a = Foo a Bool


--
Dave Menendez d...@zednenem.com
http://www.eyrie.org/~zednenem/

___
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: [Haskell-cafe] Typeclass question

2008-12-27 Thread Jake McArthur

Andrew Wagner wrote:

Hmm, I actually simplified my problem too much. What I actually want is:
data Foo a = forall a. Bar a = Foo a Bool

...except I want the 'a' on the left to match the 'a' on the right, so 
that you can only construct values out of values of the parameterized 
type, which also must be of the Bar class.


Well, you can ignore my previous contribution to this thread anyway. I 
failed to see the numerous other responses suggesting the same thing.


I recommend against what you are wanting to do. It is probably nicer to 
have something like this:


data Foo a = Foo a Bool -- don't export this

foo :: Bar a = a - Bool - Foo a -- export this
foo = Foo

You can also use GHC's new ViewPatterns extension if you would still 
like to be able to pattern match on Foo values in other modules and 
don't mind being restricted to more recent versions of GHC.


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


Re: [Haskell-cafe] Typeclass question

2008-12-27 Thread David Menendez
On Sat, Dec 27, 2008 at 3:09 PM, Andrew Wagner wagner.and...@gmail.com wrote:
 Hmm, I actually simplified my problem too much. What I actually want is:
 data Foo a = forall a. Bar a = Foo a Bool

 ...except I want the 'a' on the left to match the 'a' on the right, so that
 you can only construct values out of values of the parameterized type, which
 also must be of the Bar class.

Something like this?

{-# LANGUAGE ExistentialQuantification #-}

class Bar a where
bar :: a - a

data Foo a = (Bar a) = Foo a Bool

baz :: Foo a - a
baz (Foo a _) = bar a

This works fine for me with GHC 6.8, but I'd expect Hugs and earlier
versions of GHC to reject it.

See section 8.4.5 of the GHC manual.
http://www.haskell.org/ghc/docs/latest/html/users_guide/data-type-extensions.html#gadt-style

-- 
Dave Menendez d...@zednenem.com
http://www.eyrie.org/~zednenem/
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] typeclass question

2008-09-11 Thread Tim Docker
I have a typeclass related question that I have been puzzling over.

In a library I am working on, I have a series of functions for
converting values to Renderables:

| labelToRenderable :: Label - Renderable
| legendToRenderable :: Legend - Renderable
| axisToRenderable :: Axis v - Renderable
| layoutToRenderable :: Layout x y - Renderable

These names are overloaded for convenience via a typeclass:

| class ToRenderable a where
|   toRenderable :: a - Renderable
|
| instance ToRenderable Label where
|   toRenderable = labelToRenderable
| ...

But some recent changes mean that Renderable needs to become a type
constructor, and the functions now product different types:

| labelToRenderable :: Label - Renderable ()
| legendToRenderable :: Legend - Renderable String
| axisToRenderable :: Axis v - Renderable ()
| layoutToRenderable :: Layout x y a - Renderable a

Is there a nice way to overload a toRenderable function for these?
Something like this is possible:

| class ToRenderable a b where
|   toRenderable :: a - Renderable b

But the above is, I think, too general for my needs. I don't want
to be able to generate Renderables of different type b for a single input
type a.

Also, MPTC take me out of the world of haskell 98, which I was trying
to avoid. Am I missing something simple?

Any pointers would be much appreciated.

Tim


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


Re: [Haskell-cafe] typeclass question

2008-09-11 Thread Johannes Waldmann

 | class ToRenderable a b where
 |   toRenderable :: a - Renderable b
 
 But the above is, I think, too general for my needs. I don't want
 to be able to generate Renderables of different type b for a single input
 type a.

Sounds like a functional dependency (class ToReadable a b | a - b )

 Also, MPTC take me out of the world of haskell 98, which I was trying
 to avoid. 

Why. Everyone does it,
and MPTC will be in Haskell-Prime  (but FD may be not)
http://hackage.haskell.org/trac/haskell-prime/wiki/MultiParamTypeClassesDilemma

J.W.



signature.asc
Description: OpenPGP digital signature
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] typeclass question

2008-09-11 Thread Henning Thielemann


On Thu, 11 Sep 2008, Tim Docker wrote:


I have a typeclass related question that I have been puzzling over.

In a library I am working on, I have a series of functions for
converting values to Renderables:

| labelToRenderable :: Label - Renderable
| legendToRenderable :: Legend - Renderable
| axisToRenderable :: Axis v - Renderable
| layoutToRenderable :: Layout x y - Renderable

These names are overloaded for convenience via a typeclass:


I think that type classes are not for keystroke reduction, but for writing 
generic algorithms. If there is no algorithm that becomes more generic by 
the use of a type class, I would not use a type class, but stick to 
labelToRenderable and friends.

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


Re: [Haskell-cafe] typeclass question

2008-09-11 Thread Tim Docker
 Also, MPTC take me out of the world of haskell 98, which I was trying
 to avoid.

 Why. Everyone does it,

Well, it's a library that others might use, so I would prefer to avoid
using language extensions, especially functional deps which I don't
understand, and which seem to have an uncertain future.

Tim

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


Re: [Haskell-cafe] typeclass question

2008-09-11 Thread Johannes Waldmann
(Henning:)

 If there is no algorithm that becomes more generic by the use of a type
class,
 I would not use a type class, but stick to labelToRenderable [...]

The problem with function names as labelToRenderable
is that they have type information as part of the name.

Consistency of that information cannot be enforced by the language,
which makes it dangerous.

If you want type information
(e.g. to resolve overloading, for the compiler - and for the reader!)
use the language, and write a type annotation.

J.W.




signature.asc
Description: OpenPGP digital signature
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] typeclass question

2008-09-11 Thread Johannes Waldmann

 Well, it's a library that others might use, so I would prefer to avoid
 using language extensions, especially functional deps which I don't
 understand, and which seem to have an uncertain future.

I think there will be a storm of protest
if support for this simple shape of dependencies ( ... | a - b )
would be dropped from the major Haskell implementations.

(There used to be some status page on what compiler
supports what extension, anyone know the current location for that?)

J.W.



signature.asc
Description: OpenPGP digital signature
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] typeclass question

2008-09-11 Thread Jonathan Cast
On Thu, 2008-09-11 at 13:23 +0200, Johannes Waldmann wrote:
  Well, it's a library that others might use, so I would prefer to avoid
  using language extensions, especially functional deps which I don't
  understand, and which seem to have an uncertain future.
 
 I think there will be a storm of protest
 if support for this simple shape of dependencies ( ... | a - b )
 would be dropped from the major Haskell implementations.

For backwards-compatibility reasons, or because you think they're better
than type families?

Personally, I am quite enthusiastic about type families, although that
is influenced by a (somewhat abandoned) project of mine that ended up
with a 3 parameter type class (5 for the sub-class created for
quickCheck support) with one-to-one relations every way.  And multiple
`global' variables implemented with dynamic parameters (they would have
needed to be thread-local, eventually, anyway) with types parameterized
on the afore-mentioned 3 parameters plus two more to allow the choice
between ST and STM.  When you get types like this:

 -- | Wait for another thread to change the buffer contents.
 displayWaitRedisplay :: (Buffer b d mk,
   ?currentBuffer :: BufferState b d mk STM
TVar,
   ?currentWindow :: Window b d mk c STM TVar)
  = b TVar - STM ()

types like this:

 -- | Wait for another thread to change the buffer contents.
 displayWaitRedisplay :: (Buffer b, ?currentBuffer :: BufferState b STM,
  ?currentWindow :: Window b c STM)
  = b TVar - STM ()
 
look like heaven.

jcc


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


Re: [Haskell-cafe] typeclass question

2008-09-11 Thread Johannes Waldmann



if support for this simple shape of dependencies ( ... | a - b )  ...


For backwards-compatibility reasons, 


Yes.


or because you think they're better than type families?


Don't know (haven't used them).

Concrete example: I have  this class Partial p i b | p i - b
http://dfa.imn.htwk-leipzig.de/cgi-bin/cvsweb/tool/src/Challenger/Partial.hs?rev=1.28

What would type families buy me here?

In my code, this class has tons of instances (I count 80).
How much would I need to change them? Could this be automated?

Thanks - J.W.




signature.asc
Description: OpenPGP digital signature
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] typeclass question

2008-09-11 Thread Jonathan Cast
On Thu, 2008-09-11 at 18:34 +0200, Johannes Waldmann wrote:
  if support for this simple shape of dependencies ( ... | a - b )  ...
 
  For backwards-compatibility reasons, 
 
 Yes.

This gives point, then, to my concerns about letting Haskell become a
practical language.  At some point, production systems always seem to be
end-of-lifed by backwards compatibility.

  or because you think they're better than type families?
 
 Don't know (haven't used them).
 
 Concrete example: I have  this class Partial p i b | p i - b
 http://dfa.imn.htwk-leipzig.de/cgi-bin/cvsweb/tool/src/Challenger/Partial.hs?rev=1.28
 
 What would type families buy me here?

I can't figure out what b is.  I could, of course, argue that it would
force you to come up with a name for `b', so people reading the code
could understand what it does.

 In my code, this class has tons of instances (I count 80).
 How much would I need to change them?

   instance Partial p i b where
= instance Partial p i
 type B p i = b

And type signatures involving Partial would have to change.

  Could this be automated?

To a certain extent.  Finding the places that need to change could be
automated, which is always the first step :)

jcc


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


Re: [Haskell-cafe] typeclass question

2008-09-11 Thread Iavor Diatchki
Hi Tim,
Your example seems like a perfect fit for functional dependencies.

On Thu, Sep 11, 2008 at 3:36 AM, Tim Docker [EMAIL PROTECTED] wrote:
 Well, it's a library that others might use, so I would prefer to avoid
 using language extensions, especially functional deps which I don't
 understand, and which seem to have an uncertain future.

I completely agree with you that it is a good idea to stick to
Haskell'98 when you can, especially in library code, so you'll have to
decide if you really want to use the class.  As for not understanding
functional dependencies, it sounds like you are not giving yourself
enough credit.  Your previous comment basically contains the
definition of a functional dependency:

| But the above is, I think, too general for my needs. I don't want
| to be able to generate Renderables of different type b for a single input
| type a.

This is all there is to a fun. dep., from a programmer's
perspective---it adds a constraint on the instances one can declare
for a given multi-parameter type class.

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


[Haskell-cafe] Typeclass question

2006-12-03 Thread Jonathan Tang

I've got what's probably a beginner's question, but I'm out of ideas
for solving it.  It looks like it tripped me up in Write Yourself a
Scheme... too, since the code there seems like it's arranged so I
never ran into it...

I've got a couple functions:

binop :: (AmbrosiaData - AmbrosiaData - AmbrosiaM AmbrosiaData) -
AmbrosiaM ()
binop operator = do
 second - popStack
 first - popStack
 result - operator first second
 pushStack result

numNumOp ::  Num a = (a - a - a) - AmbrosiaData - AmbrosiaData -
AmbrosiaM AmbrosiaData
numNumOp op (Number val1) (Number val2) = return $ Number $ op val1 val2
numNumOp op (Float val1) (Float val2) = return $ Float $ op val1 val2
numNumOp op _ _ = throwError . TypeMismatch $ Number

the intention being that I can define primitive operations for an
interpreter with   (+, binop $ numNumOp (+)).  In the Number case,
val1  val2 are Integers, while in the Float case, they're Floats.
However, when I try to compile, I get:

./Primitives.hs:82:
   Cannot unify the type-signature variable `a'
   with the type `Integer'
   Expected type: Integer
   Inferred type: a
   In the application `op val1 val2'
   In the second argument of `($)', namely `op val1 val2'

This makes no sense to me, since Integer is an instance of Num and op
is defined as type Num a = a - a - a.  Shouldn't the typechecker be
able to instantiate 'a' with Integer and give the resulting type
Integer - Integer - Integer, and then pass the final Integer to
Number?  Is my understanding of typeclasses off somehow?

Any help would be appreciated.

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


Re: [Haskell-cafe] Typeclass question

2006-12-03 Thread Stefan O'Rear
On Sun, Dec 03, 2006 at 12:26:30PM -0500, Jonathan Tang wrote:
 I've got what's probably a beginner's question, but I'm out of ideas
 for solving it.  It looks like it tripped me up in Write Yourself a
 Scheme... too, since the code there seems like it's arranged so I
 never ran into it...
 
 I've got a couple functions:
 
 binop :: (AmbrosiaData - AmbrosiaData - AmbrosiaM AmbrosiaData) -
 AmbrosiaM ()
 binop operator = do
  second - popStack
  first - popStack
  result - operator first second
  pushStack result
 
 numNumOp ::  Num a = (a - a - a) - AmbrosiaData - AmbrosiaData -
 AmbrosiaM AmbrosiaData
 numNumOp op (Number val1) (Number val2) = return $ Number $ op val1 val2
 numNumOp op (Float val1) (Float val2) = return $ Float $ op val1 val2
 numNumOp op _ _ = throwError . TypeMismatch $ Number

When you say Num a = (a - a - a) - ..., what that means is:

numNumOp :: forall a. Num a = ((a - a - a) - AmbrosiaData - AmbrosiaData 
- AmbrosiaM AmbrosiaData)

That is, what you pass must be a single type.  It looks like what you
want is:

numNumOp :: (forall a. Num a = (a - a - a)) - AmbrosiaData - AmbrosiaData 
- AmbrosiaM AmbrosiaData

Notice that forall is in the argument - thus numNumOp must recieve a
polymorphic argument.  This is called rank-2 polymorphism, and numNumOp
is a rank-2 polymorphic function. Unfortunately, it turns out that
allowing foralls inside function arguments makes typechecking much
harder, in general impossible.  GHC allows it but requires explicit type
annotations on all rank-2 polymorphic functions.  Haskell98 forbids
rank-2 polymorphism altogether (and explicit foralls, for that matter).
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe