[Haskell-cafe] Type classes

2013-05-28 Thread Johannes Gerer
Dear Haskellers,

While trying to understand the interconnection and hierarchy behind
the important typeclasses, I stumbled upon the following question that
I am not able to answer:

There seems to be a hierachy of the type classes, in the sense, that
the more powerfull a class is, the more fleixblility you have for
combining them to complex programs. (Functor - Applicative -
Arrow[Choice,Plus,Apply,..] - Monad). It was nice to read in the
Typeclassopedia, that ArrowApply and Monad are equivalent, which is
shown by deriving two instances from each other:

instance Monad m = ArrowApply (Kleisli m)
instance ArrowApply a = Monad (a anyType)

The logic seems to be, that if I can derive from every instance of
class A an instance of class B, then A is more powerfull than B and
(in general) it is easier to be of class B than of class A (e.g. more
types can be made Applicatives, than Monads)

So far, I think I can follow. But what really hit me was the Cokleisli
type. Using it and the logic from above, I can show that ANY type
class is more (or equally) powerfull than the Monad:

instance AnyClass m = Monad (Cokleilsi m anyType)

I know this makes no sense, but where is the fallacy? Why even bother
with the above derivation, if any type class can be made into a monad?

I can see, that the Monad instance from above does not really
transform the type a, but instead simply fix its first argument. But
then on the other hand, the ArrowApply Instance does transform the m
type (in a way similar to Cokleisli). If attention needs to be paid to
the details, then what are they and why did they not matter above?

Thanks,

Johannes

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


Re: [Haskell-cafe] Type classes

2013-05-28 Thread Anton Kholomiov
I don't understand the final part of the question but here are some
comments for the first part.

I don't like the phrase:

 the more powerfull a class is, the more fleixblility you have for
 combining them to complex programs

powerfull, more flexibility, complex programs -- are not so precise terms.

A = B

means that B can do everything that A can do and more (methods that are
specific to B). So if type is in B we can use all A's methods with it. Does
it make B more powerful or more flexible? Is Applicative less powerful than
a Monad? It depends on the program. If we don't ever need the B's specific
operations they will confuse us all the time. We are going to end up with
more complex program but not a better one. there are cases when Applicative
code is much better than a monadic one.

Anton



2013/5/28 Johannes Gerer kue...@gmail.com

 Dear Haskellers,

 While trying to understand the interconnection and hierarchy behind
 the important typeclasses, I stumbled upon the following question that
 I am not able to answer:

 There seems to be a hierachy of the type classes, in the sense, that
 the more powerfull a class is, the more fleixblility you have for
 combining them to complex programs. (Functor - Applicative -
 Arrow[Choice,Plus,Apply,..] - Monad). It was nice to read in the
 Typeclassopedia, that ArrowApply and Monad are equivalent, which is
 shown by deriving two instances from each other:

 instance Monad m = ArrowApply (Kleisli m)
 instance ArrowApply a = Monad (a anyType)

 The logic seems to be, that if I can derive from every instance of
 class A an instance of class B, then A is more powerfull than B and
 (in general) it is easier to be of class B than of class A (e.g. more
 types can be made Applicatives, than Monads)

 So far, I think I can follow. But what really hit me was the Cokleisli
 type. Using it and the logic from above, I can show that ANY type
 class is more (or equally) powerfull than the Monad:

 instance AnyClass m = Monad (Cokleilsi m anyType)

 I know this makes no sense, but where is the fallacy? Why even bother
 with the above derivation, if any type class can be made into a monad?

 I can see, that the Monad instance from above does not really
 transform the type a, but instead simply fix its first argument. But
 then on the other hand, the ArrowApply Instance does transform the m
 type (in a way similar to Cokleisli). If attention needs to be paid to
 the details, then what are they and why did they not matter above?

 Thanks,

 Johannes

 ___
 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] Type classes

2013-05-28 Thread Johannes Gerer
Thank you for the comments on the first part. While one can argue
about
the different meanings of powerful and flexible here, that's not the
question. The question is, about showing A = B using wrappers like
Kleisli or Cokleisli:

I can use Kleisli to show that a Monad can do everything an
ArrowApply
can do:

Instance Monad m = ArrowApply (Kleisli m)

By the same argument, could'nt I say, that any type class (call it
AnyClass) can do everything a Monad can:

instance AnyClass m = Monad (Cokleilsi m ())




Another way to look at the question:

An Applicative lets you build static trees using the available
combinators. Arrows let you combine effectful computations into
networks
or graphs and monad even more complex things. But again Cokleilsi
crashes the party, as it gives you the Monad's combinators for any
type
and consequently you can build almost anything. I do not understand,
what this tells me!

Johannes

On Tue, May 28, 2013 at 3:04 PM, Anton Kholomiov
anton.kholom...@gmail.com wrote:
 I don't understand the final part of the question but here are some comments
 for the first part.

 I don't like the phrase:


 the more powerfull a class is, the more fleixblility you have for
 combining them to complex programs

 powerfull, more flexibility, complex programs -- are not so precise terms.

 A = B

 means that B can do everything that A can do and more (methods that are
 specific to B). So if type is in B we can use all A's methods with it. Does
 it make B more powerful or more flexible? Is Applicative less powerful than
 a Monad? It depends on the program. If we don't ever need the B's specific
 operations they will confuse us all the time. We are going to end up with
 more complex program but not a better one. there are cases when Applicative
 code is much better than a monadic one.

 Anton



 2013/5/28 Johannes Gerer kue...@gmail.com

 Dear Haskellers,

 While trying to understand the interconnection and hierarchy behind
 the important typeclasses, I stumbled upon the following question that
 I am not able to answer:

 There seems to be a hierachy of the type classes, in the sense, that
 the more powerfull a class is, the more fleixblility you have for
 combining them to complex programs. (Functor - Applicative -
 Arrow[Choice,Plus,Apply,..] - Monad). It was nice to read in the
 Typeclassopedia, that ArrowApply and Monad are equivalent, which is
 shown by deriving two instances from each other:

 instance Monad m = ArrowApply (Kleisli m)
 instance ArrowApply a = Monad (a anyType)

 The logic seems to be, that if I can derive from every instance of
 class A an instance of class B, then A is more powerfull than B and
 (in general) it is easier to be of class B than of class A (e.g. more
 types can be made Applicatives, than Monads)

 So far, I think I can follow. But what really hit me was the Cokleisli
 type. Using it and the logic from above, I can show that ANY type
 class is more (or equally) powerfull than the Monad:

 instance AnyClass m = Monad (Cokleilsi m anyType)

 I know this makes no sense, but where is the fallacy? Why even bother
 with the above derivation, if any type class can be made into a monad?

 I can see, that the Monad instance from above does not really
 transform the type a, but instead simply fix its first argument. But
 then on the other hand, the ArrowApply Instance does transform the m
 type (in a way similar to Cokleisli). If attention needs to be paid to
 the details, then what are they and why did they not matter above?

 Thanks,

 Johannes

 ___
 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] Type classes

2013-05-28 Thread Tom Ellis
On Tue, May 28, 2013 at 04:42:35PM +0200, Johannes Gerer wrote:
 By the same argument, could'nt I say, that any type class (call it
 AnyClass) can do everything a Monad can:
 
 instance AnyClass m = Monad (Cokleilsi m ())

That doesn't say that AnyClass can do anything a Monad can.  AnyClass m =
Monad m would say that, but that's not what you've got.

What you've got is that Cokleisli m () i.e. (-) m () is a Monad for any
m.  This is not surprising.  The implementation is the same as the Reader
monad.

Check out the instance implementations for Monad (Reader r) and Monad
(CoKleisli w a).  You will find they are the same.


http://hackage.haskell.org/packages/archive/mtl/1.1.0.2/doc/html/src/Control-Monad-Reader.html#Reader

http://hackage.haskell.org/packages/archive/comonad/3.0.0.2/doc/html/src/Control-Comonad.html#Cokleisli

Tom

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


Re: [Haskell-cafe] Type classes

2013-05-28 Thread Johannes Gerer
That makes sense. But why does

instance Monad m = ArrowApply (Kleisli m)

show that a Monad can do anything an ArrowApply can (and the two are
thus equivalent)?

On Tue, May 28, 2013 at 5:17 PM, Tom Ellis
tom-lists-haskell-cafe-2...@jaguarpaw.co.uk wrote:
 On Tue, May 28, 2013 at 04:42:35PM +0200, Johannes Gerer wrote:
 By the same argument, could'nt I say, that any type class (call it
 AnyClass) can do everything a Monad can:

 instance AnyClass m = Monad (Cokleilsi m ())

 That doesn't say that AnyClass can do anything a Monad can.  AnyClass m =
 Monad m would say that, but that's not what you've got.

 What you've got is that Cokleisli m () i.e. (-) m () is a Monad for any
 m.  This is not surprising.  The implementation is the same as the Reader
 monad.

 Check out the instance implementations for Monad (Reader r) and Monad
 (CoKleisli w a).  You will find they are the same.

 
 http://hackage.haskell.org/packages/archive/mtl/1.1.0.2/doc/html/src/Control-Monad-Reader.html#Reader
 
 http://hackage.haskell.org/packages/archive/comonad/3.0.0.2/doc/html/src/Control-Comonad.html#Cokleisli

 Tom

 ___
 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] Type classes

2013-05-28 Thread Tom Ellis
On Tue, May 28, 2013 at 05:21:58PM +0200, Johannes Gerer wrote:
 That makes sense. But why does
 
 instance Monad m = ArrowApply (Kleisli m)
 
 show that a Monad can do anything an ArrowApply can (and the two are
 thus equivalent)?

I've tried to chase around the equivalence between these two before, and
I didn't find the algebra simple.  I'll give an outline.

In non-Haskell notation

1) instance Monad m = ArrowApply (Kleisli m)

means that if m is a Monad then _ - m _ is an ArrowApply.

2) instance ArrowApply a = Monad (a anyType)

means that if _ ~ _ is an ArrowApply then a ~ _ is a Monad.

One direction seems easy: for a Monad m, 1) gives that _ - m _ is an
ArrowApply.  By 2), () - m _ is a Monad.  It is equivalent
to the Monad m we started with.

Given an ArrowApply _ ~ _, 2) shows that () ~ _ is a Monad.  Thus by
1) _ - (() ~ _) is an ArrowApply.  I believe this should be the same
type as _ ~ _ but I don't see how to demonstrate the isomorphsim here.

Tom

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


Re: [Haskell-cafe] Type classes

2013-05-28 Thread Johannes Gerer
Ok, now I see a difference, why Kleisli can be used to relate
typeclasses (like Monad and ArrowApply) and Cokleisli can not:

Kleisli m () _  =  () - m _ is isomorphic to m _

whereas

Cokleisli m () _ = m _ - () is not.

Can somebody point out the relevant category theoretical concepts,
that are at work here?



On Tue, May 28, 2013 at 5:43 PM, Tom Ellis
tom-lists-haskell-cafe-2...@jaguarpaw.co.uk wrote:
 On Tue, May 28, 2013 at 05:21:58PM +0200, Johannes Gerer wrote:
 That makes sense. But why does

 instance Monad m = ArrowApply (Kleisli m)

 show that a Monad can do anything an ArrowApply can (and the two are
 thus equivalent)?

 I've tried to chase around the equivalence between these two before, and
 I didn't find the algebra simple.  I'll give an outline.

 In non-Haskell notation

 1) instance Monad m = ArrowApply (Kleisli m)

 means that if m is a Monad then _ - m _ is an ArrowApply.

 2) instance ArrowApply a = Monad (a anyType)

 means that if _ ~ _ is an ArrowApply then a ~ _ is a Monad.

 One direction seems easy: for a Monad m, 1) gives that _ - m _ is an
 ArrowApply.  By 2), () - m _ is a Monad.  It is equivalent
 to the Monad m we started with.

 Given an ArrowApply _ ~ _, 2) shows that () ~ _ is a Monad.  Thus by
 1) _ - (() ~ _) is an ArrowApply.  I believe this should be the same
 type as _ ~ _ but I don't see how to demonstrate the isomorphsim here.

 Tom

 ___
 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] Type classes

2013-05-28 Thread Johannes Gerer
What about these two very simple type classes. Are they equivalent?
(As Monad and ArrowApply)

(This actually compiles in GHC)

class Pointed f where
  pure  :: a - f a

class Unit f where
  unit :: f a a

newtype UnitPointed f a = UnitPointed f a a
instance Unit f = Pointed (UnitPointed f) where
  pure f = UnitPointed unit

newtype Kleisli f a b = Kleisli (a - f b)
instance Pointed f = Unit (Kleisli f) where
  unit = Kleisli pure

On Tue, May 28, 2013 at 6:05 PM, Johannes Gerer kue...@gmail.com wrote:
 Ok, now I see a difference, why Kleisli can be used to relate
 typeclasses (like Monad and ArrowApply) and Cokleisli can not:

 Kleisli m () _  =  () - m _ is isomorphic to m _

 whereas

 Cokleisli m () _ = m _ - () is not.

 Can somebody point out the relevant category theoretical concepts,
 that are at work here?



 On Tue, May 28, 2013 at 5:43 PM, Tom Ellis
 tom-lists-haskell-cafe-2...@jaguarpaw.co.uk wrote:
 On Tue, May 28, 2013 at 05:21:58PM +0200, Johannes Gerer wrote:
 That makes sense. But why does

 instance Monad m = ArrowApply (Kleisli m)

 show that a Monad can do anything an ArrowApply can (and the two are
 thus equivalent)?

 I've tried to chase around the equivalence between these two before, and
 I didn't find the algebra simple.  I'll give an outline.

 In non-Haskell notation

 1) instance Monad m = ArrowApply (Kleisli m)

 means that if m is a Monad then _ - m _ is an ArrowApply.

 2) instance ArrowApply a = Monad (a anyType)

 means that if _ ~ _ is an ArrowApply then a ~ _ is a Monad.

 One direction seems easy: for a Monad m, 1) gives that _ - m _ is an
 ArrowApply.  By 2), () - m _ is a Monad.  It is equivalent
 to the Monad m we started with.

 Given an ArrowApply _ ~ _, 2) shows that () ~ _ is a Monad.  Thus by
 1) _ - (() ~ _) is an ArrowApply.  I believe this should be the same
 type as _ ~ _ but I don't see how to demonstrate the isomorphsim here.

 Tom

 ___
 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] Type classes

2013-05-28 Thread Tom Ellis
On Tue, May 28, 2013 at 09:09:48PM +0200, Johannes Gerer wrote:
 What about these two very simple type classes. Are they equivalent?
[...]
 class Pointed f where
   pure  :: a - f a
 
 class Unit f where
   unit :: f a a
 
 newtype UnitPointed f a = UnitPointed f a a
 instance Unit f = Pointed (UnitPointed f) where
   pure f = UnitPointed unit
 
 newtype Kleisli f a b = Kleisli (a - f b)
 instance Pointed f = Unit (Kleisli f) where
   unit = Kleisli pure

This is implausible, since pure f does not depend on f.

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


Re: [Haskell-cafe] Type classes

2013-05-28 Thread Johannes Gerer
Dear Tom,

I really appreciate your help, but If I could ask the perfect question
I probably would already know the answer... My example should not
prove anything, instead they collectively show, that I am missing
something. And it is not the fact, that pure f does not depend on f.
If, however, this makes all the difference, I have to ask, why was
plausability and looking at the actual definition (not just the types)
not important for the other examples.
But I think my problem lies somewhere else. Maybe all would become
evident, if I knew the rigorous definition of A is more general than
B in this context. Especially when A is a class of type, that takes
two arguments (i.e. Unit and Arrow) and B for ones, that takes only
one (like Monad, Pure,..)
Thanks again!
Johannes

On Tue, May 28, 2013 at 11:11 PM, Tom Ellis
tom-lists-haskell-cafe-2...@jaguarpaw.co.uk wrote:
 On Tue, May 28, 2013 at 09:09:48PM +0200, Johannes Gerer wrote:
 What about these two very simple type classes. Are they equivalent?
 [...]
 class Pointed f where
   pure  :: a - f a

 class Unit f where
   unit :: f a a

 newtype UnitPointed f a = UnitPointed f a a
 instance Unit f = Pointed (UnitPointed f) where
   pure f = UnitPointed unit

 newtype Kleisli f a b = Kleisli (a - f b)
 instance Pointed f = Unit (Kleisli f) where
   unit = Kleisli pure

 This is implausible, since pure f does not depend on f.

 ___
 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] Type classes

2013-05-28 Thread Tom Ellis
On Tue, May 28, 2013 at 11:22:22PM +0200, Johannes Gerer wrote:
 I have to ask, why was plausability and looking at the actual definition
 (not just the types) not important for the other examples.

It would also be important to check the definitions in the other examples
too, but it's hard enough to get the types to match!

 But I think my problem lies somewhere else. Maybe all would become
 evident, if I knew the rigorous definition of A is more general than
 B in this context. Especially when A is a class of type, that takes
 two arguments (i.e. Unit and Arrow) and B for ones, that takes only
 one (like Monad, Pure,..)

I'm not sure what the right definition is.  You are right that it is far
from obvious (at least to you and me!).

For a definition of equivalence, I feel it should go something like this:

To every instance a of A I can assign an instance b of B, and to every
instance b of B I can assign an instance a' of A.  Moreover there should be
a function polymorphic in all parameters between a and a', which has a
polymorphic inverse.  (And likewise for A and B swapped).  These functions
might need to be required to commute with all member functions of A.

Perhaps this is perfectly obvious and well known, but I haven't managed to
work it out on my own.

Tom

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


Re: [Haskell-cafe] Type classes, collections, sum types, closures, and a massive headache

2013-01-31 Thread Bob Hutchison
Thanks everyone, I very much appreciate your help, and I think it did help.

I've spent the last few days implementing a substantial chunk of my system 
using each of two different techniques. I've ended up going with and ADT 
containing functions closed over the 'thing'. This seems to be the consensus 
advice. For the record there was a perfectly viable alternative approach based 
on existential types 
(http://www.haskell.org/haskellwiki/Heterogenous_collections#Existential_types, 
thank Taylor, I'd read that and it didn't register… sigh). 

From what I could tell from trying them there's not a lot to choose between 
the two techniques, some small advantages for each. The existential types 
technique (despite criticism as an 
anti-patternhttps://lukepalmer.wordpress.com/2010/01/24/haskell-antipattern-existential-typeclass/,
 thanks Petr) is surprisingly to my taste… what can I say?

I ended up going with the ADT because I can shove some additional stuff in it, 
and since there's still a large exploratory aspect to the project this might 
matter.

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


Re: [Haskell-cafe] Type classes, collections, sum types, closures, and a massive headache

2013-01-31 Thread Bob Hutchison
for your convenience, the correct link: 
https://lukepalmer.wordpress.com/2010/01/24/haskell-antipattern-existential-typeclass/
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Type classes, collections, sum types, closures, and a massive headache

2013-01-30 Thread Tim Docker

On 29/01/2013, at 12:43 PM, Bob Hutchison hutch-li...@recursive.ca wrote:

 
 The immediate problem is mapping an input to the system, some json message 
 containing a reference to the 'thing' (like a key of some kind). I have to 
 take that reference and find the thing and operate on it. All operations are 
 easily accommodated by a type class. However, since I can't have a collection 
 with mixed types even if the types satisfy a type class, I can't quite see 
 how to actually store the things so I can find them.
 
 So there are a couple of obvious ways to handle this.
 
 I could use an ADT and a sum type of all the known kinds of thing, but I 
 already know that this has to be extended and that's going to be problematic 
 with users doing this on their own. And the type signatures look ugly. So I 
 think that's not the best.
 
 I could use an ADT that contains functions that correspond to the functions 
 of the type class, and that close over the 'thing' in question. I think this 
 could be made to work, but I'm concerned with walking into more nasty 
 surprises…
 

My advice is to go for the latter option. I'm not sure what nasty surprises you 
are expecting, but this record of functions approach is the one that I 
normally take when I am building a system that needs new types added without 
requiring global changes. I know that existentials and GADTs are possible 
solutions, but I've not needed the extra complexity here.

Cheers,

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


Re: [Haskell-cafe] Type classes, collections, sum types, closures, and a massive headache

2013-01-29 Thread Evan Laforge
 Today I thought it was about time to simplify how new 'things' of a certain 
 kind are added to the system. These things are some a cross between an event 
 and an assertion of a fact in a rule based system. There are many different 
 kinds of these things. I already have more than a dozen commonplace ones, and 
 I expect there's a much larger number of more specialized ones that a user 
 will want to add on their own. While they start out quite differently, they 
 end up satisfying a common interface and follow the identical three or four 
 state lifecycle. This sounded like a type class to me, and in fact, easily 
 implemented as such.

I hardly ever use typeclasses, I've never used existential types or
GADTs, and it's worked fine for me for many years.  Maybe just a
difference in programming style, or the sorts of things I write, but
implies at least that you can get very far not using any of that
stuff.

If each of your things have the same 3 or 4 states, can you make a
state into a value, and compose them?  E.g. 'thing1 = state1  state2
 thing1state where thing1state = ...' and state1 and state2 are
defined in a library.

If you have lots of different ways to take A to B and want to let the
caller configure it, then just pass an A-B function.  If you want to
configure an unpredictable subset of things, then maybe make a default
record and pass 'default { aToB = customVersion }'.  If each function
depends on a configuration environment that you want to inherit from
callers, then maybe put that record into a Reader.

In my case, the main design decision winds up being the balance of
data (i.e. records with values or functions) and code (i.e. functions
that do parts of what you want and can be composed together in various
ways).  Code is extensible and flexible but can't be manipulated, data
is inflexible (in that you have to hardcode some kind of schema),
but that means you can write functions to transform it.

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


[Haskell-cafe] Type classes, collections, sum types, closures, and a massive headache

2013-01-28 Thread Bob Hutchison
Hi,

I'm relatively new to Haskell, and consider myself to be towards the beginner 
side of the scale. Nevertheless, I've got this Haskell program I've been 
working on that's sitting around 11k lines right now. The pattern has been to 
let it grow to then knock it back by 'refactoring' or whatever you want to call 
it… doing it right the second time maybe… or the third time. All I want to get 
across is that though I consider myself a Haskell beginner I've still managed 
to produce something that is actually quite complex and of reasonable size in 
about three months.

I'm still getting caught by stuff that I should not be caught by.

So.

Today I thought it was about time to simplify how new 'things' of a certain 
kind are added to the system. These things are some a cross between an event 
and an assertion of a fact in a rule based system. There are many different 
kinds of these things. I already have more than a dozen commonplace ones, and I 
expect there's a much larger number of more specialized ones that a user will 
want to add on their own. While they start out quite differently, they end up 
satisfying a common interface and follow the identical three or four state 
lifecycle. This sounded like a type class to me, and in fact, easily 
implemented as such.

Now, this is how I got caught: it seems to be impossible to have collections of 
things with a common type class if they have different types. How is it that 
I've written that many lines of code in Haskell and I'm just noticing this now? 
(If I wasn't so annoyed, I'd look for something clever to reflect how loc count 
obviously doesn't mean much… but clever seems to be beyond me today).

Is this true? Are there any GHC extensions that will let me around this?

The immediate problem is mapping an input to the system, some json message 
containing a reference to the 'thing' (like a key of some kind). I have to take 
that reference and find the thing and operate on it. All operations are easily 
accommodated by a type class. However, since I can't have a collection with 
mixed types even if the types satisfy a type class, I can't quite see how to 
actually store the things so I can find them.

So there are a couple of obvious ways to handle this.

I could use an ADT and a sum type of all the known kinds of thing, but I 
already know that this has to be extended and that's going to be problematic 
with users doing this on their own. And the type signatures look ugly. So I 
think that's not the best.

I could use an ADT that contains functions that correspond to the functions of 
the type class, and that close over the 'thing' in question. I think this could 
be made to work, but I'm concerned with walking into more nasty surprises…

If anyone is able to make sense of what I wrote and has any suggestions I'd 
really appreciate hearing them.

Thanks,
Bob

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


Re: [Haskell-cafe] Type classes, collections, sum types, closures, and a massive headache

2013-01-28 Thread Taylor Hedberg
If I understand your message well enough, I think you are looking for
GHC's `ExistentialQuantification` extension. Building heterogeneous
collections is a common example of what existential types are useful
for. Take a look at this wiki page [1]; there is an example of how to
accomplish this there, along with a handful of other techniques.


[1] 
http://www.haskell.org/haskellwiki/Heterogenous_collections#Existential_types


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


Re: [Haskell-cafe] Type classes, collections, sum types, closures, and a massive headache

2013-01-28 Thread Darren Grant
On Mon, Jan 28, 2013 at 5:43 PM, Bob Hutchison hutch-li...@recursive.cawrote:


 Now, this is how I got caught: it seems to be impossible to have
 collections of things with a common type class if they have different
 types. How is it that I've written that many lines of code in Haskell and
 I'm just noticing this now? (If I wasn't so annoyed, I'd look for something
 clever to reflect how loc count obviously doesn't mean much… but clever
 seems to be beyond me today).

 Is this true? Are there any GHC extensions that will let me around this?


I just encountered this recently myself. There is a GADT
extension [1][2] that may help. The greater abstraction appears to lie in
existential types [3].

That being said, I'm a beginner as well and haven't yet used these
extensions. So far I have found that my code is simplified by redefining
heterogeneous types in terms of homogeneous functions.  If I have a class
that implements common methods, I will reorganize lists by common function
types rather than by class.

Cheers,
Darren


---
[1] http://www.haskell.org/haskellwiki/GADT
[2] http://www.haskell.org/haskellwiki/GADTs_for_dummies
[3] http://www.haskell.org/haskellwiki/Existential_type
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Type classes for converting to Text and String

2012-03-08 Thread Simon Hengel
Hi!

When writing library code that should work with both String and Text I
find my self repeatedly introducing classes like:

class ToString a where
  toString :: a - String

class ToText a where
  toText :: a - Text

(I use this with newtype wrapped value types backed by Text or
ByteString.)

So I wonder whether it would be a good idea to have a package that
provides those classes.

Or maybe just ToText, and provide default implementations of toString
and toText, like:

class ToText a where

  toText :: a - Text
  toText = Text.pack . toString

  toString :: a - String
  toString = Text.unpack . toText

How do you guys deal with that?  Any thoughts?

Cheers,
Simon

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


Re: [Haskell-cafe] Type classes for converting to Text and String

2012-03-08 Thread Christopher Done
On 8 March 2012 10:53, Simon Hengel s...@typeful.net wrote:
 When writing library code that should work with both String and Text I
 find my self repeatedly introducing classes like:

    class ToString a where
      toString :: a - String

    class ToText a where
      toText :: a - Text

Text is already an instance of IsString which provides IsString. I've
defined ToString in my own projects though, it would be nice for it to
be defined somewhere (Data.String maybe?).

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


Re: [Haskell-cafe] Type classes for converting to Text and String

2012-03-08 Thread Roman Cheplyaka
* Simon Hengel s...@typeful.net [2012-03-08 10:53:15+0100]
 When writing library code that should work with both String and Text I
 find my self repeatedly introducing classes like:
 [...]
 How do you guys deal with that?  Any thoughts?

If it's fine to depend on FunDeps, you can use ListLike.
http://hackage.haskell.org/package/ListLike

-- 
Roman I. Cheplyaka :: http://ro-che.info/

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


Re: [Haskell-cafe] Type classes for converting to Text and String

2012-03-08 Thread Simon Hengel
On Thu, Mar 08, 2012 at 11:00:34AM +0100, Christopher Done wrote:
 On 8 March 2012 10:53, Simon Hengel s...@typeful.net wrote:
  When writing library code that should work with both String and Text I
  find my self repeatedly introducing classes like:
 
     class ToString a where
       toString :: a - String
 
     class ToText a where
       toText :: a - Text
 
 Text is already an instance of IsString which provides IsString.

What exactly do you mean?

 I've defined ToString in my own projects though, it would be nice for
 it to be defined somewhere (Data.String maybe?).

We could write a proposal to add ToString to base (maybe a good idea,
not sure).  ToString has a striking similarity with Show, but it's still
different:

 * toString converts some a to a String
 * show gives a string _representation_ of some a

(e.g. converting a String to a String is just id and hence different
from show; this is akin to Python's __str__/__repr__)

But this does still not help with toText.

Cheers,
Simon

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


Re: [Haskell-cafe] Type classes for converting to Text and String

2012-03-08 Thread Simon Hengel
On Thu, Mar 08, 2012 at 12:18:56PM +0200, Roman Cheplyaka wrote:
 If it's fine to depend on FunDeps, you can use ListLike.
 http://hackage.haskell.org/package/ListLike

How would that help with toText?

Cheers,
Simon

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


Re: [Haskell-cafe] Type classes for converting to Text and String

2012-03-08 Thread Roman Cheplyaka
* Simon Hengel s...@typeful.net [2012-03-08 11:48:41+0100]
 On Thu, Mar 08, 2012 at 12:18:56PM +0200, Roman Cheplyaka wrote:
  If it's fine to depend on FunDeps, you can use ListLike.
  http://hackage.haskell.org/package/ListLike
 
 How would that help with toText?

toText = fromListLike

(ListLike instance for Text is provided by the listlike-instances
package.)

-- 
Roman I. Cheplyaka :: http://ro-che.info/

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


Re: [Haskell-cafe] Type classes for converting to Text and String

2012-03-08 Thread Yves Parès
If you just need to go back and forth from String to Text, why do you need
to be generic? pack and unpack from Data.Text do the job.

Plus, in the way of what Christopher said, you can use the
OverloadedStrings extension. You can then use the string syntax at a place
that expects a text:

{-# LANGUAGE OverloadedStrings #-}
import Data.Text

t :: Text
t = Hello

Any instance of the IsString class can be used in this way, not only Text.

2012/3/8 Simon Hengel s...@typeful.net

 Hi!

 When writing library code that should work with both String and Text I
 find my self repeatedly introducing classes like:

class ToString a where
  toString :: a - String

class ToText a where
  toText :: a - Text

 (I use this with newtype wrapped value types backed by Text or
 ByteString.)

 So I wonder whether it would be a good idea to have a package that
 provides those classes.

 Or maybe just ToText, and provide default implementations of toString
 and toText, like:

class ToText a where

  toText :: a - Text
  toText = Text.pack . toString

  toString :: a - String
  toString = Text.unpack . toText

 How do you guys deal with that?  Any thoughts?

 Cheers,
 Simon

 ___
 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] Type classes for converting to Text and String

2012-03-08 Thread Simon Hengel
On Thu, Mar 08, 2012 at 12:37:31PM +0100, Yves Parès wrote:
 If you just need to go back and forth from String to Text, why do you need
 to be generic? pack and unpack from Data.Text do the job.

Always going through String or Text may (depending on what your
underlying representation is) be less efficient than converting directly
to String/Text.

Cheers,
Simon

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


Re: [Haskell-cafe] Type classes for converting to Text and String

2012-03-08 Thread Simon Hengel
On Thu, Mar 08, 2012 at 12:54:13PM +0200, Roman Cheplyaka wrote:
 * Simon Hengel s...@typeful.net [2012-03-08 11:48:41+0100]
  On Thu, Mar 08, 2012 at 12:18:56PM +0200, Roman Cheplyaka wrote:
   If it's fine to depend on FunDeps, you can use ListLike.
   http://hackage.haskell.org/package/ListLike
  
  How would that help with toText?
 
 toText = fromListLike
 
 (ListLike instance for Text is provided by the listlike-instances
 package.)

Ah, the listlike-instances package is the missing piece.

Not sure if this is going somewhere.  But I'm still trying to get a
clear picture of the performance implications.

Say I have a newtype-wrapped ByteString that I would decode to
String/Text using UTF-8:

newtype Value = Value ByteString

Would it be possible to go from Value to Text by essentially ending up
with Data.Text.Encoding.decodeUtf8 at runtime (e.g. by using rewrite
rules)?

Cheers,
Simon

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


Re: [Haskell-cafe] Type classes for converting to Text and String

2012-03-08 Thread Roman Cheplyaka
* Simon Hengel s...@typeful.net [2012-03-08 13:20:22+0100]
 On Thu, Mar 08, 2012 at 12:54:13PM +0200, Roman Cheplyaka wrote:
  * Simon Hengel s...@typeful.net [2012-03-08 11:48:41+0100]
   On Thu, Mar 08, 2012 at 12:18:56PM +0200, Roman Cheplyaka wrote:
If it's fine to depend on FunDeps, you can use ListLike.
http://hackage.haskell.org/package/ListLike
   
   How would that help with toText?
  
  toText = fromListLike
  
  (ListLike instance for Text is provided by the listlike-instances
  package.)
 
 Ah, the listlike-instances package is the missing piece.
 
 Not sure if this is going somewhere.  But I'm still trying to get a
 clear picture of the performance implications.
 
 Say I have a newtype-wrapped ByteString that I would decode to
 String/Text using UTF-8:
 
 newtype Value = Value ByteString
 
 Would it be possible to go from Value to Text by essentially ending up
 with Data.Text.Encoding.decodeUtf8 at runtime (e.g. by using rewrite
 rules)?

You can do that, but it will work only if your functions are specialized
enough at compile time.

-- 
Roman I. Cheplyaka :: http://ro-che.info/

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


[Haskell-cafe] Type classes in Typing Haskell in Haskell

2011-12-29 Thread Alexander Bau

Hi,

recently I tried the Typing Haskell in Haskell library. But I was  
wondering why this program type checks:



-- plusMfun is standard '+': Num a = a - a - a
test =  let Just classEnv = ( addCoreClasses : addNumClasses )  
initialEnv

  e = Ap ( Ap (Var +) (Lit $ LitStr 3)) (Lit $ LitStr 5)
  impl = (foo,[([],e)])
  in
putStrLn $ pretty $ runTI $ tiImpls classEnv [plusMfun] [impl]


I was expecting some kind of typechecking error, because [Char] is no
instance of Num. But I get this:


([isIn1 cNum (TAp tList tChar)],
 [foo ::
Forall []
  ([] :=
 (TAp tList tChar))])


The predicate says that if [Char] would be in Num then the type of the  
expression would be [Char]. But actually [Char] isn't in Num. So, how do I  
provoke a type check error in this case?


Thanks in advance.


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


[Haskell-cafe] Type Classes in Haskell - how can I make GHC make a choice of types, when the type chosen doesn't matter?

2011-04-14 Thread Chris Dew
This is a question about the use of type classes in Haskell.

I get an error (below) when trying to compile the code (below and at
https://github.com/chrisdew/haskell-sandbox/blob/master/not_working_but_clean.hs
).

As someone just learning Haskell, I have tried following GHC's advice,
but I think the cause is different.

I believe the problem is that either of the types 'IO String' or plain
'String' could be the type of 'lhello - lbracket', but GHC doesn't
know which.

The problem is that it doesn't matter, either type would work fine.

I have posted a working version of the code at
https://github.com/chrisdew/haskell-sandbox/blob/master/working_but_ugly.hs
.  This replaces one of the - operators with a new (non type class)
operator '-' which forces 'lhello - lbracket' to be of type 'IO
String'.

* Is my analysis correct?  Or is there something else going on here?

* Is there any way of informing GHC what the type of 'lhello -
lbracket' doen't matter and that is should just chose either of the
two possibilities.  Or perhaps theres a LANGUAGE option which will let
me specify that 'lastest declared matching instance of the class wins'
if anything is undecided.

Thanks,

Chris.


Error:
chris@chris-linux-desktop:~/nonworkspace/haskell-sandbox$ ghc
not_working_but_clean.hs

not_working_but_clean.hs:40:16:
No instance for (Stream (IO String) (IO String) (IO String) d)
  arising from a use of `-' at not_working_but_clean.hs:40:16-34
Possible fix:
  add an instance declaration for
  (Stream (IO String) (IO String) (IO String) d)
In the first argument of `(-)', namely `lhello - lbracket'
In the second argument of `($)', namely
`lhello - lbracket - putStrLn'
In a stmt of a 'do' expression:
  forkIO $ lhello - lbracket - putStrLn

not_working_but_clean.hs:40:16:
No instance for (Stream d String (IO ()) (IO ()))
  arising from a use of `-' at not_working_but_clean.hs:40:16-47
Possible fix:
  add an instance declaration for (Stream d String (IO ()) (IO ()))
In the second argument of `($)', namely
`lhello - lbracket - putStrLn'
In a stmt of a 'do' expression:
  forkIO $ lhello - lbracket - putStrLn
In the expression:
do { forkIO $ (bracket $ hello) - putStrLn;
 forkIO $ lhello - lbracket - putStrLn;
 forkIO $ bracket hello - putStrLn;
 forkIO $ lbracket lhello - putStrLn;
    }



not_working_but_clean.hs:
{-# LANGUAGE MultiParamTypeClasses, FlexibleInstances,
TypeSynonymInstances, OverlappingInstances #-}
{-# OPTIONS_GHC #-}

module Main (
main
)
where

import Control.Concurrent (forkIO, MVar, newEmptyMVar, putMVar,
takeMVar, ThreadId, threadDelay)
import Control.Monad (forever, liftM)

class Stream a b c d where
(-) :: a - (b - c) - d

instance Stream (IO d) d (IO c) (IO c) where
f - g = f = g

instance Stream d d (IO c) (IO c) where
f - g = g f

instance Stream d d c c where
x - y = y $ x

-- This simply wraps a string in brackets.
bracket :: String - String
bracket x = ( ++ x ++ )

lbracket :: IO String - IO String
lbracket x = liftM bracket x

hello :: String
hello = Hello World!

lhello :: IO String
lhello = do return hello

main :: IO ()
main = do
   forkIO $ (bracket $ hello) - putStrLn
   forkIO $ lhello - lbracket - putStrLn
   forkIO $ bracket hello - putStrLn
   forkIO $ lbracket lhello - putStrLn
   threadDelay 1000 -- Sleep for at least 10 seconds before exiting.



working_but_ugly.hs:
{-# LANGUAGE MultiParamTypeClasses, FlexibleInstances,
TypeSynonymInstances, OverlappingInstances #-}
{-# OPTIONS_GHC #-}

module Main (
main
)
where

import Control.Concurrent (forkIO, MVar, newEmptyMVar, putMVar,
takeMVar, ThreadId, threadDelay)
import Control.Monad (forever, liftM)

class Stream a b c d where
(-) :: a - (b - c) - d

instance Stream (IO d) d (IO c) (IO c) where
f - g = f = g

instance Stream d d (IO c) (IO c) where
f - g = g f

instance Stream d d c c where
x - y = y $ x

x - y = y $ x

-- This simply wraps a string in brackets.
bracket :: String - String
bracket x = ( ++ x ++ )

lbracket :: IO String - IO String
lbracket x = liftM bracket x

hello :: String
hello = Hello World!

lhello :: IO String
lhello = do return hello

main :: IO ()
main = do
   forkIO $ (bracket $ hello) - putStrLn
   forkIO $ lhello - lbracket - putStrLn
   forkIO $ bracket hello - putStrLn
   forkIO $ lbracket lhello - putStrLn
   threadDelay 1000 -- Sleep for at least 10 seconds before exiting.

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


Re: [Haskell-cafe] Type Classes in Haskell - how can I make GHC make a choice of types, when the type chosen doesn't matter?

2011-04-14 Thread Neil Brown

On 14/04/11 13:00, Chris Dew wrote:

class Stream a b c d where
 (-) :: a -  (b -  c) -  d

instance Stream (IO d) d (IO c) (IO c) where
 f -  g = f= g

instance Stream d d (IO c) (IO c) where
 f -  g = g f

instance Stream d d c c where
 x -  y = y $ x



I notice that in all your instances, the last two types are the same.  
So do you need the final type parameter?  Could you not make it:


class Stream a b c where
  (-) :: a - (b - c) - c

I quickly tried this, and it fixes the errors you were getting.  If that 
doesn't hold for all instances you have in mind, then you may want to 
use functional dependencies or type families to specify a relationship 
between the types.


Thanks,

Neil.


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


Re: [Haskell-cafe] Type Classes in Haskell - how can I make GHC make a choice of types, when the type chosen doesn't matter?

2011-04-14 Thread Stephen Tetley
Hi Chris

What does the Stream class *do* though?

class Stream a b c d where
(-) :: a -  (b -  c) -  d

Even with Neil's change its still quite unusual:

class Stream a b c where
 (-) :: a - (b - c) - c

In the first formulation there is an input of type a, a function (b -
c) and a result of a completely different type d.

In Neil's class the function relates to the type of the answer but not
to the input.

The difficult type classes in Haskell - Applicative, Monad, and
Arrows / Category - are related to some degree to fairly standard
combinators on functions. But they generalize the combinators to
operate on other types than the function type (-). As there isn't a
relation between input and output, I don't quite see how the Stream
type could start as a combinator.

Best wishes

Stephen

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


Re: [Haskell-cafe] Type Classes in Haskell - how can I make GHC make a choice of types, when the type chosen doesn't matter?

2011-04-14 Thread Chris Dew
@Neil Brown - That did it.  It's not the ideal solution, as all -
are 'coerced' into being 'IO x' (if the rightmost term is an 'IO x'.
But it'll do for the time being.

Many thanks,

Chris.

On 14 April 2011 13:50, Neil Brown nc...@kent.ac.uk wrote:
 On 14/04/11 13:00, Chris Dew wrote:

 class Stream a b c d where
     (-) :: a -  (b -  c) -  d

 instance Stream (IO d) d (IO c) (IO c) where
     f -  g = f= g

 instance Stream d d (IO c) (IO c) where
     f -  g = g f

 instance Stream d d c c where
     x -  y = y $ x


 I notice that in all your instances, the last two types are the same.  So do
 you need the final type parameter?  Could you not make it:

 class Stream a b c where
  (-) :: a - (b - c) - c

 I quickly tried this, and it fixes the errors you were getting.  If that
 doesn't hold for all instances you have in mind, then you may want to use
 functional dependencies or type families to specify a relationship between
 the types.

 Thanks,

 Neil.



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


Re: [Haskell-cafe] Type Classes in Haskell - how can I make GHC make a choice of types, when the type chosen doesn't matter?

2011-04-14 Thread Chris Dew
@Stephen Tetley - The stream class exists simply to allow for the
creation of a - operator which can be used to 'Stream' data through
multiple pure and IO functions, on the way to some form of output.
It's probably not a great idea, as there are more idiomatic solutions
in Haskell - I'm sure someone will mention arrows.

I want the result of (-) to be what the following function requires,
either an 'a' or and 'IO a'.  This is too unconstrained if the
following function is flexible in it's input.  (e.g. another
application of (-)).   Hence my original problem.

a and b have are related, but not in a way I know how to express in
Haskell.  They are constrained to: a == b || IO a == b || a == IO b. c
and d have a similar constraint.

Could you suggest how these constraints could be expressed in the
Haskell type system?

Thanks,

Chris.

On 14 April 2011 14:28, Stephen Tetley stephen.tet...@gmail.com wrote:
 Hi Chris

 What does the Stream class *do* though?

 class Stream a b c d where
    (-) :: a -  (b -  c) -  d

 Even with Neil's change its still quite unusual:

 class Stream a b c where
  (-) :: a - (b - c) - c

 In the first formulation there is an input of type a, a function (b -
 c) and a result of a completely different type d.

 In Neil's class the function relates to the type of the answer but not
 to the input.

 The difficult type classes in Haskell - Applicative, Monad, and
 Arrows / Category - are related to some degree to fairly standard
 combinators on functions. But they generalize the combinators to
 operate on other types than the function type (-). As there isn't a
 relation between input and output, I don't quite see how the Stream
 type could start as a combinator.

 Best wishes

 Stephen

 ___
 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] Type Classes in Haskell - how can I make GHC make a choice of types, when the type chosen doesn't matter?

2011-04-14 Thread Stephen Tetley
On 14 April 2011 20:35, Chris Dew cms...@gmail.com wrote:

 Could you suggest how these constraints could be expressed in the
 Haskell type system?


Hi Chris

I'm afriad I'd have to decline - generally in Haskell implicit
lifters are problematic, so it isn't something I'd be looking to
solve.


There was a thread on Haskell Cafe about them last November called
Making monadic code more concise, that you might find interesting -
especially Oleg Kiselyov's comments:

http://www.haskell.org/pipermail/haskell-cafe/2010-November/086445.html

Best wishes

Stephen

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


Re: [Haskell-cafe] Type Classes in Haskell - how can I make GHC make a choice of types, when the type chosen doesn't matter?

2011-04-14 Thread Chris Dew
Thanks, that link's very relevant to what I'm trying.  For the time
being I'll accept a partial solution where the last two types are now
the same, and try to improve it when my knowledge of Haskell improves.

I really want (hello - bracket) in (hello - bracket -
putStrLn) to have a type of String.  Using the partial solution
which Neil Brown proposed, the code will work, but (hello -
bracket) will have a type of IO String which *seems* like it will be
less efficient.

All the best,

Chris.

On 14 April 2011 21:22, Stephen Tetley stephen.tet...@gmail.com wrote:
 On 14 April 2011 20:35, Chris Dew cms...@gmail.com wrote:

 Could you suggest how these constraints could be expressed in the
 Haskell type system?


 Hi Chris

 I'm afriad I'd have to decline - generally in Haskell implicit
 lifters are problematic, so it isn't something I'd be looking to
 solve.


 There was a thread on Haskell Cafe about them last November called
 Making monadic code more concise, that you might find interesting -
 especially Oleg Kiselyov's comments:

 http://www.haskell.org/pipermail/haskell-cafe/2010-November/086445.html

 Best wishes

 Stephen

 ___
 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] type classes and logic

2010-08-28 Thread Patrick Browne
Daniel Fischer wrote:
 class BEING human  = HUMAN human where
 Sub-classing is logical implication BEING(human)  = HUMAN(human)
 All types t that make BEING(t) = true also make HUMAN(t)=true
 
 No, it's the other way round. Every HUMAN is also a BEING, hence
 
 HUMAN(t) = BEING(t)

Could I say that HUMAN is a subset of BEING?

Sebastian Fischer wrote:
 You can define subclasses even if no instances exist. And as Daniel
 said, the code
 
 class BEING human = HUMAN human where
 
 defines a subclass HUMAN of BEING which means that every instance of
 HUMAN must also be a BEING. You can read it as: a BEING is also a HUMAN
 by the following definitions.

Thanks for pointing out my error
But I am still not sure of the interpretation of logical implication wrt
to sub-classes. Lets simplify the representation and just regard the
classes in the example as propositions (instead of predicates).
I am not sure if this simplification still makes the example valid.
Below is a reasonable interpretation of propositional logical implication.

a) If I wear a raincoat then I stay dry (sufficient condition)
wareRaincoat = stayDry
b) I will stay dry only if I ware a raincoat(necessary condition)
stayDry = wareRaincoat

In the light of the above examples how should I interpret the
class-to-subclass relation as logical implication? Is it
a)  If BEING then HUMAN (sufficient condition): BEING = HUMAN
b)  HUMAN is true only if BEING (necessary condition): HUMAN = BEING
c) Neither?

Thanks,
Pat


This message has been scanned for content and viruses by the DIT Information 
Services E-Mail Scanning Service, and is believed to be clean. http://www.dit.ie
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] type classes and logic

2010-08-28 Thread Sebastian Fischer

Daniel Fischer wrote:

class BEING human  = HUMAN human where
Sub-classing is logical implication BEING(human)  = HUMAN(human)
All types t that make BEING(t) = true also make HUMAN(t)=true


No, it's the other way round. Every HUMAN is also a BEING, hence

HUMAN(t) = BEING(t)


Could I say that HUMAN is a subset of BEING?


That depends on whether predicates are sets.. But yes, every instance  
of HUMAN is also an instance of BEING, hence, the set of HUMAN  
instances is a subset of the set of BEING instances.



In the light of the above examples how should I interpret the
class-to-subclass relation as logical implication? Is it
a)  If BEING then HUMAN (sufficient condition): BEING = HUMAN
b)  HUMAN is true only if BEING (necessary condition): HUMAN = BEING
c) Neither?


b). Every HUMAN is a BEING.

Cheers,
Sebastian

--
Underestimating the novelty of the future is a time-honored tradition.
(D.G.)



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


Re: [Haskell-cafe] type classes and logic

2010-08-28 Thread Brandon S Allbery KF8NH
-BEGIN PGP SIGNED MESSAGE-
Hash: SHA1

On 8/28/10 06:17 , Patrick Browne wrote:
 In the light of the above examples how should I interpret the
 class-to-subclass relation as logical implication? Is it
 a)  If BEING then HUMAN (sufficient condition): BEING = HUMAN
 b)  HUMAN is true only if BEING (necessary condition): HUMAN = BEING
 c) Neither?

(b).  But there's an additional wrinkle:  what it really says is A HUMAN is
(...).  Oh, and it's a BEING too.  Which is to say, Haskell doesn't look at
BEING until *after* it's decided something is a HUMAN.  (Technically
speaking, constraints are not used when selecting an instance; they're
applied after the fact, and if the selected instance doesn't conform then it
throws a type error.)

- -- 
brandon s. allbery [linux,solaris,freebsd,perl]  allb...@kf8nh.com
system administrator  [openafs,heimdal,too many hats]  allb...@ece.cmu.edu
electrical and computer engineering, carnegie mellon university  KF8NH
-BEGIN PGP SIGNATURE-
Version: GnuPG v2.0.10 (Darwin)
Comment: Using GnuPG with Mozilla - http://enigmail.mozdev.org/

iEYEARECAAYFAkx5KOcACgkQIn7hlCsL25UWyQCfTblcgeEfwOci9KE7leVs07aN
VT4AoJAwHqXoD6nbD+TZVRlAWj3N99SM
=jA0B
-END PGP SIGNATURE-
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] type classes and logic

2010-08-27 Thread Patrick Browne
Hi,
I am trying to understand type classes and sub-classes in purely logical
terms From the literature I gather that:
 1)a type class is a predicate over types (using type variables)
 2)type sub-classing is a logical implication between these predicates.

But I feel that 1) and 2) does not give enough detail and I am missing
the logical significance of the function definitions in the class and
their implementations in the instances. This following example outlines
my current (mis?)understanding:

data Person = Person Name deriving Show
data Employee = Employee Name Position deriving Show

class BEING being where

The class BEING is logically a predicate with type variable being(i.e.
BEING(being))
BEING(being) is true for types that are members of the BEING type class.
Any types that instantiate the type class BEING will have all the BEING
class functions defined on them.
Such a type is a member of the type-class BEING
Actual function signatures and/or default implementations omitted


A proof for the  predicate BEING(being) must show that there is an
inhabited type (a type which has values)
If we find a value for a type that is a proof that a type exists (it is
inhabited) that is a member of the class

instance BEING Person where

All the functions from the class BEING must be defined for the type Person
It is required the functions in the instance respect the types from the
class and type from the instantiated parameter.
t is required that when the functions are run they produce values of the
required type.
Implementations omitted



With at least one instantiation existing (e.g.  BEING(Person) = true) we
can define a sub-class
In the sub-class definition we can assume BEING(human) to be true (type
variable name does not matter)
And based on that assumption we can write a logical implication
BEING(human)  = HUMAN(human)

class BEING human  = HUMAN human where

At this point there is no additional functionality is defined for the
subclass HUMAN
Sub-classing is logical implication BEING(human)  = HUMAN(human)
All types t that make BEING(t) = true also make HUMAN(t)=true
In general for the HUMAN sub-class to be useful additional constraints
are added after the where keyword. These are similar in purpose to those
described in an ordinary class (not a sub-class)


Another example from Bird[1.Intro. to Functional Prog. using Haskell]
class Enum a where
 toEnum :: a - Int
 fromEnum :: Int - a

A type is declared an instance of the class Enum by giving definitions
toEnum and fromEnum, functions that convert between elements of the type
a and the type Int. In instance declarations fromEnum should be a left
inverse to toEnum That is for all x fromEnum(toEnum x) = x. This
requirement cannot be expressed in Haskell




My questions are:
a) Is the above *logical view* of type classes correct?

b) What is the logical role of the functions in the classes and
instances. Are they constraints on the types in predicates?

c) Apart from signature matching between class-to-instance is there any
logical relation between the functions in a class and the functions in
an instances. From Birds[1] example I suspect that while the types are
subject to logical rules of 1) and 2) the actual functions in the
instance do not have to obey any logical laws. Any instantiation that
respects types is fine?

Regards,
Pat


This message has been scanned for content and viruses by the DIT Information 
Services E-Mail Scanning Service, and is believed to be clean. http://www.dit.ie
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] type classes and logic

2010-08-27 Thread Daniel Fischer
On Friday 27 August 2010 14:54:53, Patrick Browne wrote:
 class BEING human  = HUMAN human where

 At this point there is no additional functionality is defined for the
 subclass HUMAN
 Sub-classing is logical implication BEING(human)  = HUMAN(human)
 All types t that make BEING(t) = true also make HUMAN(t)=true

No, it's the other way round. Every HUMAN is also a BEING, hence

HUMAN(t) = BEING(t)

Admittedly, the notation for subclasses in Haskell is backwards.

The corresponding situation for Java interfaces (which are roughly 
analogous to type classes) would be

interface BEING{ ... }

interface HUMAN extends BEING{ ... }
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] type classes and logic

2010-08-27 Thread Sebastian Fischer

Hi Pat,


A proof for the  predicate BEING(being) must show that there is an
inhabited type (a type which has values)


Note that in a lazy language like Haskell every type is inhabited by _| 
_, that is, bottom the undefined value.


If we find a value for a type that is a proof that a type exists (it  
is

inhabited) that is a member of the class


I don't understand the above statement. The inhabitedness of a type  
does not tell us anything about which classes it belongs to. Instance  
declarations do.


With at least one instantiation existing (e.g.  BEING(Person) =  
true) we

can define a sub-class


You can define subclasses even if no instances exist. And as Daniel  
said, the code


class BEING human = HUMAN human where

defines a subclass HUMAN of BEING which means that every instance of  
HUMAN must also be a BEING. You can read it as: a BEING is also a  
HUMAN by the following definitions.



In general for the HUMAN sub-class to be useful additional constraints
are added after the where keyword. These are similar in purpose to  
those

described in an ordinary class (not a sub-class)


The additional constraints are additional functions that need to be  
available.



What is the logical role of the functions in the classes and
instances. Are they constraints on the types in predicates?


BEING(Person) tells you that the type Person implements the functions  
declared in the type class BEING.



Any instantiation that respects types is fine?


That depends whether you ask a compiler or a programmer. The compiler  
is satisfied if you respect the types. But type classes often come  
with additional laws on the operations that programmers have come to  
expect. For example, every implementation of the function == of the Eq  
class should be an equivalence relation and a Monad instance should  
obey the monad laws. Although the compiler does not complain if it  
doesn't, users of such an invalid Monad instance eventually will.


Cheers,
Sebastian


--
Underestimating the novelty of the future is a time-honored tradition.
(D.G.)



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


Re: [Haskell-cafe] type classes and logic

2010-08-27 Thread Patrick Browne
Sebastian,
Thanks for your very useful reply.
Does the EQ example below not talk about inhabited types as proofs.

Thanks,
Pat



Sebastian Fischer wrote:
 If we find a value for a type that is a proof that a type exists (it is
 inhabited) that is a member of the class

 I don't understand the above statement. The inhabitedness of a type
 does not tell us anything about which classes it belongs to. Instance
 declarations do.

The EQ example following is from:
http://www.haskell.org/haskellwiki/Curry-Howard-Lambek_correspondence

A type class in Haskell is a proposition about a type.

class Eq a where
(==) :: a - a - Bool
(/=) :: a - a - Bool

means, logically, there is a type a for which the type a - a - Bool is
inhabited, or, from a it can be proved that a - a - Bool (the class
promises two different proofs for this, having names == and /=). This
proposition is of existential nature. A proof for this proposition (that
there is a type that conforms to the specification) is (obviously) a set
of proofs of the advertised proposition (an implementation), by an
instance declaration:

instance Eq Bool where
True  == True  = True
False == False = True
_ == _ = False

(/=) a b = not (a == b)


This message has been scanned for content and viruses by the DIT Information 
Services E-Mail Scanning Service, and is believed to be clean. http://www.dit.ie
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Type classes

2010-07-04 Thread Ivan Lazar Miljenovic
Andrew Coppin andrewcop...@btinternet.com writes:

 In summary, I think we need to devise a way of better-documenting
 class instances. 

Haddock 2.7 supports documenting instance implementations; I don't know
how this works, but according to the Changelog it's available.

-- 
Ivan Lazar Miljenovic
ivan.miljeno...@gmail.com
IvanMiljenovic.wordpress.com
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Type classes

2010-07-04 Thread Ross Paterson
On Sun, Jul 04, 2010 at 09:55:53PM +1000, Ivan Lazar Miljenovic wrote:
 Andrew Coppin andrewcop...@btinternet.com writes:
  In summary, I think we need to devise a way of better-documenting
  class instances. 
 
 Haddock 2.7 supports documenting instance implementations; I don't know
 how this works, but according to the Changelog it's available.

Now we need to go round and document our instances.

Hmm, it seems only partial: documentation attached to an instance is shown
in the list of instances under a type, but not the list under a class.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Type classes

2010-07-04 Thread Ivan Lazar Miljenovic
Ross Paterson r...@soi.city.ac.uk writes:

 On Sun, Jul 04, 2010 at 09:55:53PM +1000, Ivan Lazar Miljenovic wrote:
 Andrew Coppin andrewcop...@btinternet.com writes:
  In summary, I think we need to devise a way of better-documenting
  class instances. 
 
 Haddock 2.7 supports documenting instance implementations; I don't know
 how this works, but according to the Changelog it's available.

 Now we need to go round and document our instances.

 Hmm, it seems only partial: documentation attached to an instance is shown
 in the list of instances under a type, but not the list under a class.

I'm guessing that's to reduce noise...

-- 
Ivan Lazar Miljenovic
ivan.miljeno...@gmail.com
IvanMiljenovic.wordpress.com
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Type classes

2010-07-04 Thread David Waern
2010/7/4 Ivan Lazar Miljenovic ivan.miljeno...@gmail.com:
 Andrew Coppin andrewcop...@btinternet.com writes:

 In summary, I think we need to devise a way of better-documenting
 class instances.

 Haddock 2.7 supports documenting instance implementations; I don't know
 how this works, but according to the Changelog it's available.

It's simple:

 -- | Documentation for the instance
 instance Monoid Foo

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


Re: [Haskell-cafe] Type classes

2010-07-04 Thread Daniel Fischer
On Sunday 04 July 2010 14:07:03, Ivan Lazar Miljenovic wrote:
 Ross Paterson r...@soi.city.ac.uk writes:
  On Sun, Jul 04, 2010 at 09:55:53PM +1000, Ivan Lazar Miljenovic wrote:
  Andrew Coppin andrewcop...@btinternet.com writes:
   In summary, I think we need to devise a way of better-documenting
   class instances.
 
  Haddock 2.7 supports documenting instance implementations; I don't
  know how this works, but according to the Changelog it's available.
 
  Now we need to go round and document our instances.
 
  Hmm, it seems only partial: documentation attached to an instance is
  shown in the list of instances under a type, but not the list under a
  class.

 I'm guessing that's to reduce noise...

I'm guessing it might have something to do with the fact that often the 
module containing the class definition isn't processed together with the 
module containing the instance declaration.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Type classes

2010-07-04 Thread Daniel Fischer
On Sunday 04 July 2010 14:03:51, Ross Paterson wrote:

 Now we need to go round and document our instances.

 Hmm, it seems only partial: documentation attached to an instance is
 shown in the list of instances under a type, but not the list under a
 class.

Not much of a problem. Right-click on the type-link, open in new tab.
Except for orphan instances, I presume.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Type classes

2010-07-04 Thread David Waern
2010/7/4 Daniel Fischer daniel.is.fisc...@web.de:

  Hmm, it seems only partial: documentation attached to an instance is
  shown in the list of instances under a type, but not the list under a
  class.

 I'm guessing that's to reduce noise...

 I'm guessing it might have something to do with the fact that often the
 module containing the class definition isn't processed together with the
 module containing the instance declaration.

Actually Haddock attaches instance information to the modules in a
separate step after having processed all of them. The fact that no
documentation shows up for instances under the class documentation is
a bug, embarrasingly enough, which I hadn't noticed. Looking at the
code, it's not that I've forgotten to add code to the Html backend,
it's something deeper that is wrong, so I will have to investigate.

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


Re: [Haskell-cafe] Type classes

2010-07-04 Thread Ross Paterson
On Sun, Jul 04, 2010 at 02:32:35PM +0200, Daniel Fischer wrote:
 On Sunday 04 July 2010 14:07:03, Ivan Lazar Miljenovic wrote:
  Ross Paterson r...@soi.city.ac.uk writes:
   Hmm, it seems only partial: documentation attached to an instance is
   shown in the list of instances under a type, but not the list under a
   class.
 
  I'm guessing that's to reduce noise...
 
 I'm guessing it might have something to do with the fact that often the 
 module containing the class definition isn't processed together with the 
 module containing the instance declaration.

It could be either way: sometimes you define a new class with instances
for existing types, and with the current implementation that produces
no documentation.

(I tested with type, class and instance in the same package.)
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Type classes

2010-07-04 Thread Ivan Lazar Miljenovic
David Waern david.wa...@gmail.com writes:

 2010/7/4 Ivan Lazar Miljenovic ivan.miljeno...@gmail.com:
 Andrew Coppin andrewcop...@btinternet.com writes:

 In summary, I think we need to devise a way of better-documenting
 class instances.

 Haddock 2.7 supports documenting instance implementations; I don't know
 how this works, but according to the Changelog it's available.

 It's simple:

 -- | Documentation for the instance
 instance Monoid Foo

It's not for each method, just for the overall instance?  I was kinda
hoping to use it to be able to put runtime bounds on instances of some
classes :(

-- 
Ivan Lazar Miljenovic
ivan.miljeno...@gmail.com
IvanMiljenovic.wordpress.com
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Type classes

2010-07-04 Thread David Waern
2010/7/4 Ivan Lazar Miljenovic ivan.miljeno...@gmail.com:
 David Waern david.wa...@gmail.com writes:

 2010/7/4 Ivan Lazar Miljenovic ivan.miljeno...@gmail.com:
 Andrew Coppin andrewcop...@btinternet.com writes:

 In summary, I think we need to devise a way of better-documenting
 class instances.

 Haddock 2.7 supports documenting instance implementations; I don't know
 how this works, but according to the Changelog it's available.

 It's simple:

 -- | Documentation for the instance
 instance Monoid Foo

 It's not for each method, just for the overall instance?  I was kinda
 hoping to use it to be able to put runtime bounds on instances of some
 classes :(

It's just for the overall instance at the moment. Haddock doesn't
document instance declarations separately.

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


Re: [Haskell-cafe] Type classes

2010-07-04 Thread David Waern
2010/7/4 Ross Paterson r...@soi.city.ac.uk:

 It could be either way: sometimes you define a new class with instances
 for existing types, and with the current implementation that produces
 no documentation.

 (I tested with type, class and instance in the same package.)

Hi Ross, thanks for testing this. Could you send me the file(s) you
used? I wasn't able to reproduce the issue here with a few simple
tests.

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


Re: [Haskell-cafe] Type classes

2010-07-04 Thread David Waern
2010/7/4 David Waern david.wa...@gmail.com:
 2010/7/4 Daniel Fischer daniel.is.fisc...@web.de:

  Hmm, it seems only partial: documentation attached to an instance is
  shown in the list of instances under a type, but not the list under a
  class.

 I'm guessing that's to reduce noise...

 I'm guessing it might have something to do with the fact that often the
 module containing the class definition isn't processed together with the
 module containing the instance declaration.

 Actually Haddock attaches instance information to the modules in a
 separate step after having processed all of them. The fact that no
 documentation shows up for instances under the class documentation is
 a bug, embarrasingly enough, which I hadn't noticed. Looking at the
 code, it's not that I've forgotten to add code to the Html backend,
 it's something deeper that is wrong, so I will have to investigate.

I found the bug and fixed it, it's in the latest darcs version at
http://code.haskell.org/haddock.

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


Re: [Haskell-cafe] Type classes

2010-07-04 Thread Andrew Coppin

David Waern wrote:

I found the bug and fixed it, it's in the latest darcs version


Open Source Works.(tm)

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


[Haskell-cafe] Type classes

2008-12-26 Thread Oscar Picasso
From Real World Haskell:

data JValue = JString String
| JNumber Double
| JBool Bool
| JNull
| JObject [(String, JValue)]
| JArray [JValue]
  deriving (Eq, Ord, Show)


type JSONError = String

class JSON a where
toJValue :: a - JValue
fromJValue :: JValue - Either JSONError a

instance JSON JValue where
toJValue = id -- Really ?
fromJValue = Right

Now, instead of applying a constructor like JNumber to a value to wrap it,
 we apply the toJValue function. If we change a value's type, the compiler
 will choose a suitable implementation of toJValue to use with it.


Actually it does not work. And I don't see how it could with this toJValue
implementation. Is it possible to make it work by providing another
implementation?

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


Re: [Haskell-cafe] Type classes vr.s functions

2008-12-24 Thread Brian Hurt



On Tue, 23 Dec 2008, wren ng thornton wrote:

In particular, imagine that you have two different and valid ways to convert 
the same type into Foo; which do you choose? With the 
continuation/combinator/argument approach this is a non-issue since you can 
just pass in the one you need. With type-classes it's tricky since they're 
the same type, which leads to hacks with newtype wrappers or phantom types.


If there is guaranteed to be only one valid transformation from any given 
type into Foo, then type-classes make your intentions clear and they never 
run into this issue. If more than one valid transformation could exist for 
some type, then the extra argument is cleaner.


In this case, there is gaurenteed to be only one valid transformation. 
Basically, I have a number of similar data structures (which enforce 
different constraints, which is why they're not all the same data 
structure), and the function in question converts the specific 
(constraint-enforcing) data structures into a general 
(non-constraint-enforcing) data structure on which I can perform generic 
algorithms.


To be more specific, I'm writing a compiler in Haskell (what a shock), and 
the source data structures are the parse trees after various 
transformations- for example, after the lambda lifting phase, the parse 
tree should not have lambda expressions in them at all (they should have 
all been lifted to top-level functions).  So, while the 
before-lambda-lifting data structure has a Lambda constructor, the 
after-lambda-lifting data structure doesn't, thus enforcing the constraint 
that lambda lifting removes all (non-top-level) lambda expressions.  But I 
want to be able to get all free variables of a given expression, both 
before and after lambda lifting, so I just define a function to convert 
both types into a common generic representation that I can write a get 
free variables function to work on.


At this point, I realize that I'm being stupid and way over thinking 
things.  Haskell is a *lazy* language- I'm still wrapping my head around 
the implications of that statement.  My original thinking was that the 
conversion function would be a one-level conversion, i.e. the data 
structure would be like:

data Generic a =
UnaryOp uop a
| BinaryOp a bop a
| If a a a
...

i.e. I'd only convert the root node, and the child nodes would still be 
the original data structure.  So I'd need to pass around a function of the

form:
a - Generic a
which is my conversion function.  But what I'm doing here is 
hand-reimplementing a lazy conversion of the data structure- which I get 
for free anyways.  So what I should do is define the data structure like:

data Generic =
UnaryOp uop Generic
| BinaryOp Generic bop Generic
| If Generic Generic Generic
...

Then all I need to do is to write the pure conversion function a - 
Generic, and then run the generic algorithm over the data structure.  That 
gives me the exact behavior I'm looking for, without either (explicitly) 
passing a conversion function around or playing with fancy typeclasses.


Pardon me while I go beat my head against the wall.

Brian

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


Re: [Haskell-cafe] Type classes vr.s functions

2008-12-23 Thread wren ng thornton

Brian Hurt wrote:


So, style question for people, if I can.  I have a certain problem-
basically, I have a bunch of functions which need a special function,
of type a - Foo say.  And a bunch of other functions which can define
that function on some type of interest, and then what to call the first
batch of functions.  I can do this either by defining a type class,
something like:
class Fooable a where
toFoo :: a - Foo
or I can simply have all the functions which need a toFoo take an extra
agrument.  Performance really isn't that important here, so it's really
a matter of style- which approach would people prefer in this case?


For issues of style, I would say to use type-classes. However, this 
isn't strictly a question of style. As Luke Palmer mentions there are 
differences of power between the two.


In particular, imagine that you have two different and valid ways to 
convert the same type into Foo; which do you choose? With the 
continuation/combinator/argument approach this is a non-issue since you 
can just pass in the one you need. With type-classes it's tricky since 
they're the same type, which leads to hacks with newtype wrappers or 
phantom types.


If there is guaranteed to be only one valid transformation from any 
given type into Foo, then type-classes make your intentions clear and 
they never run into this issue. If more than one valid transformation 
could exist for some type, then the extra argument is cleaner.


Note that when I say any given type I mean the domain of values along 
with its semantic connotations. For instance, there's a straightforward 
way of 'converting' Double into an instance of Num. However, if we 
semantically interpret the values of Double as if they were in the 
log-domain, then there is a different way to convert it into Num[1]. But 
really, these are different types because they have different semantics 
even if they have the same values. Though much abused, newtype 
declarations are intended to capture exactly this distinction between 
values and semantics, and they make it straightforward for the Haskell 
type-checker to see that they are indeed different types.


[1] http://hackage.haskell.org/cgi-bin/hackage-scripts/package/logfloat

--
Live well,
~wren
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Type classes vr.s functions

2008-12-20 Thread Brian Hurt


So, style question for people, if I can.  I have a certain problem-
basically, I have a bunch of functions which need a special function,
of type a - Foo say.  And a bunch of other functions which can define
that function on some type of interest, and then what to call the first
batch of functions.  I can do this either by defining a type class,
something like:
class Fooable a where
toFoo :: a - Foo
or I can simply have all the functions which need a toFoo take an extra
agrument.  Performance really isn't that important here, so it's really
a matter of style- which approach would people prefer in this case?

Brian

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


Re: [Haskell-cafe] Type classes vr.s functions

2008-12-20 Thread Brandon S. Allbery KF8NH

On 2008 Dec 20, at 20:20, Brian Hurt wrote:

class Fooable a where
   toFoo :: a - Foo
or I can simply have all the functions which need a toFoo take an  
extra
agrument.  Performance really isn't that important here, so it's  
really

a matter of style- which approach would people prefer in this case?



A third possibility is to use the simple Reader monad ((-) r).

--
brandon s. allbery [solaris,freebsd,perl,pugs,haskell] allb...@kf8nh.com
system administrator [openafs,heimdal,too many hats] allb...@ece.cmu.edu
electrical and computer engineering, carnegie mellon universityKF8NH


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


Re: [Haskell-cafe] Type classes vr.s functions

2008-12-20 Thread Luke Palmer
On Sat, Dec 20, 2008 at 6:20 PM, Brian Hurt bh...@spnz.org wrote:


 So, style question for people, if I can.  I have a certain problem-
 basically, I have a bunch of functions which need a special function,
 of type a - Foo say.  And a bunch of other functions which can define
 that function on some type of interest, and then what to call the first
 batch of functions.  I can do this either by defining a type class,
 something like:
 class Fooable a where
toFoo :: a - Foo
 or I can simply have all the functions which need a toFoo take an extra
 agrument.  Performance really isn't that important here, so it's really
 a matter of style- which approach would people prefer in this case?


And it doesn't matter as the performance would be the same in the two cases
also.

My general rule of thumb is to always write combinators first, since they do
not suffer the composability limitations that typeclasses do (rougly
typeclasses perform a proof search which is subject to restrictions to
ensure decidability, whereas with combinators you provide the proof, so
there are no such restrictions).  Then typeclass instances can be trivially
defined in terms of the combinators.  Note that the other way around is not
usually possible.  So eg.:

  module Foo where

  type Fooify a = a - Foo
  int :: Fooify Int
  int = ...
  list :: Fooify a - Fooify [a]
  list = ...

  -- then, if determined that this would be convenient
  class Fooable a where
  toFoo :: Fooify a

  instance Fooable Int where toFoo = int
  instance (Fooable a) = Fooable [a] where toFoo = list toFoo
  ...

Luke



 Brian

 ___
 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] Type classes question

2008-10-07 Thread Ryan Ingram
On Tue, Oct 7, 2008 at 1:13 PM, Roly Perera
[EMAIL PROTECTED] wrote:
 Hi,

 I'm reasonably well versed in Haskell but fairly new to defining type classes.
 In particular I don't really understand how to arrange for all instances of X
 to also be instances of Y.

 It's quite possibly that my question is ill-posed, so I'll make it as concrete
 as possible: in the following code, I define a Stream class, with two
 instances, Stream1 and Stream2.  How do I arrange for there to be one
 implementation of Functor's fmap for all Stream instances?  I currently rely 
 on
 delegation, but in the general case this isn't nice.

With your current implementation, you can't.  You get lucky because
all of your instance declarations are of the form
 instance Stream (X a) a
for some type X.

But it's just as possible to say

 newtype Stream3 = S3 [Int]

 instance Stream Stream3 Int where
   first (S3 xs) = head xs
   next (S3 xs) = tail xs
   fby x (S3 xs) = S3 (x:xs)

Now the only valid fmap_ is over functions of type (Int - Int).

If you really want all your instances to be type constructors, you
should just say so:

 class Stream f where
first :: f a - a
next :: f a - f a
fby :: a - f a - f a

Now, with this implementation what you want is at least somewhat
possible, but there's a new problem: there's no good way in haskell to
define superclasses or default methods for existing classes.  There is
a standing class aliases proposal [1], but nobody has implemented
it.

The current recommended practice is to define a default and leave it
to your instances to use it.  It's kind of ugly, but thems the breaks:

 class Functor f = Stream f where -- you said you want all streams to be 
 functors, so enforce it!
first :: f a - a
next :: f a - f a
fby :: a - f a - f a

 fmapStreamDefault f = uncurry fby . both (f . first) (fmap_ f . next)

 instance Functor Stream1 where fmap = fmapStreamDefault
 instance Stream Stream1 where
first (x : _) = x
next (_ : xs) = xs
fby = (:)

Here's another possible solution:

 newtype AsFunctor s a = AF { fstream :: (s a) }
 instance (Stream f) = Functor (AsFunctor f) where
 fmap f (AF s) = AF (fmapStreamDefault f s)

Now to use fmap you wrap in AF and unwrap with fstream.

None of the existing solutions are really satisfactory, unfortunately.

   -- ryan

[1] http://repetae.net/recent/out/classalias.html
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Type classes question

2008-10-07 Thread Roly Perera
Hi,

I'm reasonably well versed in Haskell but fairly new to defining type classes.  
In particular I don't really understand how to arrange for all instances of X 
to also be instances of Y.  

It's quite possibly that my question is ill-posed, so I'll make it as concrete 
as possible: in the following code, I define a Stream class, with two 
instances, Stream1 and Stream2.  How do I arrange for there to be one 
implementation of Functor's fmap for all Stream instances?  I currently rely on 
delegation, but in the general case this isn't nice.

I guess I'm either misunderstanding what it is I'm trying to achieve, or how to 
do this kind of thing in Haskell.  Any help would be greatly appreciated.

many thanks,
Roly Perera



{-# LANGUAGE MultiParamTypeClasses, FlexibleInstances, 
ExistentialQuantification, FunctionalDependencies #-}

module Test where

---
-- Just some helpers.
---

-- Product map.
prod :: (a - b) - (c - d) - (a, c) - (b, d)
f `prod` g = \(a, c) - (f a, g c)

-- Diagonal.
diag :: a - (a, a)
diag x = (x, x)

-- Mediating morphism into the product.
both :: (a - b) - (a - c) - a - (b, c)
both f g = prod f g . diag

---
-- Abstract stream.
---
class Stream s a | s - a where
first :: s - a
next :: s - s
fby :: a - s - s

-- I want every Stream to be a Functor.
fmap_ :: Stream s' b = (a - b) - s - s'
fmap_ f = uncurry fby . both (f . first) (fmap_ f . next)

---
-- Implementation 1.
---
data Stream1 a = a : Stream1 a

instance Functor Stream1 where
fmap = fmap_

instance Stream (Stream1 a) a where
first (x : _) = x
next (_ : xs) = xs
fby = (:)

---
-- Implementation 2.
---
data Stream2 a = forall b . S b (b - a) (b - b)

instance Functor Stream2 where
fmap = fmap_

instance Stream (Stream2 a) a where
first (S x c _) = c x
next (S x c i) = S (i x) c i
fby y s = S (y, s) fst (uncurry (,) . both first next . snd)




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


Re: [Haskell-cafe] Type classes question

2008-10-07 Thread Bulat Ziganshin
Hello Roly,

Tuesday, October 7, 2008, 4:13:25 PM, you wrote:

 I'm reasonably well versed in Haskell but fairly new to defining type classes.

http://haskell.org/haskellwiki/OOP_vs_type_classes may be useful

-- 
Best regards,
 Bulatmailto:[EMAIL PROTECTED]

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


Re: [Haskell-cafe] type classes

2008-07-03 Thread Cotton Seed
Hi Henning,

The numeric prelude was inspiration for a lot of my design.  Part of
the reason I didn't use it was because one of my goals is to learn
Haskell better, and I wanted to grapple with these design decisions
myself.

I decided, like IsZeroTestable in the numeric prelude, to make
zero/one separate type classes.  Thus, I have

class AbelianGroup a where
  (+) :: a - a - a
  negate :: a - a

class HasZero a where
  zero :: a

so ZModN is an instance of AbelianGroup but not HasZero.  Most
functions that want a zero have two forms, for example,

sum :: (HasZero a, AbelianGroup a) = [a] - a
sumWithZero :: (AbelianGroup a) = a - [a] - a

although I may eventually require all types to have a corresponding Ty
class and change this to

sumWithTy :: (AbelianGroup a) = AblieanGroupTy a - [a] - a

Matrices are another example that fits this model.  Numeric prelude
defines zero/one to be 1x1 matrices, but asserts dimensions match in
various operations, so they don't actually seem usable.

Cotton

On Thu, Jul 3, 2008 at 1:22 AM, Henning Thielemann
[EMAIL PROTECTED] wrote:

 On Wed, 2 Jul 2008, Cotton Seed wrote:

 Hi everyone,

 I'm working on a computational algebra program and I've run into a
 problem.
 In my program, I have types for instances of algebraic objects, e.g. ZModN
 for modular integers, and types for the objects themselves, e.g. ZModNTy
 for
 the ring of modular integers.

 Maybe you are also interested in:
  http://darcs.haskell.org/numericprelude/src/Number/ResidueClass.hs
  http://darcs.haskell.org/numericprelude/src/Number/ResidueClass/


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


[Haskell-cafe] type classes

2008-07-02 Thread Cotton Seed
Hi everyone,

I'm working on a computational algebra program and I've run into a problem.
In my program, I have types for instances of algebraic objects, e.g. ZModN
for modular integers, and types for the objects themselves, e.g. ZModNTy for
the ring of modular integers.

Now, I want to subclass ZModNTy from something like

class RingTy a b where
  order :: a - Integer
  units :: a - [b]

where `a' represents algebraic object, and `b' the type of instances of that
object.  I want an instance

instance RingTy ZModNTy ZModN where ...

but then code that only uses order fails with errors like

No instance for (RingTy ZModNTy b)
  arising from a use of `order' at Test2.hs:16:8-15

since there is no constraint on the second type variable.

I think what I really want is

class RingTy a where
  order :: a b - Integer
  units :: a b - [b]

but this doesn't work either since ZModNTy is not parametric in its type
like, say, `Polynomial a' is.

Is this a common problem?  Is there a standard way to handle it?

Thank you for your attention,

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


Re: [Haskell-cafe] type classes

2008-07-02 Thread Dan Doel
On Wednesday 02 July 2008, Cotton Seed wrote:
 Hi everyone,

 I'm working on a computational algebra program and I've run into a problem.
 In my program, I have types for instances of algebraic objects, e.g. ZModN
 for modular integers, and types for the objects themselves, e.g. ZModNTy
 for the ring of modular integers.

 Now, I want to subclass ZModNTy from something like

 class RingTy a b where
   order :: a - Integer
   units :: a - [b]

 where `a' represents algebraic object, and `b' the type of instances of
 that object.  I want an instance

 instance RingTy ZModNTy ZModN where ...

 but then code that only uses order fails with errors like

 No instance for (RingTy ZModNTy b)
   arising from a use of `order' at Test2.hs:16:8-15

 since there is no constraint on the second type variable.

 I think what I really want is

 class RingTy a where
   order :: a b - Integer
   units :: a b - [b]

 but this doesn't work either since ZModNTy is not parametric in its type
 like, say, `Polynomial a' is.

 Is this a common problem?  Is there a standard way to handle it?

Correct me if I'm wrong, but wouldn't the a uniquely determine the b? In that 
case, you'd probably want a functional dependency:

  class RingTy a b | a - b where
order :: a - Integer
units :: a - [b]

This solves the problem with order, because with multi-parameter type classes, 
all the variables should be determined for a use of a method. Since b is not 
involved with order, it could be anything, so it's rather ambiguous. The 
functional dependency solves this by uniquely determined b from a, so order 
is no longer ambiguous.

Alternately, with the new type families, this can become:

  class RingTy a where
type RingElem a :: *
order :: a - Integer
units :: a - [RingElem a]

Or something along those lines.

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


Re: [Haskell-cafe] type classes

2008-07-02 Thread Cotton Seed
Hi Dan,

Thanks!  This is exactly what I was looking for.

Cotton

On Wed, Jul 2, 2008 at 9:57 PM, Dan Doel [EMAIL PROTECTED] wrote:

 On Wednesday 02 July 2008, Cotton Seed wrote:
  Hi everyone,
 
  I'm working on a computational algebra program and I've run into a problem.
  In my program, I have types for instances of algebraic objects, e.g. ZModN
  for modular integers, and types for the objects themselves, e.g. ZModNTy
  for the ring of modular integers.
 
  Now, I want to subclass ZModNTy from something like
 
  class RingTy a b where
order :: a - Integer
units :: a - [b]
 
  where `a' represents algebraic object, and `b' the type of instances of
  that object.  I want an instance
 
  instance RingTy ZModNTy ZModN where ...
 
  but then code that only uses order fails with errors like
 
  No instance for (RingTy ZModNTy b)
arising from a use of `order' at Test2.hs:16:8-15
 
  since there is no constraint on the second type variable.
 
  I think what I really want is
 
  class RingTy a where
order :: a b - Integer
units :: a b - [b]
 
  but this doesn't work either since ZModNTy is not parametric in its type
  like, say, `Polynomial a' is.
 
  Is this a common problem?  Is there a standard way to handle it?

 Correct me if I'm wrong, but wouldn't the a uniquely determine the b? In that
 case, you'd probably want a functional dependency:

  class RingTy a b | a - b where
order :: a - Integer
units :: a - [b]

 This solves the problem with order, because with multi-parameter type classes,
 all the variables should be determined for a use of a method. Since b is not
 involved with order, it could be anything, so it's rather ambiguous. The
 functional dependency solves this by uniquely determined b from a, so order
 is no longer ambiguous.

 Alternately, with the new type families, this can become:

  class RingTy a where
type RingElem a :: *
order :: a - Integer
units :: a - [RingElem a]

 Or something along those lines.

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


Re: [Haskell-cafe] type classes

2008-07-02 Thread Henning Thielemann


On Wed, 2 Jul 2008, Cotton Seed wrote:


Hi everyone,

I'm working on a computational algebra program and I've run into a problem.
In my program, I have types for instances of algebraic objects, e.g. ZModN
for modular integers, and types for the objects themselves, e.g. ZModNTy for
the ring of modular integers.


Maybe you are also interested in:
  http://darcs.haskell.org/numericprelude/src/Number/ResidueClass.hs
  http://darcs.haskell.org/numericprelude/src/Number/ResidueClass/

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


[Haskell-cafe] type classes

2007-12-14 Thread Peter Padawitz
I'd like to define several instances of the same type class with the 
same type variable instance. Only method instances differ. How can I do 
this without writing copies of the type class?


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


Re: [Haskell-cafe] type classes

2007-12-14 Thread Jules Bean

Peter Padawitz wrote:
I'd like to define several instances of the same type class with the 
same type variable instance. Only method instances differ. How can I do 
this without writing copies of the type class?


newtypes and modules have both been suggested.

I have another suggestion:

Don't!

Don't use typeclasses.

The only useful thing about typeclasses is that they are a kind of 
type-indexed family of dictionaries. If you don't want to use the type 
indexin, then don't use classes. Just use your own kind of dictionary.


E.g., instead of:


class Foo a where { bar :: a - Int; baz :: a - String }

instance Foo Double ...
instance Foo Double ... -- bother, I wanted a different Double instance!


you should just have:

data Foo a = Foo { bar :: a - Int, baz :: a - String }

foo1 :: Foo Double
foo1 = Foo { ... }

foo2 :: Foo Double
foo2 = Foo { ... }

-- now I can have as many 'instances' for the same type as I want!

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


Re: [Haskell-cafe] type classes

2007-12-14 Thread Ketil Malde
Lutz Donnerhacke [EMAIL PROTECTED] writes:

 * Peter Padawitz wrote:
 I'd like to define several instances of the same type class with the
 same type variable instance. Only method instances differ. How can I do
 this without writing copies of the type class?

 Define the type class in a module named MyClass. Define the each instance
 in a module named MyInstanceX where X is a version number.

 Include only the MyInstanceX module, you currently need.

Or, if you need more than one at the same time, wrap your data type in
one newtype per instance.

-k
-- 
If I haven't seen further, it is by standing in the footprints of giants
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] type classes

2007-12-14 Thread Lutz Donnerhacke
* Peter Padawitz wrote:
 I'd like to define several instances of the same type class with the
 same type variable instance. Only method instances differ. How can I do
 this without writing copies of the type class?

Define the type class in a module named MyClass. Define the each instance
in a module named MyInstanceX where X is a version number.

Include only the MyInstanceX module, you currently need.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Type classes: Missing language feature?

2007-08-07 Thread DavidA
Hi, there's something I'm trying to do with type classes that seems to fit very 
naturally with my mental model of type classes, but doesn't seem to be 
supported by the language. I'm wondering whether I'm missing something, or 
whether there's some language extension that could help me or alternative way 
of achieving what I'm trying to achieve.

I'm trying to define multivariate polynomials, which are sums of monomials - 
for example x^2y + z^4. In algorithms on multivariate polynomials, one 
typically wants to support different monomial orders. For example, the lex 
order is dictionary order - xxy  xy  y  yyy - whereas the graded lex (glex) 
order also takes into account the degree of the monomials - y  xy  xxy  yyy.

Here's some code (based on http://sigfpe.blogspot.com/2007/07/ill-have-
buchburger-with-fries.html):

import Data.Map as M
import Data.List as L

newtype Monomial = Monomial (Map String Int) deriving (Eq)
x = Monomial $ singleton x 1
y = Monomial $ singleton y 1
instance Show Monomial where
show (Monomial a) = concatMap (\(v,i)- v ++ ^ ++ show i) $ toList a -- 
simplified for brevity
instance Num Monomial where
Monomial a * Monomial b = Monomial $ unionWith (+) a b

newtype Lex = Lex Monomial deriving (Eq)
newtype Glex = Glex Monomial deriving (Eq)

instance Ord Lex where
Lex (Monomial m) = Lex (Monomial m') = toList m = toList m'

instance Ord Glex where
Glex (Monomial m) = Glex (Monomial m') = (sum $ elems m, toList m) = (sum 
$ elems m', toList m')

Now, what I'd like to do is have Lex and Glex, and any further monomial 
orderings I define later, automatically derive Show and Num instances from 
Monomial (because it seems like boilerplate to have to define Show and Num 
instances by hand). Something like the following (not valid Haskell):

class OrdMonomial m where
fromRaw :: Monomial - m
toRaw :: m - Monomial

instance OrdMonomial Lex where
fromRaw m = Lex m
toRaw (Lex m) = m

instance OrdMonomial Glex where
fromRaw m = Glex m
toRaw (Glex m) = m

derive OrdMonomial m = Show m where
show m = show (toRaw m)

derive OrdMonomial m = Num m where
m * m' = fromRaw (toRaw m * toRaw m')

Is there a way to do what I'm trying to do? (Preferably without resorting to 
template Haskell, etc) - It seems like a natural thing to want to do.

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


Re: [Haskell-cafe] Type classes: Missing language feature?

2007-08-07 Thread Derek Elkins
On Tue, 2007-08-07 at 12:58 +, DavidA wrote:
 Hi, there's something I'm trying to do with type classes that seems to fit 
 very 
 naturally with my mental model of type classes, but doesn't seem to be 
 supported by the language. I'm wondering whether I'm missing something, or 
 whether there's some language extension that could help me or alternative way 
 of achieving what I'm trying to achieve.
 
 I'm trying to define multivariate polynomials, which are sums of monomials - 
 for example x^2y + z^4. In algorithms on multivariate polynomials, one 
 typically wants to support different monomial orders. For example, the lex 
 order is dictionary order - xxy  xy  y  yyy - whereas the graded lex 
 (glex) 
 order also takes into account the degree of the monomials - y  xy  xxy  
 yyy.
 
 Here's some code (based on http://sigfpe.blogspot.com/2007/07/ill-have-
 buchburger-with-fries.html):
 
 import Data.Map as M
 import Data.List as L
 
 newtype Monomial = Monomial (Map String Int) deriving (Eq)
 x = Monomial $ singleton x 1
 y = Monomial $ singleton y 1
 instance Show Monomial where
 show (Monomial a) = concatMap (\(v,i)- v ++ ^ ++ show i) $ toList a -- 
 simplified for brevity
 instance Num Monomial where
 Monomial a * Monomial b = Monomial $ unionWith (+) a b
 
 newtype Lex = Lex Monomial deriving (Eq)
 newtype Glex = Glex Monomial deriving (Eq)
 
 instance Ord Lex where
 Lex (Monomial m) = Lex (Monomial m') = toList m = toList m'
 
 instance Ord Glex where
 Glex (Monomial m) = Glex (Monomial m') = (sum $ elems m, toList m) = 
 (sum 
 $ elems m', toList m')
 
 Now, what I'd like to do is have Lex and Glex, and any further monomial 
 orderings I define later, automatically derive Show and Num instances from 
 Monomial (because it seems like boilerplate to have to define Show and Num 
 instances by hand). Something like the following (not valid Haskell):
 
 class OrdMonomial m where
 fromRaw :: Monomial - m
 toRaw :: m - Monomial
 
 instance OrdMonomial Lex where
 fromRaw m = Lex m
 toRaw (Lex m) = m
 
 instance OrdMonomial Glex where
 fromRaw m = Glex m
 toRaw (Glex m) = m
 
 derive OrdMonomial m = Show m where
 show m = show (toRaw m)
 
 derive OrdMonomial m = Num m where
 m * m' = fromRaw (toRaw m * toRaw m')
 
 Is there a way to do what I'm trying to do? (Preferably without resorting to 
 template Haskell, etc) - It seems like a natural thing to want to do.

I don't think there is a way to do exactly what you want.  However,
there's an alternative approach that you may want to look at.  Right now
you are using a technique called Wrapper types.  An alternative would be
to use phantom types and have the ordering be specified by the type
parameter.  So something like the following,

newtype Monomial ord = Monomial (Map String Int) deriving (Eq)

instance Show (Monomial ord) where
show (Monomial a) = concatMap (\(v,i)- v ++ ^ ++ show i) $ toList a

instance Num (Monomial ord) where
Monomial a * Monomial b = Monomial $ unionWith (+) a b

data Lex -- this uses a minor extension which is not necessary
data GLex

instance Ord (Monomial Lex) where
Monomial m = Monomial m' = toList m = toList m'

instance Ord (Monomial GLex) where
Monomial m = Monomial m' 
   = (sum $ elems m, toList m) = (sum $ elems m', toList m')

You can add a trivial conversion function
convertOrdering :: Monomial a - Monomial b
convertOrdering (Monomial x) = Monomial x

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


Re: [Haskell-cafe] Type classes: Missing language feature?

2007-08-07 Thread Tillmann Rendel

DavidA wrote:
Now, what I'd like to do is have Lex and Glex, and any further monomial 
orderings I define later, automatically derive Show and Num instances from 
Monomial (because it seems like boilerplate to have to define Show and Num 
instances by hand). Something like the following (not valid Haskell):


class OrdMonomial m where
fromRaw :: Monomial - m
toRaw :: m - Monomial

instance OrdMonomial Lex where
fromRaw m = Lex m
toRaw (Lex m) = m

instance OrdMonomial Glex where
fromRaw m = Glex m
toRaw (Glex m) = m

derive OrdMonomial m = Show m where
show m = show (toRaw m)

derive OrdMonomial m = Num m where
m * m' = fromRaw (toRaw m * toRaw m')


Change derive to instance and enable some GHC extensions by passing

  -fglasgow-exts
  -fallow-overlapping-instances
  -fallow-undecidable-instances

to it (or use a GHC_OPTIONS pragma at the top of your source file) to 
make your code work with GHC. To go a step further, using functional 
dependencies, you can write a small framework:


  -- the class of wrapper types
  class Wrapper w a | w - a where
wrap :: a - w
unwrap :: w - a

  -- the class of types with derived show instances
  class Wrapper w = DeriveShow w

  -- actual deriving of show instances
  instance (Wrapper w a, Show a, DeriveShow w) = Show w where
show = show . unwrap

and use it for your situation:

  -- the inner type to be wrapped and it's instances
  newtype Monomial = Monomial (Map String Int) deriving (Eq)

  instance Show Monomial where
show (Monomial a) = ...

  -- some wrappers around this inner type
  newtype Lex = Lex Monomial deriving (Eq)
  newtype Glex = Glex Monomial deriving (Eq)

  instance Wrapper Lex Monomial where
wrap x = Lex x
unwrap (Lex x) = x

  instance Wrapper Glex Monomial where
wrap x = Glex x
unwrap (Glex x) = x

  -- specialised instances for the wrappers
  instance Ord Lex where
Lex (Monomial m) = Lex (Monomial m') = ...

  instance Ord Glex where
Glex (Monomial m) = Glex (Monomial m') = ...

  -- derived instances for the wrappers
  instance DeriveShow Lex
  instance DeriveShow Glex

But given newtype deriving, wich should work for you for everything 
except Show and Read, this may well be overkill.


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


[Haskell-cafe] Type classes and type equality

2007-04-16 Thread Neil Mitchell

Hi,

I'm looking for a type class which checks whether two types are the
same or not. My first guess is:

class Same a b where
  same :: a - b - Bool

instance Same a a where
  same _ _ = True

instance Same a b where
  same _ _ = False

In Hugs this seems to work with overlapping instances (not requiring
unsafe overlapping instances).

GHC requires {-# LANGUAGE MultiParamTypeClasses, IncoherentInstances #-}

So my question is if this is safe? Will the compiler always pick the
right one? Is there a better way to do this?

The alternative I thought of is using Typeable, but this is not
supported particularly well on Hugs (no deriving Typeable) and would
require modifications to the existing data structures (additional
derivings) so is not such a good choice.

Thanks

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


Re: [Haskell-cafe] Type classes and type equality

2007-04-16 Thread Jeremy Shaw
At Mon, 16 Apr 2007 13:44:13 +0100,
Neil Mitchell wrote:
 
 Hi,

 So my question is if this is safe? Will the compiler always pick the
 right one? Is there a better way to do this?

I noticed that the results can be a bit suprising sometimes. See if
you can predict the answers to these (in ghci):

 same 1 1

 let x = (undefined :: a) in same x x

 f :: a - Bool
 f a = same a a

 f (undefined :: a)

Here is what ghci says:

*Main same 1 1
False

*Main :t 1
1 :: forall t. (Num t) = t

*Main let x = (undefined :: a) in same x x
False

 f :: a - Bool
 f a = same a a

*Main f (undefined :: a)
True

I'm not saying anything is wrong here. Just be careful how you use it
:)

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


Re: [Haskell-cafe] Type classes and type equality

2007-04-16 Thread Clifford Beshers

Jeremy Shaw wrote:


I noticed that the results can be a bit suprising sometimes. See if
you can predict the answers to these (in ghci):
  


Interesting examples.  Here's another one that I would find problematic:

   *SameType same Nothing (Just xyzzy)
   False
   *SameType same (Nothing :: Maybe String) (Just xyzzy)
   True

And of course, the case with the integers lifts right up:

   *SameType same (Just 1) (Just 1)
   False


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


[Haskell-cafe] Type classes to 'reflect' constructor structure

2007-04-05 Thread Jules Bean
In the thread 'automatic derivation', Joel Reymont is looking for 
metaprogramming functionality with which he wants to automatically 
derive a parser and a pretty printer for his ADT (which is an AST for a 
minilanguage).


I replied showing that a significant amount of the boilerplate could be 
removed anyway just using haskell's built in ability to process parsers 
as 'data'. I could completely automate the nullary constructions, but I 
needed type information for n-ary ones.


A bit of poking around with typeclasses showed a proof-of-concept for 
getting the type-checker to extract that information for us:


{-# OPTIONS -fglasgow-exts #-}
import Data.Typeable


-- Stage 1 is just counting the arguments

class CountArgs s where numArgs :: s - Integer

data TestType = Nullary | Unary Int | Binary Int String
 | OtherBinary String Int

instance CountArgs TestType where numArgs x = 0
instance CountArgs (a-TestType) where numArgs x = 1
instance CountArgs (a-b-TestType) where numArgs x = 2

-- *Main numArgs Nullary
-- 0
-- *Main numArgs Unary
-- 1
-- *Main numArgs Binary
-- 2

-- Stage 2 actually lists the types of the arguments
-- I'll use a seperate ADT to make the types concrete

data ArgTypes = JInt | JStr deriving (Show)

class ConcreteType t where makeAT :: t - ArgTypes

instance ConcreteType Int where makeAT _ = JInt
instance ConcreteType String where makeAT _ = JStr

class DescribeArgs s where descArgs :: s - [ArgTypes]

instance DescribeArgs TestType  where descArgs _ = []
instance ConcreteType a = DescribeArgs (a-TestType)
where descArgs _ = [makeAT (undefined::a)]
instance (ConcreteType a, ConcreteType b) =
   DescribeArgs (a-b-TestType)
where descArgs _ = [makeAT (undefined::a), makeAT (undefined::b)]

-- *Main descArgs Nullary
-- []
-- *Main descArgs Unary
-- [JInt]
-- *Main descArgs Binary
-- [JInt,JStr]
-- *Main descArgs OtherBinary
-- [JStr,JInt]

-- Stage 3 is just the Data.Typeable version of the stage 2

class DescribeArgs2 s where descArgs2 :: s - [TypeRep]

instance DescribeArgs2 TestType  where descArgs2 _ = []
instance Typeable a = DescribeArgs2 (a-TestType)
where descArgs2 _ = [typeOf (undefined::a)]
instance (Typeable a, Typeable b) =
   DescribeArgs2 (a-b-TestType)
where descArgs2 _ = [typeOf (undefined::a), typeOf (undefined::b)]

-- *Main descArgs2 Nullary
-- []
-- *Main descArgs2 Unary
-- [Int]
-- *Main descArgs2 Binary
-- [Int,[Char]]
-- *Main descArgs2 OtherBinary
-- [[Char],Int]


There are still some things this approach fails on: it can't give you a 
complete list of all constructors of TestType, for example. (Such a list 
would necessarily an existential type, like [exists x . DescribeArgs x 
- x]).


I'm sure my thoughts aren't original. Have other people taken this 
further into interesting directions? Where is the line beyond which you 
need 'true' metaprogramming?


Jules

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


[Haskell-cafe] Type classes

2006-03-20 Thread Max Vasin

Hi!

I'm currently experimenting with a bibliography generation tool for
LaTeX. It will (if it will be finished) use BibTeX databases but
bibliography styles will be written in Haskell. I want styles to be
able to transform database entries into some style specific data type,
so I define 

 class DatabaseEntry e where
   entryLabel :: e - String
   formatEntry:: e - String
   compareEntries :: e - e - Ordering

Then I define

 data Entry = forall a. (DatabaseEntry a) = Entry a

 instance DatabaseEntry Entry where
 entryLabel (Entry e) = entryLabel e
 formatEntry (Entry e) = formatEntry e

How can I define compareEntries for this instance?

-- 
WBR,
Max Vasin.

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


Re: [Haskell-cafe] Type classes

2006-03-20 Thread Stefan Holdermans

Max,


class DatabaseEntry e where
  entryLabel :: e - String
  formatEntry:: e - String
  compareEntries :: e - e - Ordering


Then I define


data Entry = forall a. (DatabaseEntry a) = Entry a



instance DatabaseEntry Entry where
entryLabel (Entry e) = entryLabel e
formatEntry (Entry e) = formatEntry e


How can I define compareEntries for this instance?


In general: you can't. The field of the Entry constructor has a  
existentially quantified typed. Given two arbitrary values of type  
Entry, this type may be instantiated with a different type for each  
value, so you cannot easily compare the fields.


If you extend the DatabaseEntry class such that it supplies a method  
that allows to produce some canonical representation for database  
entries suited for comparison, then you could take that road.


Are you sure that your Entry type needs to be existentially quantified?

HTH,

  Stefan

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


RE: [Haskell-cafe] Type classes

2006-03-20 Thread Geest, G. van den
Title: RE: [Haskell-cafe] Type classes







I suppose you want to define compareEntries like this:
 compareEntries (Entry x) (Entry y) = compareEntries x y

An option is to just implement it the following way (Haskell98!):

 class DatabaseEntry e where
 entryLabel :: e - String
 formatEntry :: e - String
 compareEntries :: e - e - Ordering

 data Entry a = Entry a

 instance DatabaseEntry a = DatabaseEntry (Entry a) where
 entryLabel (Entry e) = entryLabel e
 formatEntry (Entry e) = formatEntry e
 compareEntries (Entry x) (Entry y) = compareEntries x y



Gerrit


-Original Message-
From: [EMAIL PROTECTED] on behalf of Max Vasin
Sent: Mon 3/20/2006 3:46 PM
To: haskell-cafe@haskell.org
Subject: [Haskell-cafe] Type classes


Hi!

I'm currently experimenting with a bibliography generation tool for
LaTeX. It will (if it will be finished) use BibTeX databases but
bibliography styles will be written in Haskell. I want styles to be
able to transform database entries into some style specific data type,
so I define

 class DatabaseEntry e where
 entryLabel :: e - String
 formatEntry :: e - String
 compareEntries :: e - e - Ordering

Then I define

 data Entry = forall a. (DatabaseEntry a) = Entry a

 instance DatabaseEntry Entry where
 entryLabel (Entry e) = entryLabel e
 formatEntry (Entry e) = formatEntry e

How can I define compareEntries for this instance?

--
WBR,
Max Vasin.

___
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] Type classes

2006-03-20 Thread Matthias Fischmann


see my discussion a few moments ago, in particular my posting

  http://www.haskell.org/pipermail/haskell-cafe/2006-March/014981.html

as you by now already know from this thread, the link tells you that
the only possible solution is to turn the two entries to be compared
into something of the same type, which can only be done with another
type class.  i am using 'Show' for now and compare the strings,
because it's really simple and i don't care about performance at this
stage of the project.  might bite me later, though.

cheers,
matthias



On Mon, Mar 20, 2006 at 05:46:43PM +0300, Max Vasin wrote:
 To: haskell-cafe@haskell.org
 From: Max Vasin [EMAIL PROTECTED]
 Date: Mon, 20 Mar 2006 17:46:43 +0300
 Subject: [Haskell-cafe] Type classes
 
 
 Hi!
 
 I'm currently experimenting with a bibliography generation tool for
 LaTeX. It will (if it will be finished) use BibTeX databases but
 bibliography styles will be written in Haskell. I want styles to be
 able to transform database entries into some style specific data type,
 so I define 
 
  class DatabaseEntry e where
entryLabel :: e - String
formatEntry:: e - String
compareEntries :: e - e - Ordering
 
 Then I define
 
  data Entry = forall a. (DatabaseEntry a) = Entry a
 
  instance DatabaseEntry Entry where
  entryLabel (Entry e) = entryLabel e
  formatEntry (Entry e) = formatEntry e
 
 How can I define compareEntries for this instance?
 
 -- 
 WBR,
 Max Vasin.
 
 ___
 Haskell-Cafe mailing list
 Haskell-Cafe@haskell.org
 http://www.haskell.org/mailman/listinfo/haskell-cafe

-- 
Institute of Information Systems, Humboldt-Universitaet zu Berlin

web:  http://www.wiwi.hu-berlin.de/~fis/
e-mail:   [EMAIL PROTECTED]
tel:  +49 30 2093-5742
fax:  +49 30 2093-5741
office:   Spandauer Strasse 1, R.324, 10178 Berlin, Germany
pgp:  AD67 CF64 7BB4 3B9A 6F25  0996 4D73 F1FD 8D32 9BAA
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Type classes and hFoldr from HList

2005-11-07 Thread Greg Buchholz
Ralf Lammel wrote:
 
 What you can do is define a dedicated *type code* for composition.
 
 comp  = hFoldr (undefined::Comp) (id::Int - Int) test
 
 data Comp
 
 instance Apply Comp (x - y,y - z) (x - z)
  where
   apply _ (f,g) = g . f

That does it!


Thanks,

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


[Haskell-cafe] Type classes and hFoldr from HList

2005-11-06 Thread Greg Buchholz

  I was playing around with the HList library from the paper...

Strongly typed heterogeneous collections
http://homepages.cwi.nl/~ralf/HList/

...and I thought I'd try to fold the composition function (.) through a
heterogeneous list of functions, using hFoldr...

{-# OPTIONS -fglasgow-exts #-}
{-# OPTIONS -fallow-undecidable-instances #-}

import CommonMain

main = print $ comp abc

test = HCons ((+1)::(Int-Int)) (HCons ((*2)::(Int-Int)) (HCons length HNil))

comp = hFoldr (.) id test

instance Apply (a - b - c - d) (a, b) (c - d)  
where
apply f (a,b) = f a b

...but it fails with the following type error...

]Compiling Main ( compose.hs, interpreted )
]
]compose.hs:10:7:
]No instances for (Apply ((b - c) - (a - b) - a - c)
](Int - Int, r)
]([Char] - a3),
]  Apply ((b - c) - (a - b) - a - c) (Int - Int, r1) 
r,
]  Apply ((b - c) - (a - b) - a - c) ([a2] - Int, a1 
-a1) r1)
]  arising from use of `hFoldr' at compose.hs:10:7-12
]Probable fix:
]  add an instance declaration for (Apply ((b - c) - (a - b) - a - c)
] (Int - Int, r)
] ([Char] - a3),
]   Apply ((b - c) - (a - b) - a - c)
](Int - Int, r1) r,
]   Apply ((b - c) - (a - b) - a - c)
]([a2] - Int, a1 - a1) r1)
]In the definition of `comp': comp = hFoldr (.) id test

...Anyway, I couldn't quite tell whether I was using hFoldr incorrectly,
or if I needed to have more constraints placed on the construction of
test, or if needed some sort of type-level function that resolves...

Apply ((b - c) - (a - b) - a - c)

...into (a - c), or something else altogether.  I figured someone might
be able to help point me in the right direction.


Thanks,

Greg Buchholz

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


RE: [Haskell-cafe] Type classes and hFoldr from HList

2005-11-06 Thread Ralf Lammel
Hi Greg,

Since hfoldr is right-associative, I prefer to reorder your list of
functions as follows:

 test = HCons (length::String - Int) (HCons ((+1)::(Int-Int)) (HCons
((*2)::(Int-Int)) HNil))

Note that I also annotated length with its specific type.
(If you really wanted to leave things more polymorphic, you would need
to engage in TypeCast.)

Providing a specific Apply instance for (.) is not necessary, strictly
necessary. We could try to exploit the normal function instance for
Apply.

Let me recall that one here for convenience:

instance Apply (x - y) x y
 where
  apply f x = f x

Let me also recall the hFoldr instances:

class HList l = HFoldr f v l r | f v l - r
 where
  hFoldr :: f - v - l - r

instance HFoldr f v HNil v
 where
  hFoldr _ v _ = v

instance ( HFoldr f v l r
 , Apply f (e,r) r'
 )
  = HFoldr f v (HCons e l) r'
 where
  hFoldr f v (HCons e l) = apply f (e,hFoldr f v l)


To fit in (.), we would flip and uncurry it.
So we could try:

comp' = hFoldr (uncurry (flip (.))) (id::Int - Int) test

This wouldn't work.
The trouble is the required polymorphism of the first argument of
hFoldr.
The type of that argument as such is polymorphic.
However, this polymorphism does not survive type class parameterization.
You see this by looking at the HCons instance of HFoldr.
The different occurrences of f would need to be used at different
types.
This would only work if the type class parameter f were instantiated by
the polymorphic type of (uncurry (flip (.))). (And even then we may need
something like TypeCast.)

What you can do is define a dedicated *type code* for composition.

comp  = hFoldr (undefined::Comp) (id::Int - Int) test

data Comp

instance Apply Comp (x - y,y - z) (x - z)
 where
  apply _ (f,g) = g . f


Ralf


 -Original Message-
 From: [EMAIL PROTECTED] [mailto:haskell-cafe-
 [EMAIL PROTECTED] On Behalf Of Greg Buchholz
 Sent: Sunday, November 06, 2005 7:01 PM
 To: haskell-cafe@haskell.org
 Subject: [Haskell-cafe] Type classes and hFoldr from HList
 
 
   I was playing around with the HList library from the paper...
 
 Strongly typed heterogeneous collections
 http://homepages.cwi.nl/~ralf/HList/
 
 ...and I thought I'd try to fold the composition function (.) through
a
 heterogeneous list of functions, using hFoldr...
 
 {-# OPTIONS -fglasgow-exts #-}
 {-# OPTIONS -fallow-undecidable-instances #-}
 
 import CommonMain
 
 main = print $ comp abc
 
 test = HCons ((+1)::(Int-Int)) (HCons ((*2)::(Int-Int)) (HCons
length
 HNil))
 
 comp = hFoldr (.) id test
 
 instance Apply (a - b - c - d) (a, b) (c - d)
 where
 apply f (a,b) = f a b
 
 ...but it fails with the following type error...
 
 ]Compiling Main ( compose.hs, interpreted )
 ]
 ]compose.hs:10:7:
 ]No instances for (Apply ((b - c) - (a - b) - a - c)
 ](Int - Int, r)
 ]([Char] - a3),
 ]  Apply ((b - c) - (a - b) - a - c) (Int -
Int,
 r1) r,
 ]  Apply ((b - c) - (a - b) - a - c) ([a2] -
 Int, a1 -a1) r1)
 ]  arising from use of `hFoldr' at compose.hs:10:7-12
 ]Probable fix:
 ]  add an instance declaration for (Apply ((b - c) - (a - b) -
a -
  c)
 ] (Int - Int, r)
 ] ([Char] - a3),
 ]   Apply ((b - c) - (a - b) -
a -
  c)
 ](Int - Int, r1) r,
 ]   Apply ((b - c) - (a - b) -
a -
  c)
 ]([a2] - Int, a1 - a1) r1)
 ]In the definition of `comp': comp = hFoldr (.) id test
 
 ...Anyway, I couldn't quite tell whether I was using hFoldr
incorrectly,
 or if I needed to have more constraints placed on the construction of
 test, or if needed some sort of type-level function that resolves...
 
 Apply ((b - c) - (a - b) - a - c)
 
 ...into (a - c), or something else altogether.  I figured someone
might
 be able to help point me in the right direction.

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


Re: [Haskell-cafe] Type classes... popular for newbies, isn't it?

2004-08-09 Thread Stefan Holdermans
Arjun,
  AG This class definition is giving me a lot of problems
  AG with the successor function:
 class (Ord st) = MinimaxState st where
successors :: st - [(action, st)]
terminal   :: st - Bool
 instance MinimaxState Int where
terminal i   = i == 0
successors i = [(1,i+1), (-1,i-1)]
See, http://www.haskell.org//pipermail/haskell-cafe/2004-July/006424.html.
HTH,
Stefan
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Type classes... popular for newbies, isn't it?

2004-08-09 Thread Stefan Holdermans
Arjan,
AG I'm curious as to why my class declaration
AG compiles in GHC, as there doesn't seem to
AG be any way to use it.
 class (Ord st) = MinimaxState st where
   successors :: forall a . st - [(a, st)]
   terminal   :: st - True
Any implementation of the successors method needs to produce values of 
an arbitrarely type a. Hence, it can only produce the empty list or a 
list of pairs that all have bottom as their first component.

 instance MinimaxState Bool where
   successors = const []
   terminal   = not
 instance MinimaxState Int where
   successors n = [(undefined, pred n), (undefined, succ n)]
   terminal 0   = True
   terminal n   = False
HTH,
Stefan
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Type classes... popular for newbies, isn't it?

2004-08-07 Thread Stefan Holdermans
Arjun,
  AG This class definition is giving me a lot of problems
  AG with the successor function:
 class (Ord st) = MinimaxState st where
   successors :: st - [(action, st)]
   terminal   :: st - Bool
 instance MinimaxState Int where
   terminal i   = i == 0
   successors i = [(1,i+1), (-1,i-1)]
See, http://www.haskell.org//pipermail/haskell-cafe/2004-July/006424.html.
HTH,
Stefan
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Type classes... popular for newbies, isn't it?

2004-08-07 Thread Arjun Guha
I'd rather not do that, but even if I did, the type-variable action 
would not be reachable in the terminal function.  I could specify a 
functional dependency st - action (though I've never used it, it would 
be a fun to learn).  I'm curious as to why my class declaration 
compiles in GHC, as there doesn't seem to be any way to use it.

-Arjun
On Aug 7, 2004, at 01:06, [EMAIL PROTECTED] wrote:
Hi Arjun.
How about inserting one more parameter, action, in your class 
definition:

class (Ord st) = MinimaxState st action where
   successors:: st - [(action,st)]
   terminal:: st - Bool
instance MinimaxState Int Int where
   terminal i = i == 0
   successors i = [(1,i+1), (-1,i-1)]
Then don't forget to start the compiler/interpreter with 
-fglasgow-exts.

Hope this helps.
Regards,
Carlos

___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Type classes... popular for newbies, isn't it?

2004-08-07 Thread Stefan Holdermans
Arjan,
AG I'm curious as to why my class declaration
AG compiles in GHC, as there doesn't seem to
AG be any way to use it.
  class (Ord st) = MinimaxState st where
successors :: forall a . st - [(a, st)]
terminal   :: st - True
Any implementation of the successors method needs to produce values of
an arbitrarely type a. Hence, it can only produce the empty list or a
list of pairs that all have bottom as their first component.
  instance MinimaxState Bool where
successors = const []
terminal   = not
  instance MinimaxState Int where
successors n = [(undefined, pred n), (undefined, succ n)]
terminal 0   = True
terminal n   = False
HTH,
Stefan
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Type classes... popular for newbies, isn't it?

2004-08-07 Thread camarao
 How about inserting one more parameter, action, in your class
 definition:
 class (Ord st) = MinimaxState st action where
successors:: st - [(action,st)]
terminal:: st - Bool
 instance MinimaxState Int Int where
terminal i = i == 0
successors i = [(1,i+1), (-1,i-1)]

 I'd rather not do that, but even if I did, the type-variable action
 would not be reachable in the terminal function.  I could specify a
 functional dependency st - action (though I've never used it, it would
 be a fun to learn).

Right... you need the functional dependency because of terminal, and in
general a type annotation for using it.

Carlos



___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Type classes... popular for newbies, isn't it?

2004-08-06 Thread Arjun Guha
This class definition is giving me a lot of problems with the successor 
function:

class (Ord st) = MinimaxState st where
  successors:: st - [(action,st)]
  terminal:: st - Bool
A trivial example would be:
instance MinimaxState Int where
  terminal i = i == 0
  successors i = [(1,i+1), (-1,i-1)]
However, I get this error in GHC:
Could not deduce (Num action)
from the context (MinimaxState Int, Ord Int)
  arising from the literal `1' at AbTest.hs:7
Probable fix:
Add (Num action) to the class or instance method `successors'
In the first argument of `negate', namely `1'
In the list element: (- 1, (- i) - 1)
In the definition of `successors':
successors i = [(1, i + 1), (- 1, (- i) - 1)]
I have the class definition and the instance definition in seperate 
files.  I don't understand where I'm supposed to put the probable fix. 
 I don't want it to be in the class definition, since action should be 
fairly arbitrary.

In fact, no matter what I try, I get errors, for example:
instance MinimaxState Int where
  terminal i = i == 0
  successors i = [(action,i+1), (action,i-1)]
Cannot unify the type-signature variable `action'
with the type `[Char]'
Expected type: action
Inferred type: [Char]
In the list element: (action, i + 1)
In the definition of `successors':
successors i = [(action, i + 1), (action, (- i) - 1)]
Any suggestions?
-Arjun
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe