Re: [Haskell-cafe] Extending Type Classes

2013-08-27 Thread Simon Peyton-Jones
See http://ghc.haskell.org/trac/ghc/wiki/DefaultSuperclassInstances

| -Original Message-
| From: Haskell-Cafe [mailto:haskell-cafe-boun...@haskell.org] On Behalf
| Of Henning Thielemann
| Sent: 26 August 2013 20:07
| To: Frantisek Farka
| Cc: Haskell Cafe
| Subject: Re: [Haskell-cafe] Extending Type Classes
| 
| 
|   The problem of refinement of type classes annoys me from time to time
| when I work on the NumericPrelude. It is an experimental type class
| hierarchy for mathematical types. Sometimes a new data type T shall be
| implemented and it turns out that you can implement only a part of all
| methods of a certain class. Then a natural step is to split the class
| into
| two classes A and B: 'A' contains the methods we can implement for T and
| 'B' contains the remaining methods and 'B' is a sub-class of 'A'.
|   First, this means that all client code has to be rewritten. Second,
| code
| for instances becomes very lengthy, because over the time code tends to
| contain one instances for every method. However the many small instances
| actually carry information: Every instance has its specialised
| constraints. E.g. you would certainly try to use only Applicative
| constraints in an Applicative instance and not Monad constraints.
| However,
| if there is a way to define Applicative and Monad instances in one go,
| the
| Applicative instance may get Monad constraints.
| 
| ___
| 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] Extending Type Classes

2013-08-26 Thread Henning Thielemann


 The problem of refinement of type classes annoys me from time to time 
when I work on the NumericPrelude. It is an experimental type class 
hierarchy for mathematical types. Sometimes a new data type T shall be 
implemented and it turns out that you can implement only a part of all 
methods of a certain class. Then a natural step is to split the class into 
two classes A and B: 'A' contains the methods we can implement for T and 
'B' contains the remaining methods and 'B' is a sub-class of 'A'.
 First, this means that all client code has to be rewritten. Second, code 
for instances becomes very lengthy, because over the time code tends to 
contain one instances for every method. However the many small instances 
actually carry information: Every instance has its specialised 
constraints. E.g. you would certainly try to use only Applicative 
constraints in an Applicative instance and not Monad constraints. However, 
if there is a way to define Applicative and Monad instances in one go, the 
Applicative instance may get Monad constraints.


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


[Haskell-cafe] Extending Type Classes

2013-07-05 Thread Frantisek Farka
Hello all,

I was looking for my master thesis topic and my supervisor suggested an
idea of extending class system so it enables refactoring Type Class
hierarchy without affecting client source code which is using
refactored classes. 

One example is Functor - Applicative - Monad problem and corresponding
proposal [1]. But this proposal instead of allowing the change through
extending Type Classes forces client code to prepare for the new class
layout and then switch the classes to the new layout.

My goal is rather to allow direct changes in class hierarchy without
affecting client source code. I have found different proposals
approaching this problem on HaskellWiki, some of them are overlapping,
some of them refer each other. The most promising to me seems Default
superclass instances proposal [2]. This one is somehow implemented in
the Strathclyde Haskell Enhancement (SHE) [3] but I haven't found much
reference or user experience really.

So the reason why I write this email is to ask you for some tips where
above mentioned problem occurs in real source code. I would like to
investigate some real examples before designing some ad hoc changes to
the Type Classes system.

Besides that I'd appreciate anyone who has used default superclass
instances in SHE to share his experience.

And last but not least I am always grateful for any comments and
suggestions.



Best wishes

Frantisek


[1] http://www.haskell.org/haskellwiki/Functor_hierarchy_proposal
[2] http://hackage.haskell.org/trac/ghc/wiki/DefaultSuperclassInstances
[3] https://personal.cis.strath.ac.uk/conor.mcbride/pub/she/


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


[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] Library API design: functional objects VS type classes

2013-03-05 Thread Atsuro Hoshino
Hi Rob,

I usually prefer type class approach for early stage of development.

Type class approach is more flexible, less works required.
One might get a function with lots of constraints, and quite a lot of
language extensions may appear, though it works.

Once things got settled down, I reconsider API.


The type signatures shown in your example::

  class FooC a where
mkFooC :: IO a
readFooC :: a - IO Int
incrFooC :: a - IO ()

and:

  data FooT a = FooT {
  readFooT :: IO a
, incrFooT :: IO ()
}

Resulting type of 'readFooC' is fixed to 'Int' within the type class.
On the other hand, resulting type of 'readFooT' is type variable 'a'.

Made slight modification to the type class shown in your
example. Changed result type of 'readFooC' to take associated
type:

http://hpaste.org/83507

Once criteria for comparison I can think is performance.

For compilation time, I guess functional object approach give better
performance, since some of the works done by compiler are already done
manually. Though, I haven't done benchmark of compilation time, and
not sure how much interest exist in performance of compilation.

For runtime performance, one can do benchmark in its concrete usecase.
I suppose, generally, functions defined with type class are slower
than functions having concrete type. See SPECIALIZE pragam in GHC[1].

Another criteria I can think is extensibility.

Suppose that we want to have new member function, 'incrTwice'. If we
have chance to change the source of 'FooC', adding new member function
to 'FooC' type class directly is possible, with default function body
filled in.

  class FooC a where
type FooCVal a :: *
mkFooC :: IO a
readFooC :: a - IO (FooCVal a)
incrFooC :: a - IO ()
incrTwiceC :: a - IO ()
incrTwiceC a = incrFooC a  incrFooC a

Though, having reasonable default is not always possible.

For additional source of inspiration, might worth looking the
classic[2], and scrap your type classes article[3].


[1]:
http://www.haskell.org/ghc/docs/7.6.1/html/users_guide/pragmas.html#specialize-pragma
[2]: http://homepages.inf.ed.ac.uk/wadler/papers/class/class.ps
[3]: http://www.haskellforall.com/2012/05/scrap-your-type-classes.html

Hope these help.


Regards,
--
Atsuro



On Tue, Mar 5, 2013 at 7:50 AM, Rob Stewart robstewar...@gmail.com wrote:

 Hi,

 I have a question about API design for Haskell libraries. It is a simple
 one:
 functional object data structures encapsulating mutable state VS type
 classes encapsulating mutable state

 Here is a simple example. I present an API: using a type class `FooC`,
 and aso as a data structure `FooT`. Both are stateful, in the form of
 an MVar holding an Integer, with an operation `incrFoo` to increment
 this value by one, and another `readFoo` to read the Integer value.
 -
 import Control.Concurrent

 -- API approach 1: Using type classes
 class FooC a where
   mkFooC :: IO a
   readFooC :: a - IO Int
   incrFooC :: a - IO ()

 newtype Bar = Bar (MVar Int)
 instance FooC Bar where
   mkFooC = newMVar 0 = \i - return $ Bar i
   readFooC (Bar mv) = readMVar mv
   incrFooC (Bar mv) =
 modifyMVar_ mv $ \i - return (i+1)

 -- API approach 2: Using direct field records
 data FooT a = FooT {
 readFooT :: IO a
   , incrFooT :: IO ()
   }

 mkBar :: IO (FooT Int)
 mkBar = do
   mv - newMVar 0
   return FooT {
   readFooT = readMVar mv
 , incrFooT = modifyMVar_ mv $ \i - return (i+1)
 }

 -- Tests the type class API
 testTypeClass :: IO ()
 testTypeClass = do
   bar - mkBar
   incrFooT bar
   incrFooT bar
   i - readFooT bar
   print i -- prints 2

 -- Tests the direct data structure API
 testDataStruct :: IO ()
 testDataStruct = do
   bar - (mkFooC :: IO Bar)
   incrFooC bar
   incrFooC bar
   i - readFooC bar
   print i -- prints 2
 

 With that, I now ask: which is more common? Which is the better API
 design for a library? The APIs are almost identical. Under what
 conditions is the type classes preferred over the mutable object
 style data structure? There are two related resources that provides
 additional context here, that favour the functional objects approach:
 - Section 3.4 Mutable Objects in Haskell's Overlooked Object
 System http://goo.gl/gnZXL
 - A similar question (data structures vs type classes) in Haskell
 Antipattern: Existential Typeclass

 http://lukepalmer.wordpress.com/2010/01/24/haskell-antipattern-existential-typeclass/

 Thanks!

 --
 Rob

 ___
 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] Library API design: functional objects VS type classes

2013-03-05 Thread Edsko de Vries
What is the advance of using type classes? A function of the form

  f :: Show a = ...

really has an implicit argument

  f :: Show__Dict a - ...

that the compiler infers for us. So, the advantage of type classes is one
of convenience: we don't have to pass dictionaries around, or even figure
out which dictionaries we need; the compiler does that for us. But if we
have a type class of the form

  class Foo a where
mkFoo :: IO FooToken
otherFun1 :: FooToken - ...
otherFun2 :: FooToken - ...

then this advantage is mostly lost; we still need to pass around an
explicit FooToken object. In a case like this, I don't see the advantage of
using a type class over using a data type

  data Foo = Foo { otherFun1 :: ... , otherFun2 :: ... }
  mkFoo :: .. - Foo

There are exceptions; for instance, if you want to encode 'inheritance' in
some way then type classes might still be useful; for instance, see the
Gtk2Hs library, which uses this extensively.

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


Re: [Haskell-cafe] Library API design: functional objects VS type classes

2013-03-05 Thread Joey Adams
On Mon, Mar 4, 2013 at 5:50 PM, Rob Stewart robstewar...@gmail.com wrote:

 ...
 -
 import Control.Concurrent

 -- API approach 1: Using type classes
 class FooC a where
   mkFooC :: IO a
   readFooC :: a - IO Int
   incrFooC :: a - IO ()


I recommend taking 'mkFooC' out of the typeclass.  It keeps you from being
able to (easily) construct a 'FooC' from dynamic data, e.g.:

mkFoo :: Host - Port - IO MyFoo

After this change, the typeclass approach and the data constructor approach
are nearly equivalent, except:

 * With the typeclass approach, the compiler passes the dictionary
implicitly, which can be more convenient to use (e.g. `readFooC a` instead
of `readFooC (getFoo a)`).

 * With the typeclass approach, you have to define a Foo type to contain
the environment needed for Foo methods.  With the record approach, you can
just construct and use a FooT record directly.

Either way, don't forget about simple encapsulation:

data LineDevice -- abstract

-- Some LineDevice constructors for common tasks
stdio :: LineDevice
openFile :: FilePath - IO LineDevice
connectTo :: HostName - PortId - IO LineDevice

getLine :: LineDevice - Int - IO ByteString
putLine :: LineDevice - ByteString - IO ()

This interface is very easy to understand.  If you want to let users make
their own LineDevice objects, you can still provide an internal module
with something like this:

data Driver = Driver
{ getLine :: Int - IO ByteString
, putLine :: ByteString - IO ()
}

newLineDevice :: Driver - IO LineDevice

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


[Haskell-cafe] Library API design: functional objects VS type classes

2013-03-04 Thread Rob Stewart
Hi,

I have a question about API design for Haskell libraries. It is a simple one:
functional object data structures encapsulating mutable state VS type
classes encapsulating mutable state

Here is a simple example. I present an API: using a type class `FooC`,
and aso as a data structure `FooT`. Both are stateful, in the form of
an MVar holding an Integer, with an operation `incrFoo` to increment
this value by one, and another `readFoo` to read the Integer value.
-
import Control.Concurrent

-- API approach 1: Using type classes
class FooC a where
  mkFooC :: IO a
  readFooC :: a - IO Int
  incrFooC :: a - IO ()

newtype Bar = Bar (MVar Int)
instance FooC Bar where
  mkFooC = newMVar 0 = \i - return $ Bar i
  readFooC (Bar mv) = readMVar mv
  incrFooC (Bar mv) =
modifyMVar_ mv $ \i - return (i+1)

-- API approach 2: Using direct field records
data FooT a = FooT {
readFooT :: IO a
  , incrFooT :: IO ()
  }

mkBar :: IO (FooT Int)
mkBar = do
  mv - newMVar 0
  return FooT {
  readFooT = readMVar mv
, incrFooT = modifyMVar_ mv $ \i - return (i+1)
}

-- Tests the type class API
testTypeClass :: IO ()
testTypeClass = do
  bar - mkBar
  incrFooT bar
  incrFooT bar
  i - readFooT bar
  print i -- prints 2

-- Tests the direct data structure API
testDataStruct :: IO ()
testDataStruct = do
  bar - (mkFooC :: IO Bar)
  incrFooC bar
  incrFooC bar
  i - readFooC bar
  print i -- prints 2


With that, I now ask: which is more common? Which is the better API
design for a library? The APIs are almost identical. Under what
conditions is the type classes preferred over the mutable object
style data structure? There are two related resources that provides
additional context here, that favour the functional objects approach:
- Section 3.4 Mutable Objects in Haskell's Overlooked Object
System http://goo.gl/gnZXL
- A similar question (data structures vs type classes) in Haskell
Antipattern: Existential Typeclass
http://lukepalmer.wordpress.com/2010/01/24/haskell-antipattern-existential-typeclass/

Thanks!

--
Rob

___
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


Re: [Haskell-cafe] Non polymorphic numerals option -- avoiding type classes

2012-12-27 Thread David Virebayre
Prelude :t [[1,2],3]

you have a list with 2 elements:
- [1,2]
- 3
the type of [1,2] is [Integer]
the type of 3 is Integer

But all elements in a list must have the same type.





2012/12/27 Rustom Mody rustompm...@gmail.com:


 On Thu, Dec 27, 2012 at 1:48 AM, Roman Cheplyaka r...@ro-che.info wrote:

 * Rustom Mody rustompm...@gmail.com [2012-12-26 20:12:17+0530]
  So is there any set of flags to make haskell literals less polymorphic?

 Yes, there is!

   % ghci -XRebindableSyntax
   GHCi, version 7.6.1: http://www.haskell.org/ghc/  :? for help
   Loading package ghc-prim ... linking ... done.
   Loading package integer-gmp ... linking ... done.
   Loading package base ... linking ... done.
import Prelude hiding (fromInteger)
   Prelude let fromInteger = id
   Prelude :t 3
   3 :: Integer

 Roman



 Thanks Roman -- that helps.
 And yet the ghci error is much more obscure than the gofer error:

 --- contents of .ghci ---
 :set -XRebindableSyntax
 let fromInteger = id
 -- ghci session -
 $ ghci
 GHCi, version 7.4.1: http://www.haskell.org/ghc/  :? for help

 Loading package ghc-prim ... linking ... done.
 Loading package integer-gmp ... linking ... done.
 Loading package base ... linking ... done.
 Prelude :t 5
 5 :: Integer
 Prelude :t [[1,2],3]

 interactive:1:8:
 Couldn't match expected type `[Integer]' with actual type `Integer'
 Expected type: Integer - [Integer]
   Actual type: Integer - Integer
 In the expression: 3
 In the expression: [[1, 2], 3]


 - The same in gofer -
 Gofer session for:
 pustd.pre
 ? :t [[1,2],3]


 ERROR: Type error in list
 *** expression : [[1,2],3]

 *** term   : 3
 *** type   : Int
 *** does not match : [Int]
 --
 So the error is occurring at the point of the fromInteger (= id) but the
 message does not indicate that

 --
 http://www.the-magus.in
 http://blog.languager.org


 ___
 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] Non polymorphic numerals option -- avoiding type classes

2012-12-27 Thread Kim-Ee Yeoh
Hi David, it looks like Rustom's aware that haskell's not lisp. What he
really wants methinks is a way to suppress type classes altogether! That or
a NoOverloadedNumerals extension.

-- Kim-Ee


On Thu, Dec 27, 2012 at 4:03 PM, David Virebayre dav.vire+hask...@gmail.com
 wrote:

 Prelude :t [[1,2],3]

 you have a list with 2 elements:
 - [1,2]
 - 3
 the type of [1,2] is [Integer]
 the type of 3 is Integer

 But all elements in a list must have the same type.





 2012/12/27 Rustom Mody rustompm...@gmail.com:
 
 
  On Thu, Dec 27, 2012 at 1:48 AM, Roman Cheplyaka r...@ro-che.info
 wrote:
 
  * Rustom Mody rustompm...@gmail.com [2012-12-26 20:12:17+0530]
   So is there any set of flags to make haskell literals less
 polymorphic?
 
  Yes, there is!
 
% ghci -XRebindableSyntax
GHCi, version 7.6.1: http://www.haskell.org/ghc/  :? for help
Loading package ghc-prim ... linking ... done.
Loading package integer-gmp ... linking ... done.
Loading package base ... linking ... done.
 import Prelude hiding (fromInteger)
Prelude let fromInteger = id
Prelude :t 3
3 :: Integer
 
  Roman
 
 
 
  Thanks Roman -- that helps.
  And yet the ghci error is much more obscure than the gofer error:
 
  --- contents of .ghci ---
  :set -XRebindableSyntax
  let fromInteger = id
  -- ghci session -
  $ ghci
  GHCi, version 7.4.1: http://www.haskell.org/ghc/  :? for help
 
  Loading package ghc-prim ... linking ... done.
  Loading package integer-gmp ... linking ... done.
  Loading package base ... linking ... done.
  Prelude :t 5
  5 :: Integer
  Prelude :t [[1,2],3]
 
  interactive:1:8:
  Couldn't match expected type `[Integer]' with actual type `Integer'
  Expected type: Integer - [Integer]
Actual type: Integer - Integer
  In the expression: 3
  In the expression: [[1, 2], 3]
 
 
  - The same in gofer -
  Gofer session for:
  pustd.pre
  ? :t [[1,2],3]
 
 
  ERROR: Type error in list
  *** expression : [[1,2],3]
 
  *** term   : 3
  *** type   : Int
  *** does not match : [Int]
  --
  So the error is occurring at the point of the fromInteger (= id) but the
  message does not indicate that
 
  --
  http://www.the-magus.in
  http://blog.languager.org
 
 
  ___
  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

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


Re: [Haskell-cafe] Non polymorphic numerals option -- avoiding type classes

2012-12-27 Thread Rustom Mody
On Thu, Dec 27, 2012 at 8:26 PM, Kim-Ee Yeoh k...@atamo.com wrote:

 Hi David, it looks like Rustom's aware that haskell's not lisp. What he
 really wants methinks is a way to suppress type classes altogether! That or
 a NoOverloadedNumerals extension.

 -- Kim-Ee


I'm not really sure about that... Look!

ghci with default startup

$ ghci
GHCi, version 7.4.1: http://www.haskell.org/ghc/  :? for help
Loading package ghc-prim ... linking ... done.
Loading package integer-gmp ... linking ... done.
Loading package base ... linking ... done.
Prelude :t [[1,2],3]
[[1,2],3] :: (Num [t], Num t) = [[t]]

So it would appear that ghci is giving a well-typing for [[1,2], 3].
But is it?

Prelude [[1,2],3]

interactive:3:8:
No instance for (Num [t0])
  arising from the literal `3'
Possible fix: add an instance declaration for (Num [t0])
In the expression: 3
In the expression: [[1, 2], 3]
In an equation for `it': it = [[1, 2], 3]
---
So is it well-typed in ghci or not??

And  now we add Roman's suggestions...
$ cat .ghci
:set -XRebindableSyntax
let fromInteger = id

And run ghci again

$ ghci
GHCi, version 7.4.1: http://www.haskell.org/ghc/  :? for help
Loading package ghc-prim ... linking ... done.
Loading package integer-gmp ... linking ... done.
Loading package base ... linking ... done.
Prelude :t [[1,2],3]

interactive:1:8:
Couldn't match expected type `[Integer]' with actual type `Integer'
Expected type: Integer - [Integer]
  Actual type: Integer - Integer
In the expression: 3
In the expression: [[1, 2], 3]
Prelude [[1,2],3]

interactive:3:8:
Couldn't match expected type `[Integer]' with actual type `Integer'
Expected type: Integer - [Integer]
  Actual type: Integer - Integer
In the expression: 3
In the expression: [[1, 2], 3]
Prelude

So far so good -- when an expression is type-wrong, its 'wrongness' is the
same irrespective of whether I ask for its type or evaluate it.

But now we are in for new surprises:  Try out
f x y = x / y
Prelude :l f
[1 of 1] Compiling Main ( f.hs, interpreted )

f.hs:1:11: Not in scope: `/'
Failed, modules loaded: none.
Prelude (/)

Oh is it that now integer literals are just plain Integers and cant be
divided using '/' ??

So lets replace '/' with '+'
f.hs:1:11: Not in scope: `+'

And now I am at my wits end!
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Non polymorphic numerals option -- avoiding type classes

2012-12-27 Thread satvik chauhan
I don't know about the RebindableSyntax extension.  But

Prelude :t [[1,2],3]
[[1,2],3] :: (Num [t], Num t) = [[t]]

The above only says that is is possible to have a list like [[1,2],3] if
you have for a Num t, [t] is also an instance of Num. But it doesn't
guarantee the existence of such an instance. When you actually execute the
code then you see that no such instance exists by default.

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


Re: [Haskell-cafe] Non polymorphic numerals option -- avoiding type classes

2012-12-27 Thread Roman Cheplyaka
* Rustom Mody rustompm...@gmail.com [2012-12-27 22:18:15+0530]
 But now we are in for new surprises:  Try out
 f x y = x / y
 Prelude :l f
 [1 of 1] Compiling Main ( f.hs, interpreted )
 
 f.hs:1:11: Not in scope: `/'
 Failed, modules loaded: none.
 Prelude (/)

It's because RebindableSyntax implies NoImplicitPrelude. This is not an
issue if you only work in the interpreter (you can put import Prelude
hiding (fromInteger) in .ghci), but you'd also need to put that into
every source file that you wish to load.

An alternative would be to create your own Prelude (or use an existing
one, like [1]) and use it instead of the one defined in base (by hiding
base and exposing a different package).

[1]: 
http://hackage.haskell.org/packages/archive/simpleprelude/1.0.1.3/doc/html/Prelude.html

Roman

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


Re: [Haskell-cafe] Non polymorphic numerals option -- avoiding type classes

2012-12-27 Thread Roman Cheplyaka
Forgot to say: if you go the first route, you'll also need to define your
fromInteger in every module — the one from .ghci won't be in scope.

You can define

  module MyPrelude (module Prelude, fromInteger) where

  import Prelude hiding (fromInteger)

  fromInteger = id

and import it instead.

* Roman Cheplyaka r...@ro-che.info [2012-12-27 19:22:53+0200]
 * Rustom Mody rustompm...@gmail.com [2012-12-27 22:18:15+0530]
  But now we are in for new surprises:  Try out
  f x y = x / y
  Prelude :l f
  [1 of 1] Compiling Main ( f.hs, interpreted )
  
  f.hs:1:11: Not in scope: `/'
  Failed, modules loaded: none.
  Prelude (/)
 
 It's because RebindableSyntax implies NoImplicitPrelude. This is not an
 issue if you only work in the interpreter (you can put import Prelude
 hiding (fromInteger) in .ghci), but you'd also need to put that into
 every source file that you wish to load.
 
 An alternative would be to create your own Prelude (or use an existing
 one, like [1]) and use it instead of the one defined in base (by hiding
 base and exposing a different package).
 
 [1]: 
 http://hackage.haskell.org/packages/archive/simpleprelude/1.0.1.3/doc/html/Prelude.html
 
 Roman

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


Re: [Haskell-cafe] Non polymorphic numerals option -- avoiding type classes

2012-12-27 Thread Kim-Ee Yeoh
On Thu, Dec 27, 2012 at 11:48 PM, Rustom Mody rustompm...@gmail.com wrote:
 On Thu, Dec 27, 2012 at 8:26 PM, Kim-Ee Yeoh k...@atamo.com wrote:
 What he really wants methinks is a way to suppress type classes
altogether! That or a NoOverloadedNumerals extension.

 I'm not really sure about that... Look!

 Prelude :t [[1,2],3]
 [[1,2],3] :: (Num [t], Num t) = [[t]]

As Satvik explained, well-typed does not imply instantiable. And with
constraints, not instantiable /does/ imply not evaluable!

 :set -XRebindableSyntax
 let fromInteger = id
 Prelude :t [[1,2],3]

 Couldn't match expected type `[Integer]' with actual type `Integer'
 Expected type: Integer - [Integer]
   Actual type: Integer - Integer
 In the expression: 3
 In the expression: [[1, 2], 3]

You can see overloaded numerals at work again via the hidden hand of
fromInteger.

Presumably some imaginary NoOverloadedNumerals extension would thoroughly
purge its presence.

-- Kim-Ee


On Thu, Dec 27, 2012 at 11:48 PM, Rustom Mody rustompm...@gmail.com wrote:

 On Thu, Dec 27, 2012 at 8:26 PM, Kim-Ee Yeoh k...@atamo.com wrote:

 Hi David, it looks like Rustom's aware that haskell's not lisp. What he
really wants methinks is a way to suppress type classes altogether! That or
a NoOverloadedNumerals extension.

 -- Kim-Ee


 I'm not really sure about that... Look!

 ghci with default startup
 

 $ ghci
 GHCi, version 7.4.1: http://www.haskell.org/ghc/  :? for help
 Loading package ghc-prim ... linking ... done.
 Loading package integer-gmp ... linking ... done.
 Loading package base ... linking ... done.
 Prelude :t [[1,2],3]
 [[1,2],3] :: (Num [t], Num t) = [[t]]

 So it would appear that ghci is giving a well-typing for [[1,2], 3].
 But is it?

 Prelude [[1,2],3]

 interactive:3:8:

 No instance for (Num [t0])
   arising from the literal `3'

 Possible fix: add an instance declaration for (Num [t0])
 In the expression: 3
 In the expression: [[1, 2], 3]
 In an equation for `it': it = [[1, 2], 3]
 ---
 So is it well-typed in ghci or not??

 And  now we add Roman's suggestions...
 $ cat .ghci

 :set -XRebindableSyntax
 let fromInteger = id

 And run ghci again


 $ ghci
 GHCi, version 7.4.1: http://www.haskell.org/ghc/  :? for help
 Loading package ghc-prim ... linking ... done.
 Loading package integer-gmp ... linking ... done.
 Loading package base ... linking ... done.
 Prelude :t [[1,2],3]

 interactive:1:8:
 Couldn't match expected type `[Integer]' with actual type `Integer'
 Expected type: Integer - [Integer]
   Actual type: Integer - Integer
 In the expression: 3
 In the expression: [[1, 2], 3]
 Prelude [[1,2],3]

 interactive:3:8:

 Couldn't match expected type `[Integer]' with actual type `Integer'
 Expected type: Integer - [Integer]
   Actual type: Integer - Integer
 In the expression: 3
 In the expression: [[1, 2], 3]
 Prelude

 So far so good -- when an expression is type-wrong, its 'wrongness' is
the same irrespective of whether I ask for its type or evaluate it.

 But now we are in for new surprises:  Try out
 f x y = x / y
 Prelude :l f
 [1 of 1] Compiling Main ( f.hs, interpreted )

 f.hs:1:11: Not in scope: `/'
 Failed, modules loaded: none.
 Prelude (/)

 Oh is it that now integer literals are just plain Integers and cant be
divided using '/' ??

 So lets replace '/' with '+'
 f.hs:1:11: Not in scope: `+'

 And now I am at my wits end!
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Non polymorphic numerals option -- avoiding type classes

2012-12-26 Thread Rustom Mody
In haskell, we have

Prelude :t 4
4 :: Num a = a
Prelude

This may be nice in its generality but it makes it hard (for me at least)
when teaching a beginners course to teach polymorphic vs monomorphic
types.  The above leads to even more 'advanced' results like this:

Prelude :t [[1],2]
[[1],2] :: (Num [t], Num t) = [[t]]


Prelude [[1],2]

interactive:5:6:
No instance for (Num [t0])
  arising from the literal `2'
Possible fix: add an instance declaration for (Num [t0])
In the expression: 2
In the expression: [[1], 2]
In an equation for `it': it = [[1], 2]


By contrast in gofer, numeric literals are monomorphic and no such
peculiarities arise

? :t [[1],2]
ERROR: Type error in list
*** expression : [[1],2]
*** term   : 2
*** type   : Int
*** does not match : [Int]

[[1],2]
ERROR: Type error in list
*** expression : [[1],2]
*** term   : 2
*** type   : Int
*** does not match : [Int]


So is there any set of flags to make haskell literals less polymorphic?
ie I want 3 to have type Int and 3.0 to have type Float.

This is of course for beginning students to not see type classes too early
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Non polymorphic numerals option -- avoiding type classes

2012-12-26 Thread koomi
You should note that GHCi uses extended defaulting rules as explained in
[1].
This means that a literal like 5 will only be of type Num a = a in GHCi
while in a normal Haskell program it will default to some concrete type
(Integer if there are no other constraints). Also, if you define x = 5
in a .hs file and load the file in GHCi, x will have type Integer.

In my short search I could not find out how to reverse this behavior,
:unset -XExtendedDefaultRules does not seem to work.


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


Re: [Haskell-cafe] Non polymorphic numerals option -- avoiding type classes

2012-12-26 Thread koomi
Sorry, forgot the link:
http://www.haskell.org/ghc/docs/7.0.4/html/users_guide/interactive-evaluation.html
Section 2.4.5 Type defaulting in GHCi
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Non polymorphic numerals option -- avoiding type classes

2012-12-26 Thread Roman Cheplyaka
* Rustom Mody rustompm...@gmail.com [2012-12-26 20:12:17+0530]
 So is there any set of flags to make haskell literals less polymorphic?

Yes, there is!

  % ghci -XRebindableSyntax
  GHCi, version 7.6.1: http://www.haskell.org/ghc/  :? for help
  Loading package ghc-prim ... linking ... done.
  Loading package integer-gmp ... linking ... done.
  Loading package base ... linking ... done.
   import Prelude hiding (fromInteger)
  Prelude let fromInteger = id
  Prelude :t 3
  3 :: Integer

Roman

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


Re: [Haskell-cafe] Non polymorphic numerals option -- avoiding type classes

2012-12-26 Thread Rustom Mody
On Thu, Dec 27, 2012 at 1:48 AM, Roman Cheplyaka r...@ro-che.info wrote:

 * Rustom Mody rustompm...@gmail.com [2012-12-26 20:12:17+0530]
  So is there any set of flags to make haskell literals less polymorphic?

 Yes, there is!

   % ghci -XRebindableSyntax
   GHCi, version 7.6.1: http://www.haskell.org/ghc/  :? for help
   Loading package ghc-prim ... linking ... done.
   Loading package integer-gmp ... linking ... done.
   Loading package base ... linking ... done.
import Prelude hiding (fromInteger)
   Prelude let fromInteger = id
   Prelude :t 3
   3 :: Integer

 Roman



Thanks Roman -- that helps.
And yet the ghci error is much more obscure than the gofer error:

--- contents of .ghci ---
:set -XRebindableSyntax
let fromInteger = id
-- ghci session -
$ ghci
GHCi, version 7.4.1: http://www.haskell.org/ghc/  :? for help
Loading package ghc-prim ... linking ... done.
Loading package integer-gmp ... linking ... done.
Loading package base ... linking ... done.
Prelude :t 5
5 :: Integer
Prelude :t [[1,2],3]

interactive:1:8:
Couldn't match expected type `[Integer]' with actual type `Integer'
Expected type: Integer - [Integer]
  Actual type: Integer - Integer
In the expression: 3
In the expression: [[1, 2], 3]


- The same in gofer -
Gofer session for:
pustd.pre
? :t [[1,2],3]

ERROR: Type error in list
*** expression : [[1,2],3]
*** term   : 3
*** type   : Int
*** does not match : [Int]
--
So the error is occurring at the point of the fromInteger (= id) but the
message does not indicate that

-- 
http://www.the-magus.in
http://blog.languager.org
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [GHC] #7224: Polymorphic kind annotations on type classes don't always work as expected

2012-10-11 Thread GHC
#7224: Polymorphic kind annotations on type classes don't always work as 
expected
+---
  Reporter:  slindley   |  Owner:   
  Type:  bug| Status:  closed   
  Priority:  normal |  Milestone:   
 Component:  Compiler (Type checker)|Version:  7.6.1-rc1
Resolution:  fixed  |   Keywords:  kind polymorphism
Os:  Unknown/Multiple   |   Architecture:  Unknown/Multiple 
   Failure:  GHC rejects valid program  | Difficulty:  Unknown  
  Testcase:  polykinds/T7224|  Blockedby:   
  Blocking: |Related:   
+---
Changes (by igloo):

  * status:  merge = closed
  * resolution:  = fixed


Comment:

 Merged as c4aa0165bb8eb4b65d8c1299fdff279e1f97bbb4

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/7224#comment:5
GHC http://www.haskell.org/ghc/
The Glasgow Haskell Compiler

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


Re: [GHC] #7224: Polymorphic kind annotations on type classes don't always work as expected

2012-09-18 Thread GHC
#7224: Polymorphic kind annotations on type classes don't always work as 
expected
+---
Reporter:  slindley |   Owner:  
 
Type:  bug  |  Status:  merge   
 
Priority:  normal   |   Milestone:  
 
   Component:  Compiler (Type checker)  | Version:  7.6.1-rc1   
 
Keywords:  kind polymorphism|  Os:  Unknown/Multiple
 
Architecture:  Unknown/Multiple | Failure:  GHC rejects valid 
program
  Difficulty:  Unknown  |Testcase:  polykinds/T7224 
 
   Blockedby:   |Blocking:  
 
 Related:   |  
+---
Changes (by simonpj):

  * status:  new = merge
  * difficulty:  = Unknown
  * testcase:  = polykinds/T7224


Comment:

 Thanks for the report.  The declaration of {{{PMonad'}}} is bogus becuase
 you are using a ''kind'' variable `i` in a ''type'', the type of
 {{{ret'}}}.  Now GHC says
 {{{
 T7224.hs:10:19:
 Kind variable `i' used as a type
 In the type `a - m i i a'
 In the class declaration for PMonad'
 }}}
 Merge to 7.6 branh.

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/7224#comment:3
GHC http://www.haskell.org/ghc/
The Glasgow Haskell Compiler

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


Re: [GHC] #7224: Polymorphic kind annotations on type classes don't always work as expected

2012-09-18 Thread GHC
#7224: Polymorphic kind annotations on type classes don't always work as 
expected
+---
Reporter:  slindley |   Owner:  
 
Type:  bug  |  Status:  merge   
 
Priority:  normal   |   Milestone:  
 
   Component:  Compiler (Type checker)  | Version:  7.6.1-rc1   
 
Keywords:  kind polymorphism|  Os:  Unknown/Multiple
 
Architecture:  Unknown/Multiple | Failure:  GHC rejects valid 
program
  Difficulty:  Unknown  |Testcase:  polykinds/T7224 
 
   Blockedby:   |Blocking:  
 
 Related:   |  
+---

Comment(by slindley):

 Ah yes. Kind variables bound at the top level of a type class definition
 are in scope for the rest of the class definition. I guess (if the GHC
 type system was suitably adapted) it might actually be useful to allow
 kind variables in types.

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/7224#comment:4
GHC http://www.haskell.org/ghc/
The Glasgow Haskell Compiler

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


Re: [GHC] #7224: Polymorphic kind annotations on type classes don't always work as expected

2012-09-17 Thread GHC
#7224: Polymorphic kind annotations on type classes don't always work as 
expected
---+
 Reporter:  slindley   |  Owner:
 
 Type:  bug| Status:  new   
 
 Priority:  normal |  Component:  Compiler (Type 
checker)
  Version:  7.6.1-rc1  |   Keywords:  kind polymorphism 
 
   Os:  Unknown/Multiple   |   Architecture:  Unknown/Multiple  
 
  Failure:  GHC rejects valid program  |   Testcase:
 
Blockedby: |   Blocking:
 
  Related: |  
---+

Comment(by simonpj@…):

 commit 77b63e74454170bd658c6773b9d5c172920d5cc5
 {{{
 Author: Simon Peyton Jones simo...@microsoft.com
 Date:   Mon Sep 10 13:13:24 2012 +0100

 Two fixes to kind unification

 * Don't unify a kind signature-variable with non-tyvar kind
 * Don't allow a kind variable to appear in a type
   (Trac #7224)

  compiler/typecheck/TcHsType.lhs |9 +++--
  compiler/typecheck/TcUnify.lhs  |   20 ++--
  2 files changed, 21 insertions(+), 8 deletions(-)
 }}}

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/7224#comment:2
GHC http://www.haskell.org/ghc/
The Glasgow Haskell Compiler

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


Re: [GHC] #7224: Polymorphic kind annotations on type classes don't always work as expected

2012-09-09 Thread GHC
#7224: Polymorphic kind annotations on type classes don't always work as 
expected
---+
 Reporter:  slindley   |  Owner:
 
 Type:  bug| Status:  new   
 
 Priority:  normal |  Component:  Compiler (Type 
checker)
  Version:  7.6.1-rc1  |   Keywords:  kind polymorphism 
 
   Os:  Unknown/Multiple   |   Architecture:  Unknown/Multiple  
 
  Failure:  GHC rejects valid program  |   Testcase:
 
Blockedby: |   Blocking:
 
  Related: |  
---+

Comment(by slindley):

 If I'd actually switched on PolyKinds in ghci as well as the source file,
 then I'd have got:

 {{{
 *Main :t ret
 ret :: PMonad k m = a - m i i a
 *Main :t ret'
 ret' :: PMonad' m = a - m BOX BOX a
 }}}

 (The mysterious * disappears if {{{PolyKinds}}} is enabled.)

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/7224#comment:1
GHC http://www.haskell.org/ghc/
The Glasgow Haskell Compiler

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


[GHC] #7224: Polymorphic kind annotations on type classes don't always work as expected

2012-09-06 Thread GHC
#7224: Polymorphic kind annotations on type classes don't always work as 
expected
---+
 Reporter:  slindley   |  Owner:
 
 Type:  bug| Status:  new   
 
 Priority:  normal |  Component:  Compiler (Type 
checker)
  Version:  7.6.1-rc1  |   Keywords:  kind polymorphism 
 
   Os:  Unknown/Multiple   |   Architecture:  Unknown/Multiple  
 
  Failure:  GHC rejects valid program  |   Testcase:
 
Blockedby: |   Blocking:
 
  Related: |  
---+
 Consider the following code for defining Atkey-style parameterised monads:

 {{{
 {-# LANGUAGE
 PolyKinds
  #-}

 class PMonad m where
   ret  :: a - m i i a
   bind :: m i j a - (a - m j k b) - m i k b
 class PMonad' (m :: i - i - * - *) where
   ret'  :: a - m i i a
   bind' :: m i j a - (a - m j k b) - m i k b
 }}}

 The following types are inferred for {{{ret}}} and {{{ret'}}}:

 {{{
 *Main :t ret
 ret :: PMonad * m = a - m i i a
 *Main :t ret'
 ret' :: PMonad' m = a - m BOX BOX a
 }}}

 But {{{ret'}}} should have the former type.

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/7224
GHC http://www.haskell.org/ghc/
The Glasgow Haskell Compiler

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


[Haskell-cafe] model theory for type classes

2012-08-23 Thread Patrick Browne
{-I am trying to apply model theoretic concepts to Haskell by considering type classes as theories and instances as models.Then the declaration of a sub-class specifies a signature morphism from the superclass to the subclass.In case below the theories (classes) are signature only (no default methods) so a signature morphisms can be considered as a theory morphisms.The only purpose of the code below is to explore the concepts of model expansion[1] and model reduct [2] in HaskellI am not trying to improve or rewrite the code itself for any particular application.Neither am I trying to find OO style inheritance semantics in Haskell type classes.Rather, I am wondering if the last instance of Worker (commented out) demonstrates that there is no model expansion in this case.That is, for theory morphism the theory(Person) = theory(Worker) we do not get (model(Person) sub-model model(Worker)).If there is no model expansion could it be because of the constructor discipline, which only allows variables, and constructors in the LHS argument patterns.[1] http://www.informatik.uni-bremen.de/~cxl/papers/wadt04b.pdf[2] http://en.wikipedia.org/wiki/Reduct-}constant::Intconstant = (1::Int)fun1::Int - Intfun1 (constant::Int) = 8class Person i n | i - n where pid :: i name :: i - n-- There is a signature/theory morphism from Person to Workerclass Person i n = Worker i n s | i - s where salary :: i - s   -- model(Person)instance Person Int [Char] where pid = (1::Int) name (1::Int)  = (john::[Char])-- We can say that a model(Worker) can use model(Person).instance Worker Int [Char] Int where-- Hypothesis: pid on the RHS shows that a model(Person) is *available* in model(Person) (reduct)?  salary i = if i == pid then 100 else 0 -- instance Worker Int [Char] Int where-- Hypothesis: The model of Person cannot be expanded to a model of Worker(no model expansion)-- pid below is not inherited from Person, it is just a local variable--   salary pid = 100
 Tá an teachtaireacht seo scanta ó thaobh ábhar agus víreas ag Seirbhís Scanta Ríomhphost de chuid Seirbhísí Faisnéise, ITBÁC agus meastar í a bheith slán.  http://www.dit.ie
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] model theory for type classes

2012-08-23 Thread Brent Yorgey
On Thu, Aug 23, 2012 at 01:25:39PM +0100, Patrick Browne wrote:
 
If there is no model expansion could it be because of the constructor
discipline, which only allows variables, and constructors in the LHS
argument patterns.

Indeed, a variable name as a pattern on the LHS of a function
definition has nothing to do with any names which might be in scope.
It is simply a pattern which matches anything.  I am not sure what (if
anything) this says about model expansions.

constant::Int
constant = (1::Int)
fun1::Int - Int
fun1 (constant::Int) = 8

fun1 returns 8 for all inputs.  The fact that fun1's definition uses
the name 'constant' which happens to have the same name as something
in scope is irrelevant.  For example, this is precisely the same as the above:

constant :: Int
constant = 1
fun1 :: Int - Int
fun1 foo = 8

-Brent

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


Re: [Haskell-cafe] model theory for type classes

2012-08-23 Thread Patrick Browne
On 23/08/12, Brent Yorgey  byor...@seas.upenn.edu wrote:fun1 returns 8 for all inputs.  The fact that fun1's definition usesthe name 'constant' which happens to have the same name as somethingin scope is irrelevant.  For example, this is precisely the same as the above:constant :: Intconstant = 1fun1 :: Int - Intfun1 foo = 8-BrentYes, I am aware the semantics of Haskell is this situation. 
I also know for every model of a subclass there must exist a model of the super-class.
I am just not sure whether there is a model expansion from the super-class model to the subclass model.I am also unsure of the morphism from type variables in the class definition to actual types in instances and to the operations in the instance.In a intuitive way I think that I understand these things, but not in a model theoretic way.

Thanks,
Pat
 Tá an teachtaireacht seo scanta ó thaobh ábhar agus víreas ag Seirbhís Scanta Ríomhphost de chuid Seirbhísí Faisnéise, ITBÁC agus meastar í a bheith slán.  http://www.dit.ie
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] model theory for type classes

2012-08-23 Thread wren ng thornton

On 8/23/12 1:02 PM, Patrick Browne wrote:

I am just not sure whether there is a model expansion from the super-class model
to the subclass model.


If by model expansion from... you mean that there is a 
canonical/unique/special mapping from every superclass model to some 
subclass model, then the answer is no.


Consider, for instance, applicative functors and monads. We have the 
(idealized) type classes:


class Functor a where...
class Functor a = Applicative a where...
class Applicative a = Monad a where...

However, there are strictly more Applicative instances than there are 
Monad instances. E.g., lists support an Applicative instance based on 
zip and an Applicative instance based on the cartesian product; however, 
only the latter of these can be extended to a Monad.



Well, technically, that's only if we assume the appropriate laws are 
part of the theories defined by the type classes. Without this 
assumption every type class can be instantiated at every type (for every 
method f, define f = undefined).


--
Live well,
~wren

___
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


Re: [Haskell-cafe] decoupling type classes

2012-01-17 Thread Dominique Devriese
2012/1/16 Yin Wang yinwa...@gmail.com:
 The typical example would be

 instance Eq a = Eq [a] where
  [] == [] = True
  (a : as) == (b : bs) = a == b  as == bs
  _ == _ = False

 It can handle this case, although it doesn't handle it as a parametric
 instance. I suspect that we don't need the concept of parameter
 instances at all. We just searches for instances recursively at the
 call site:

 That seems like it could work, but typically, one would like
 termination guarantees for this search, to avoid the type-checker
 getting stuck...

 Good point. Currently I'm guessing that we need to keep a stack of the
 traced calls. If a recursive call needs an implicit parameter X which
 is matched by one of the functions in the stack, we back up from the
 stack and resolve X to the function found on stack.

You may want to look at scala's approach for their implicit arguments.
They use a certain to conservatively detect infinite loops during the
instance search, but I don't remember the details off hand. While
talking about related work, you may also want to take a look at
Scala's implicit arguments, GHC implicit arguments and C++ concepts...


 foo x =
   let overload bar (x:Int) = x + 1
   in \() - bar x


 baz =
  in foo (1::Int)

 Even if we have only one definition of bar in the program, we should
 not resolve it to the definition of bar inside foo. Because that
 bar is not visible at the call site foo (1::int). We should report
 an error in this case. Think of bar as a typed dynamically scoped
 variable helps to justify this decision.

 So you're saying that any function that calls an overloaded function
 should always allow its own callers to provide this, even if a correct
 instance is in scope. Would that mean all instances have to be
 resolved from main? This also strikes me as strange, since I gather
 you would get something like length :: Monoid Int = [a] - Int,
 which would break if you happen to have a multiplicative monoid in
 scope at the call site?

 If you already have a correct instance in scope, then you should have
 no way defining another instance with the same name and type in the
 scope as the existing one. This is the case for Haskell.

Yes, but different ones may be in scope at different places in the code, right?

 But it may be useful to allow nested definitions (using let) to shadow
 the existing instances in the outer scope of the overloaded call.

I considered something like this for instance arguments in Agda, but
it was hard to make the instance resolution deterministic when
allowing such a form of prioritisation. The problem occurred if a
shadower and shadowee instance had slightly different types, such that
only the shadowee was actually type-valid for a certain instance
argument. However, the type information which caused the shadower to
become invalid only became available late in the type inference
process. In such a case, it is necessary to somehow ascertain that the
shadower instance is not chosen, but I did not manage to figure out
how to get this right.

Dominique

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


Re: [Haskell-cafe] decoupling type classes

2012-01-16 Thread Dominique Devriese
Yin,

2012/1/14 Yin Wang yinwa...@gmail.com:
 On Sat, Jan 14, 2012 at 2:38 PM, Dominique Devriese
 dominique.devri...@cs.kuleuven.be wrote:
 I may or may not have thought about it. Maybe you can give an example
 of parametric instances where there could be problems, so that I can
 figure out whether my system works on the example or not.

 The typical example would be

 instance Eq a = Eq [a] where
  [] == [] = True
  (a : as) == (b : bs) = a == b  as == bs
  _ == _ = False

 It can handle this case, although it doesn't handle it as a parametric
 instance. I suspect that we don't need the concept of parameter
 instances at all. We just searches for instances recursively at the
 call site:

That seems like it could work, but typically, one would like
termination guarantees for this search, to avoid the type-checker
getting stuck...

 foo x =
   let overload bar (x:Int) = x + 1
   in \() - bar x


 baz =
  in foo (1::Int)

 Even if we have only one definition of bar in the program, we should
 not resolve it to the definition of bar inside foo. Because that
 bar is not visible at the call site foo (1::int). We should report
 an error in this case. Think of bar as a typed dynamically scoped
 variable helps to justify this decision.

So you're saying that any function that calls an overloaded function
should always allow its own callers to provide this, even if a correct
instance is in scope. Would that mean all instances have to be
resolved from main? This also strikes me as strange, since I gather
you would get something like length :: Monoid Int = [a] - Int,
which would break if you happen to have a multiplicative monoid in
scope at the call site?

Dominique

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


Re: [Haskell-cafe] decoupling type classes

2012-01-16 Thread Yin Wang
 The typical example would be

 instance Eq a = Eq [a] where
  [] == [] = True
  (a : as) == (b : bs) = a == b  as == bs
  _ == _ = False

 It can handle this case, although it doesn't handle it as a parametric
 instance. I suspect that we don't need the concept of parameter
 instances at all. We just searches for instances recursively at the
 call site:

 That seems like it could work, but typically, one would like
 termination guarantees for this search, to avoid the type-checker
 getting stuck...

Good point. Currently I'm guessing that we need to keep a stack of the
traced calls. If a recursive call needs an implicit parameter X which
is matched by one of the functions in the stack, we back up from the
stack and resolve X to the function found on stack.


 foo x =
   let overload bar (x:Int) = x + 1
   in \() - bar x


 baz =
  in foo (1::Int)

 Even if we have only one definition of bar in the program, we should
 not resolve it to the definition of bar inside foo. Because that
 bar is not visible at the call site foo (1::int). We should report
 an error in this case. Think of bar as a typed dynamically scoped
 variable helps to justify this decision.

 So you're saying that any function that calls an overloaded function
 should always allow its own callers to provide this, even if a correct
 instance is in scope. Would that mean all instances have to be
 resolved from main? This also strikes me as strange, since I gather
 you would get something like length :: Monoid Int = [a] - Int,
 which would break if you happen to have a multiplicative monoid in
 scope at the call site?

If you already have a correct instance in scope, then you should have
no way defining another instance with the same name and type in the
scope as the existing one. This is the case for Haskell.

But it may be useful to allow nested definitions (using let) to shadow
the existing instances in the outer scope of the overloaded call.

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


Re: [Haskell-cafe] decoupling type classes

2012-01-14 Thread Yin Wang
 Also, you don't seem to have thought about the question of parametric
 instances: do you allow them or not, if you do, what computational
 power do they get etc.?

I may or may not have thought about it. Maybe you can give an example
of parametric instances where there could be problems, so that I can
figure out whether my system works on the example or not.


 I'm surprised that you propose passing all type class methods
 separately. It seems to me that for many type classes, you want to
 impose a certain correspondence between the types of the different
 methods in a type class (for example, for the Monad class, you would
 expect return to be of type (a - m a) if (=) is of type (m a - (a
 - m b) - m b)). I would expect that inferencing these releations in
 each function that uses either of the methods will lead to overly
 general inferenced types and the need for more guidance to the type
 inferencer?

I thought they should be of type (a - m a) and (m a - (a - m b) -
m b)), but I just found that as if they should also work if they were
of type (c - m c) and (m a - (a - m b) - m b)).

It doesn't seem to really hurt. We either will have actually types
when they are called (thus catches type errors). Or if they stay
polymorphic, c will be unified with a when they bind. Also, return and
(=) will be dispatched to correct instances just as before.


 By separating the methods, you would also lose the laws that associate
 methods in a type class, right?

 An alternative to what you suggest, is the approach I recommend for
 using instance arguments: wrapping all the methods in a standard data
 type (i.e. define the dictionary explicitly), and pass this around as
 an implicit argument.

I went quickly through your paper and manual and I like the explicit
way. The examples show that the records seem to be a good way to group
the overloaded functions, so I have the impression that grouping and
overloading are orthogonal features. But in your paper I haven't
seen any overloaded functions outside of records, so I guess they are
somehow tied together in your implementation, which is not necessary.

Maybe we can let the user to choose to group or not. If they want to
group and force further constraints among the overloaded functions,
they can use overloaded records and access the functions through the
records; otherwise, they can define overloaded functions separately
and just use them directly. This way also makes the implementation
more modular.


 For this example, one might also argue that the problem is in fact
 that the Num type class is too narrow, and + should instead be defined
 in a parent type class (Monoid comes to mind) together with 0 (which
 also makes sense for strings, by the way)?

I guess more hierarchies solves only some of the problem like this,
but in general this way complicates things, because the overloaded
functions are not in essence related.


 There is another benefit of this decoupling: it can subsume the
 functionality of MPTC. Because the methods are no longer grouped,
 there is no “common” type parameter to the methods. Thus we can easily
 have more than one parameter in the individual methods and
 conveniently use them as MPTC methods.

 Could you explain this a bit further?

In my system, there are no explicit declarations containing type
variables. The declaration overload g is all that is needed.

For example,

overload g
 ... ...
f x (Int y) = g x y


then, f has the inferred type:

'a - Int - {{ g:: 'a - Int - 'b }} - 'b

(I borrowed your notation here.)

Here it automatically infers the type for g ('a - Int - 'b) just
from its _usage_ inside f, as if there were a type class definition
like:

class G a where
  g :: a - Int - b

So not only we don't need to defined type classes, we don't even need
to declare the principle types of the overloaded functions. We can
infer them from their usage and they don't even need to have the same
principle type! All it takes is:

overload g

And even this is not really necessary. It is for sanity purposes - to
avoid inadvertent overloading.

So if g is used as:

f x y (Int z) = g x z y

then f has type 'a - 'b - Int - {{ g :: 'a - Int - 'b - 'c}} - 'c

Then g will be equivalent to the one you would have defined in a MPTC method.


 I would definitely argue against treating undefined variables as
 overloaded automatically. It seems this will lead to strange errors if
 you write typo's for example.

I agree, thus I will keep the overload keyword and check that the
unbound variables have been declared as overloaded before generating
the implicit argument.


 But the automatic overloading of the undefined may be useful in
 certain situations. For example, if we are going to use Haskell as a
 shell language. Every “command” must be evaluated when we type them.
 If we have mutually recursive definitions, the shell will report
 “undefined variables” either way we order the functions. The automatic
 overloading may solve this problem. The undefined

Re: [Haskell-cafe] decoupling type classes

2012-01-14 Thread Yin Wang
On Sat, Jan 14, 2012 at 2:38 PM, Dominique Devriese
dominique.devri...@cs.kuleuven.be wrote:
 I may or may not have thought about it. Maybe you can give an example
 of parametric instances where there could be problems, so that I can
 figure out whether my system works on the example or not.

 The typical example would be

 instance Eq a = Eq [a] where
  [] == [] = True
  (a : as) == (b : bs) = a == b  as == bs
  _ == _ = False

It can handle this case, although it doesn't handle it as a parametric
instance. I suspect that we don't need the concept of parameter
instances at all. We just searches for instances recursively at the
call site:

1. If g has an implicit parameter f, search for values which
matches the name and instantiated type in the current scope.

2. If a value is found, use it as the argument.

3. Check if the value is a function with implicit parameters, if so,
search for values that matches the name and type of the implicit
parameters.

4. Do this recursively until no more arguments contain implicit parameters.


 This coupling you talk about is not actually there for instance
 arguments. Instance arguments are perfectly usable without records.
 There is some special support for automatically constructing record
 projections with instance arguments though.

Cool. So it seems to be close to what I had in mind.


 I am not sure about the exact workings of your system, but I want to
 point out that alternative choices can be made about the workings of
 inferencing and resolving type-class instances such that local
 instances can be allowed. For example, in Agda, we do not infer
 instance arguments and we give an error in case of ambiguity, but
 because of this, we can allow local instances...

Certainly it should report error when there are ambiguities, but
sometimes it should report an error even there is only one value that
matches the name and type. For example,

foo x =
  let overload bar (x:Int) = x + 1
  in \() - bar x


baz =
 in foo (1::Int)

Even if we have only one definition of bar in the program, we should
not resolve it to the definition of bar inside foo. Because that
bar is not visible at the call site foo (1::int). We should report
an error in this case. Think of bar as a typed dynamically scoped
variable helps to justify this decision.

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


Re: [Haskell-cafe] decoupling type classes

2012-01-12 Thread Dominique Devriese
Yin,

2012/1/12 Yin Wang yinwa...@gmail.com:
 I have an idea about type classes that I have been experimenting. It
 appears to be a generalization to Haskell’s type classes and seems to
 be doable. It seems to related the three ideas: type classes, implicit
 parameters, and (typed) dynamic scoping. But I don't know whether it
 is good or not. I hope to get some opinions before going further.

I find your ideas interesting. You may be interested in a related
design which I recently implemented for Agda [2], and an ICFP 2011
paper that presents it [1].

Also, you don't seem to have thought about the question of parametric
instances: do you allow them or not, if you do, what computational
power do they get etc.?

 I have an experimental system which “decouples” the dictionary.
 Instead of passing on a dictionary, it passes individual “implicit
 parameters around. Those implicit parameters are type inferenced and
 they can contain type parameters just as methods in a type class.
 Similarly, they are resolved by their types in the call site's scope.

I'm surprised that you propose passing all type class methods
separately. It seems to me that for many type classes, you want to
impose a certain correspondence between the types of the different
methods in a type class (for example, for the Monad class, you would
expect return to be of type (a - m a) if (=) is of type (m a - (a
- m b) - m b)). I would expect that inferencing these releations in
each function that uses either of the methods will lead to overly
general inferenced types and the need for more guidance to the type
inferencer?

By separating the methods, you would also lose the laws that associate
methods in a type class, right?

An alternative to what you suggest, is the approach I recommend for
using instance arguments: wrapping all the methods in a standard data
type (i.e. define the dictionary explicitly), and pass this around as
an implicit argument.

 The convenience of this approach compared to Haskell’s type classes is
 that we no longer require a user of a type class to define ALL the
 methods in a type class. For example, a user could just define a
 method + without defining other methods in the Num class: -, *, … He
 can use the method + independently. For example, if + is defined on
 the String type to be concatenation, we can use + in another function:

 weirdConcat x y = x + y + y

 This has a utility, because the methods in the Num class don’t “make
 sense” for Strings except +, but the current type class design
 requires us to define them. Note here that weirdConcat will not have
 the type (Num a) = a - a - a, since we no longer have the Num
 class, it is decoupled into separate methods.

For this example, one might also argue that the problem is in fact
that the Num type class is too narrow, and + should instead be defined
in a parent type class (Monoid comes to mind) together with 0 (which
also makes sense for strings, by the way)?

 There is another benefit of this decoupling: it can subsume the
 functionality of MPTC. Because the methods are no longer grouped,
 there is no “common” type parameter to the methods. Thus we can easily
 have more than one parameter in the individual methods and
 conveniently use them as MPTC methods.

Could you explain this a bit further?

 Here g is explicitly declared as “overloaded”, although my
 experimental system doesn’t need this. Any undefined variable inside
 function body automatically becomes overloaded. This may cause
 unintended overloading and it catches bugs late. That’s why we need
 the “overload” declarations.

I would definitely argue against treating undefined variables as
overloaded automatically. It seems this will lead to strange errors if
you write typo's for example.

 But the automatic overloading of the undefined may be useful in
 certain situations. For example, if we are going to use Haskell as a
 shell language. Every “command” must be evaluated when we type them.
 If we have mutually recursive definitions, the shell will report
 “undefined variables” either way we order the functions. The automatic
 overloading may solve this problem. The undefined variables will
 temporarily exist as automatic overloaded functions. Once we actually
 define a function with the same name AND satisfies the type
 constraints, they become implicit parameters to the function we
 defined before. If we call a function whose implicit parameters are
 not associated, the shell reports error very similar to Haskell’s
 “type a is not of class Num …”

The design you suggest seems to differ from Haskell's current
treatment, where functions can refer to other functions defined
further in the file, but still have them resolved statically?

 RELATIONSHIP TO DYNAMIC SCOPING

 It seems to be helpful to think of the “method calls” as referencing
 dynamically scoped variables. They are dispatched depending on the
 bindings we have in the call site's scope (and not the scope where the
 method is defined!). So

[Haskell-cafe] decoupling type classes

2012-01-11 Thread Yin Wang
Hi all,

I have an idea about type classes that I have been experimenting. It
appears to be a generalization to Haskell’s type classes and seems to
be doable. It seems to related the three ideas: type classes, implicit
parameters, and (typed) dynamic scoping. But I don't know whether it
is good or not. I hope to get some opinions before going further.

Basically, Haskell’s type classes passes dictionaries around. Each
dictionary contains one or more “methods”. When “names” which belong
to a dictionary are called, we invoke functions that match its
principle type in the call site's scope.

I have an experimental system which “decouples” the dictionary.
Instead of passing on a dictionary, it passes individual “implicit
parameters around. Those implicit parameters are type inferenced and
they can contain type parameters just as methods in a type class.
Similarly, they are resolved by their types in the call site's scope.

The convenience of this approach compared to Haskell’s type classes is
that we no longer require a user of a type class to define ALL the
methods in a type class. For example, a user could just define a
method + without defining other methods in the Num class: -, *, … He
can use the method + independently. For example, if + is defined on
the String type to be concatenation, we can use + in another function:

weirdConcat x y = x + y + y

This has a utility, because the methods in the Num class don’t “make
sense” for Strings except +, but the current type class design
requires us to define them. Note here that weirdConcat will not have
the type (Num a) = a - a - a, since we no longer have the Num
class, it is decoupled into separate methods.

There is another benefit of this decoupling: it can subsume the
functionality of MPTC. Because the methods are no longer grouped,
there is no “common” type parameter to the methods. Thus we can easily
have more than one parameter in the individual methods and
conveniently use them as MPTC methods.



SOME IMPLEMENTATION DETAILS

Here is how it can be implemented. When we see an “undefined” variable
in a function definition which has been declared as “overloaded
function”, we store the function name, and the type variables that are
associated with it. For example,

overload g — (explicitly declare g as an overloaded function)

f x y (String s) = …
…
let z = g x s y in
…
…

We don’t know what x and y are, but we know from the body of f that
their types satisfy this pattern: g ’a String ’b. Thus we store this
pattern constraint as an extra (implicit) argument in the type of f:

f :: a → b → String (exist g: g a String b)

We may have multiple such arguments.

At the call sites of f, we look for a function g in the scope that
satisfies the pattern g ‘a String ’b, but we don’t pass on the
substitution, so they remain polymorphic. Once found, the function is
passed as an extra parameter to f. This is essentially dictionary
passing, but without grouping. It can be also more efficient because
the parameters may be stored in registers.

Here g is explicitly declared as “overloaded”, although my
experimental system doesn’t need this. Any undefined variable inside
function body automatically becomes overloaded. This may cause
unintended overloading and it catches bugs late. That’s why we need
the “overload” declarations.

But the automatic overloading of the undefined may be useful in
certain situations. For example, if we are going to use Haskell as a
shell language. Every “command” must be evaluated when we type them.
If we have mutually recursive definitions, the shell will report
“undefined variables” either way we order the functions. The automatic
overloading may solve this problem. The undefined variables will
temporarily exist as automatic overloaded functions. Once we actually
define a function with the same name AND satisfies the type
constraints, they become implicit parameters to the function we
defined before. If we call a function whose implicit parameters are
not associated, the shell reports error very similar to Haskell’s
“type a is not of class Num …”


RELATIONSHIP TO DYNAMIC SCOPING

It seems to be helpful to think of the “method calls” as referencing
dynamically scoped variables. They are dispatched depending on the
bindings we have in the call site's scope (and not the scope where the
method is defined!). So it is very much similar to the much-hated
dynamic scoping. But the dispatching is more disciplined — it doesn't
just match the name. It must match both the name and the inferred
principle type.

This intuition also explains why local instances shouldn't be allowed,
because if we capture the variables at the definition site, the method
call becomes statically scoped.



-- yin

___
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] Do type classes have a partial order?

2011-11-14 Thread Patrick Browne
Is there a partial order on Haskell type classes?If so, does it induce any quasi-order relation on types named in the instances?In the example below types C and D have the same operation fThanks,Patdata C = C deriving Showdata D = D deriving Showclass A t where f::t-t f t = t instance A C whereinstance A D whereclass A t = B t whereinstance B C whereinstance B D where

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


Re: [Haskell-cafe] Do type classes have a partial order?

2011-11-14 Thread Ling Yang
It seems like you would, going by semantics of System F, where types
with type variables name a certain subset of types, = constraints
further restrict the types of the same shape (are they an
independent kind of restriction?),  so typeclass declarations
with/without = specify a partial order over types because the subset
relation is.

On Mon, Nov 14, 2011 at 3:47 AM, Patrick Browne patrick.bro...@dit.ie wrote:
 Is there a partial order on Haskell type classes?
 If so, does it induce any quasi-order relation on types named in the
 instances?
 In the example below types C and D have the same operation f
 Thanks,
 Pat

 data C = C deriving Show
 data D = D deriving Show

 class A t where
  f::t-t
  f t = t

 instance A C where
 instance A D where


 class A t = B t where

 instance B C where
 instance B D where

 ___
 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


[Haskell-cafe] Simple GADTs, type families and type classes combination with type error.

2011-07-22 Thread Serguey Zefirov
Why does GHC complains on the code below ? (I'll explain in a second a
requirement to do just so)

I get errors with ghc 6.12.1 and 7.0.2.

-
{-# LANGUAGE GADTs, TypeFamilies #-}

class CPU cpu where
type CPUFunc cpu

data Expr cpu where
EVar :: String - Expr cpu
EFunc :: CPU cpu = CPUFunc cpu - Expr cpu

class CPU cpu = FuncVars cpu where
funcVars :: CPUFunc cpu - [String]

exprVars :: FuncVars cpu = Expr cpu - [String]
exprVars (EVar v) = [v]
-- an offending line:
exprVars (EFunc f) = funcVars f
-

I tried to split creation and analysis constraints. CPU required for
creation of expressions, FuncVars required for analysis. It all looks
nice but didn't work.

(In our real code EVar is slightly more complicated, featuring Var
cpu argument)

It looks like GHC cannot relate parameters inside and outside of
GADT constructor.

Not that I hesitate to add a method to a CPU class, but I think it is
not the right thing to do. So if I can split my task into two classes,
I will feel better.

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


Re: [Haskell-cafe] Simple GADTs, type families and type classes combination with type error.

2011-07-22 Thread Felipe Almeida Lessa
On Fri, Jul 22, 2011 at 12:12 PM, Serguey Zefirov sergu...@gmail.com wrote:
 Why does GHC complains on the code below ? (I'll explain in a second a
 requirement to do just so)

I don't why =(.  But you can workaround by using

  class CPU cpu where
data CPUFunc cpu

Note that you don't need the class constraint 'CPU cpu =' inside the
GADT since 'cpu' is not an existential.

Cheers, =)

-- 
Felipe.

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


Re: [Haskell-cafe] Simple GADTs, type families and type classes combination with type error.

2011-07-22 Thread Dan Doel
On Fri, Jul 22, 2011 at 11:12 AM, Serguey Zefirov sergu...@gmail.com wrote:
 -
 {-# LANGUAGE GADTs, TypeFamilies #-}

 class CPU cpu where
        type CPUFunc cpu

 data Expr cpu where
        EVar :: String - Expr cpu
        EFunc :: CPU cpu = CPUFunc cpu - Expr cpu

 class CPU cpu = FuncVars cpu where
        funcVars :: CPUFunc cpu - [String]

 exprVars :: FuncVars cpu = Expr cpu - [String]
 exprVars (EVar v) = [v]
 -- an offending line:
 exprVars (EFunc f) = funcVars f
 -

 I tried to split creation and analysis constraints. CPU required for
 creation of expressions, FuncVars required for analysis. It all looks
 nice but didn't work.

 (In our real code EVar is slightly more complicated, featuring Var
 cpu argument)

 It looks like GHC cannot relate parameters inside and outside of
 GADT constructor.

 Not that I hesitate to add a method to a CPU class, but I think it is
 not the right thing to do. So if I can split my task into two classes,
 I will feel better.

GHC cannot decide what instance of FuncVars to use. The signature of
funcVars is:

funcVars :: FuncVars cpu = CPUFunc cpu - [String]

This does not take any arguments that allow cpu to be determined. For
instance, if there were instances (rolling them into one declaration
for simplicity):

instance FuncVars Int where
  type CPUFunc Int = Int
  ...

instance FuncVars Char where
  type CPUFunc Char = Int

Then GHC would see that CPUFunc cpu = Int, but from this, it cannot
determine whether cpu = Int or cpu = Char. CPUFunc is not
(necessarily) injective.

Making CPUFunc a data family as Felipe suggested fixes this by CPUFunc
essentially being a constructor of types, not a function that
computes. So it would be impossible for CPUFunc a = CPUFunc b unless a
= b.

Also, if you have a class whose only content is an associated type,
there's really no need for the class at all. It desugars into:

type family CPUFunc a :: *

class CPU a

So it's just a type family and an empty class, which will all have
exactly the same cases defined. You could instead use just the family.

-- Dan

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


Re: [Haskell-cafe] Simple GADTs, type families and type classes combination with type error.

2011-07-22 Thread aditya siram
I just had a problem closely related to this on StackOverflow [1]
which was explained beautifully by cammcann.

The problem is that because type CPUFunc cpu is located inside the
definition of the class CPU it creates the illusion that they are
somehow tied together where CPUFunc is somehow in the CPU
namespace. It isn't. CPUFunc is actually defined globally and the
compiler would complain if you tried to create a CPUFunc type anywhere
else in your code.

The solution is the make CPUFunc a brand new datatype by changing
type CPUFunc cpu to data CPUFunc cpu .

-deech


[1] 
http://stackoverflow.com/questions/6663547/writing-a-function-polymorphic-in-a-type-family

On Fri, Jul 22, 2011 at 10:12 AM, Serguey Zefirov sergu...@gmail.com wrote:
 Why does GHC complains on the code below ? (I'll explain in a second a
 requirement to do just so)

 I get errors with ghc 6.12.1 and 7.0.2.

 -
 {-# LANGUAGE GADTs, TypeFamilies #-}

 class CPU cpu where
        type CPUFunc cpu

 data Expr cpu where
        EVar :: String - Expr cpu
        EFunc :: CPU cpu = CPUFunc cpu - Expr cpu

 class CPU cpu = FuncVars cpu where
        funcVars :: CPUFunc cpu - [String]

 exprVars :: FuncVars cpu = Expr cpu - [String]
 exprVars (EVar v) = [v]
 -- an offending line:
 exprVars (EFunc f) = funcVars f
 -

 I tried to split creation and analysis constraints. CPU required for
 creation of expressions, FuncVars required for analysis. It all looks
 nice but didn't work.

 (In our real code EVar is slightly more complicated, featuring Var
 cpu argument)

 It looks like GHC cannot relate parameters inside and outside of
 GADT constructor.

 Not that I hesitate to add a method to a CPU class, but I think it is
 not the right thing to do. So if I can split my task into two classes,
 I will feel better.

 ___
 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] Simple GADTs, type families and type classes combination with type error.

2011-07-22 Thread Serguey Zefirov
2011/7/22 Dan Doel dan.d...@gmail.com:
 On Fri, Jul 22, 2011 at 11:12 AM, Serguey Zefirov sergu...@gmail.com wrote:
 GHC cannot decide what instance of FuncVars to use. The signature of
 funcVars is:
    funcVars :: FuncVars cpu = CPUFunc cpu - [String]

 This does not take any arguments that allow cpu to be determined. For
 instance, if there were instances (rolling them into one declaration
 for simplicity):

    instance FuncVars Int where
      type CPUFunc Int = Int
      ...

    instance FuncVars Char where
      type CPUFunc Char = Int

 Then GHC would see that CPUFunc cpu = Int, but from this, it cannot
 determine whether cpu = Int or cpu = Char. CPUFunc is not
 (necessarily) injective.

But cpu variable is the same in all places. If we don't dive into
CPUFunc reduction (to Int or whatever) we can safely match funcVars
argument and unify cpu.

This is the case when we write generic functions over type family application.

 Also, if you have a class whose only content is an associated type,
 there's really no need for the class at all. It desugars into:

    type family CPUFunc a :: *

    class CPU a

It would be somewhat inconvenient. I omitted some constraints in CPU
class for the sake of presentation.

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


Re: [Haskell-cafe] Simple GADTs, type families and type classes combination with type error.

2011-07-22 Thread Serguey Zefirov
2011/7/22 Felipe Almeida Lessa felipe.le...@gmail.com:
 On Fri, Jul 22, 2011 at 12:12 PM, Serguey Zefirov sergu...@gmail.com wrote:
 Why does GHC complains on the code below ? (I'll explain in a second a
 requirement to do just so)

 I don't why =(.  But you can workaround by using

  class CPU cpu where
    data CPUFunc cpu


Thank you very much. I completely forgot that.

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


Re: [Haskell-cafe] Simple GADTs, type families and type classes combination with type error.

2011-07-22 Thread Dan Doel
On Fri, Jul 22, 2011 at 4:11 PM, Serguey Zefirov sergu...@gmail.com wrote:
 But cpu variable is the same in all places. If we don't dive into
 CPUFunc reduction (to Int or whatever) we can safely match funcVars
 argument and unify cpu.

 This is the case when we write generic functions over type family application.

Here is approximately what the checking algorithm knows in the problematic case:

  exprVars (EFunc f) = funcVars f

  exprVars :: FuncVars cpu1 = Expr cpu1 - [String]
  EFunc f :: Expr cpu1
  funcVars :: FuncVars cpu2 = CPUFunc cpu2 - [String]
  f :: CPUFunc cpu1

Thus, it can determine:

  CPUFunc cpu2 = CPUFunc cpu1

Now it needs to decide which instance of FuncVars to feed to funcVars.
But it only knows that cpu2 should be such that the above type
equation holds. However, since CPUFunc is a type family, it is not
sound in general to reason from:

  CPUFunc cpu1 = CPUFunc cpu2

to:

  cpu1 = cpu2

So the type checker doesn't. You have nothing there that determines
cpu1 to be the same as cpu2. So you need to make some change that does
determine them to be the same.

In situations like these, it would be handy if there were a way to
specify what type certain variables are instantiated to, but it's sort
of understandable that there isn't, because it'd be difficult to do in
a totally satisfactory way.

-- Dan

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


Re: [Haskell-cafe] Can it be proven there are no intermediate useful type classes between Applicative Functors Monads?

2011-06-07 Thread wren ng thornton

On 6/6/11 7:05 PM, Casey McCann wrote:

On Mon, Jun 6, 2011 at 5:32 PM, Matthew Steelemdste...@alum.mit.edu  wrote:

branchApplicative = liftA3 (\b t f -  if b then t else f)


This definition doesn't satisfy the laws given for the Branching
class; it will execute the effects of both branches regardless of
which is chosen.


How would it violate the laws for Identity or Reader?


It wouldn't violate the laws for those (or other benign effects, given a 
suitable definition of benign), but it'd clearly violate the laws for 
things like Writer, ST, IO,...


--
Live well,
~wren

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


Re: [Haskell-cafe] Can it be proven there are no intermediate useful type classes between Applicative Functors Monads?

2011-06-07 Thread David Barbour
On Sun, Jun 5, 2011 at 12:51 PM, KC kc1...@gmail.com wrote:

 If new intermediate classes crop up then there would be no point in fixing

 class (Applicative m) = Monad m where

 since it would have to be changed if new intermediate classes are found.


You might check out a few articles regarding Kleisli arrows [1][2] for
possibilities that live between applicative and monad.

Applicative itself is also a little on the strong side. I had to reject
Applicative for one model of signal transformers because 'pure' was not a
legal constructor, even though 'fmap . const' and '*' were okay. And even
Functor is too strong if you want effective linearity. I've found Adam
Megacz's Generalized Arrows [3] to be a suitable chassis for weaker models.

[1] http://www.haskell.org/haskellwiki/Arrow_tutorial#Kleisli_Arrows
[2] http://lambda-the-ultimate.org/node/4273
[3] http://www.cs.berkeley.edu/~megacz/garrows/
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Can it be proven there are no intermediate useful type classes between Applicative Functors Monads?

2011-06-07 Thread David Barbour
On Mon, Jun 6, 2011 at 4:05 PM, Casey McCann syntaxgli...@gmail.com wrote:

 ArrowChoice and ArrowApply are conceptually distinct and I expect
 there are instances of the former that have no possible instance for
 the latter. Branching vs. Monad I am much less certain of.


For a real-time or embedded DSL, or hardware modeling, you could easily
desire 'Branching' and limited 'Loop' classes while rejecting the full power
of Monads.


 some type that's not obviously equivalent to one of these definitions:
   branchMonad mb t f = do { b - mb; if b then t else f }
   branchApplicative = liftA3 (\b t f - if b then t else f)


Earlier forms of my reactive demand programming model [1] - before I
switched to arrows - would qualify. The model has limited side-effects (e.g.
power a camera on only when someone is observing it) so we cannot use
branchApplicative. The reactivity requires continuously weaving the two
branches over time and recombining the results, which is distinct from
branchMonad.

[1] http://awelonblue.wordpress.com/2011/05/21/comparing-frp-to-rdp/
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Can it be proven there are no intermediate useful type classes between Applicative Functors Monads?

2011-06-07 Thread David Barbour
On Tue, Jun 7, 2011 at 6:14 AM, Casey McCann syntaxgli...@gmail.com wrote:

 On Mon, Jun 6, 2011 at 7:55 PM, David Barbour dmbarb...@gmail.com wrote:
  Earlier forms of my reactive demand programming model [1] - before I
  switched to arrows - would qualify. The model has limited side-effects
 (e.g.
  power a camera on only when someone is observing it) so we cannot use
  branchApplicative. The reactivity requires continuously weaving the two
  branches over time and recombining the results, which is distinct from
  branchMonad.

 Oh, very nice, thank you. I'd actually suspected that models of
 reactive behavior might be a case where the distinction is meaningful.
 I do still wonder if there's something roughly equivalent to the
 (grossly inefficient and unusable, but producing the same results
 otherwise) monad instance for zipping infinite streams, but I don't
 have time to work through it right now to be sure...


The main trouble with using monads directly is that they're simply too
powerful. Monads allow ad-hoc joins and loops based on data. The number of
reactive relationships during any given instant can vary widely and
unpredictably based on data. This makes it difficult to maintain stable
relationships over continuous time. Looping and Branching must be carefully
managed in my reactive model in order to gain stability over time that
Monads do not possess.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Non-advanced usage of Type classes

2011-06-07 Thread Arnaud Bailly
Hello,
In a recent thread, it has been asserted that defining type class is
something you seldom need when programming in Haskell.

There is one thing that as non-professional Haskell programmer I found
type-classes useful for: Testing. This is probably very OO and is pretty
much influenced by what I read in RWH but I find useful to define TC that
abstract away from low-level interactions with other code, possibly IO
related, in such a way that I can have one implementation for testing and
one implementation for real work that is wired in caller context. This is
what is called mockist TDD in some circles: Write code that expresses what
it needs in its own terms, then implement glue to the code that provide
the concrete behaviour.

For example, while designing some program (a game...) I defined a type class
thus:

 class (Monad io) = CommandIO io where
  readCommand  :: io Command
  writeResult  :: CommandResult - io ()

Then I defined in a module Commands.IO :

 instance CommandIO IO where
  readCommand = do input - getLine
  ...
 writeResult r = putStrLn $ show r

and for the purpose of testing I defined in some test module:

 instance CommandIO (S.State ([Command],[CommandResult])) where
   readCommand   = do ((c:cs),rs) - S.get
 
   writeResult r = do (cs,rs) - S.get
 ...

Is this badly designed  code that tries to mimic OO in a functional setting?
If the answer is yes, how could I achieve same result (eg. testing the code
that does command REPL) without defining type classes?

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


Re: [Haskell-cafe] Non-advanced usage of Type classes

2011-06-07 Thread Evan Laforge
 Is this badly designed  code that tries to mimic OO in a functional setting?
 If the answer is yes, how could I achieve same result (eg. testing the code
 that does command REPL) without defining type classes?

Here's how I do it:

data InteractiveState = InteractiveState {
  state_read :: IO Command
  , state_write :: Result - IO ()
  }

Now when I run it for real, I pass 'InteractiveState getLine putStrLn'
and when I run it for testing, I pass 'InteractiveState (getChan
in_chan) (putChan out_chan)'.

Of course, you have to pass this InteractiveState around, but
hopefully your IO using section is restricted to a small event loop
and threading it through is not a burden.  And there's always StateT.

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


Re: [Haskell-cafe] Non-advanced usage of Type classes

2011-06-07 Thread Arnaud Bailly
On Tue, Jun 7, 2011 at 10:32 PM, Evan Laforge qdun...@gmail.com wrote:

  Is this badly designed  code that tries to mimic OO in a functional
 setting?
  If the answer is yes, how could I achieve same result (eg. testing the
 code
  that does command REPL) without defining type classes?

 Here's how I do it:

 data InteractiveState = InteractiveState {
  state_read :: IO Command
  , state_write :: Result - IO ()
  }


How about :

 data InteractiveState io = InteractiveState {
 state_read :: io Command
 , state_write :: Result - io ()
 }

Then you don't even depend on some specific monad. I understand you can
always (always?) encapsulate what is done through a type class by using a
data containing functions. But then, is this not even closer to OO
programming, an object that carries its own methods with itself, possibly
with the additional overhead that *each* instance would have its own private
references to possibly identical functions.

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


Re: [Haskell-cafe] Non-advanced usage of Type classes

2011-06-07 Thread Evan Laforge
 Here's how I do it:

 data InteractiveState = InteractiveState {
  state_read :: IO Command
  , state_write :: Result - IO ()
  }


 How about :

 data InteractiveState io = InteractiveState {
 state_read :: io Command
 , state_write :: Result - io ()
 }

I guess you could, but I like it concrete.

 Then you don't even depend on some specific monad. I understand you can
 always (always?) encapsulate what is done through a type class by using a
 data containing functions. But then, is this not even closer to OO
 programming, an object that carries its own methods with itself, possibly
 with the additional overhead that *each* instance would have its own private
 references to possibly identical functions.

No, because I don't think there are any objects?  In fact, I'm not
even sure what you mean.  I'm assuming you have an event loop like:

event_loop st = do
  cmd - state_read st
  state_write st (calculate_response cmd)
  event_loop st

calculate_response :: Command - Result

Since 'st' never changes (in my case it does have some changing
values), you can just write:

event_loop st = forever $ state_write st = calculate_response $
state_read st

There are no objects or private references here, and I'm not even sure
what they mean in this context.

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


Re: [Haskell-cafe] Non-advanced usage of Type classes

2011-06-07 Thread Brandon Allbery
On Tue, Jun 7, 2011 at 16:16, Arnaud Bailly arnaud.oq...@gmail.com wrote:
 For example, while designing some program (a game...) I defined a type class
 thus:

 class (Monad io) = CommandIO io where
  readCommand  :: io Command
  writeResult  :: CommandResult - io ()

This is in fact one of the reasons to use type classes.  In fact,
you'll find a somewhat more general variety of it on Hackage in a
couple of forms, the one I'm most familiar with being MonadPrompt.

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


Re: [Haskell-cafe] Non-advanced usage of Type classes

2011-06-07 Thread Yves Parès
 Is this badly designed  code that tries to mimic OO in a functional
setting? If the answer is yes, how could I achieve same result (eg. testing
the code that does command REPL) without defining type classes?

Why would that be badly designed? And why would that be more OO? IMO it is a
perfectly suited usage of type classes.

 Here's how I do it:

 data InteractiveState = InteractiveState {
  state_read :: IO Command
 , state_write :: Result - IO ()
 }

Well, it's pretty much the same thing, except you explicitely carry a value
containing your methods instead of simply carrying a type. Plus it delays
the resolution of which function will be called to the execution.
With typeclasses, it will be determined statically, no need to carry the
functions.


2011/6/7 Arnaud Bailly arnaud.oq...@gmail.com

 Hello,
 In a recent thread, it has been asserted that defining type class is
 something you seldom need when programming in Haskell.

 There is one thing that as non-professional Haskell programmer I found
 type-classes useful for: Testing. This is probably very OO and is pretty
 much influenced by what I read in RWH but I find useful to define TC that
 abstract away from low-level interactions with other code, possibly IO
 related, in such a way that I can have one implementation for testing and
 one implementation for real work that is wired in caller context. This is
 what is called mockist TDD in some circles: Write code that expresses what
 it needs in its own terms, then implement glue to the code that provide
 the concrete behaviour.

 For example, while designing some program (a game...) I defined a type
 class thus:

  class (Monad io) = CommandIO io where
   readCommand  :: io Command
   writeResult  :: CommandResult - io ()

 Then I defined in a module Commands.IO :

  instance CommandIO IO where
   readCommand = do input - getLine
   ...
  writeResult r = putStrLn $ show r

 and for the purpose of testing I defined in some test module:

  instance CommandIO (S.State ([Command],[CommandResult])) where
readCommand   = do ((c:cs),rs) - S.get
  
writeResult r = do (cs,rs) - S.get
  ...

 Is this badly designed  code that tries to mimic OO in a functional
 setting? If the answer is yes, how could I achieve same result (eg. testing
 the code that does command REPL) without defining type classes?

 Regards,
 Arnaud



 ___
 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] Non-advanced usage of Type classes

2011-06-07 Thread Yves Parès
...and the other one being operational (which I find simpler).


2011/6/8 Brandon Allbery allber...@gmail.com

 On Tue, Jun 7, 2011 at 16:16, Arnaud Bailly arnaud.oq...@gmail.com
 wrote:
  For example, while designing some program (a game...) I defined a type
 class
  thus:
 
  class (Monad io) = CommandIO io where
   readCommand  :: io Command
   writeResult  :: CommandResult - io ()

 This is in fact one of the reasons to use type classes.  In fact,
 you'll find a somewhat more general variety of it on Hackage in a
 couple of forms, the one I'm most familiar with being MonadPrompt.

 ___
 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] Can it be proven there are no intermediate useful type classes between Applicative Functors Monads?

2011-06-06 Thread Brent Yorgey
On Sun, Jun 05, 2011 at 12:51:47PM -0700, KC wrote:
 If new intermediate classes crop up then there would be no point in fixing
 
 class (Applicative m) = Monad m where
 
 since it would have to be changed if new intermediate classes are
 found.

There actually is at least one intermediate class that I know of,

  class Applicative m = Branching m where
branch :: m Bool - m a - m a - m a

subject to the laws

  branch (m * pure True)  t f == m * t
  branch (m * pure False) t f == m * f

or something like that.  The idea is that Applicative computations
have a fixed structure which is independent of intermediate results;
Monad computations correspond to (potentially) infinitely branching
trees, since intermediate results (which could be of an infinite-sized
type) can be used to compute the next action; but Branching
computations correspond to *finitely* branching trees, since future
computation can depend on intermediate results, but only one binary
choice at a time.

However, I doubt this qualifies as useful no matter how you define
it, although I would not be sad to be proven wrong.  In any case, I
think it is ethically indefensible to procrastinate in doing something
good just in case you might miss an opportunity to do something
perfect later.

-Brent

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


Re: [Haskell-cafe] Can it be proven there are no intermediate useful type classes between Applicative Functors Monads?

2011-06-06 Thread KC
On Mon, Jun 6, 2011 at 9:19 AM, Brent Yorgey byor...@seas.upenn.edu wrote:
 On Sun, Jun 05, 2011 at 12:51:47PM -0700, KC wrote:
 If new intermediate classes crop up then there would be no point in fixing

 class (Applicative m) = Monad m where

 since it would have to be changed if new intermediate classes are
 found.

 There actually is at least one intermediate class that I know of,

  class Applicative m = Branching m where
    branch :: m Bool - m a - m a - m a

 subject to the laws

  branch (m * pure True)  t f == m * t
  branch (m * pure False) t f == m * f

 or something like that.  The idea is that Applicative computations
 have a fixed structure which is independent of intermediate results;
 Monad computations correspond to (potentially) infinitely branching
 trees, since intermediate results (which could be of an infinite-sized
 type) can be used to compute the next action; but Branching
 computations correspond to *finitely* branching trees, since future
 computation can depend on intermediate results, but only one binary
 choice at a time.

 However, I doubt this qualifies as useful no matter how you define
 it, although I would not be sad to be proven wrong.  In any case, I
 think it is ethically indefensible to procrastinate in doing something
 good just in case you might miss an opportunity to do something
 perfect later.

 -Brent


I take it you would prefer the following signature

class (Applicative m) = Monad m where


-- 
--
Regards,
KC

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


Re: [Haskell-cafe] Can it be proven there are no intermediate useful type classes between Applicative Functors Monads?

2011-06-06 Thread Casey McCann
On Mon, Jun 6, 2011 at 12:19 PM, Brent Yorgey byor...@seas.upenn.edu wrote:
 The idea is that Applicative computations
 have a fixed structure which is independent of intermediate results;
 Monad computations correspond to (potentially) infinitely branching
 trees, since intermediate results (which could be of an infinite-sized
 type) can be used to compute the next action; but Branching
 computations correspond to *finitely* branching trees, since future
 computation can depend on intermediate results, but only one binary
 choice at a time.

Is this truly an intermediate variety of structure, though? Or just
different operations on existing structures? With Applicative, there
are examples of useful structures that truly can't work as a Monad,
the usual example being arbitrary lists with liftA2 (,) giving zip,
not the cartesian product. Do you know any examples of both:

1) Something with a viable instance for Branching, but either no Monad
instance, or multiple distinct Monad instances compatible with the
Branching instance
2) Same as above, except for a viable Applicative instance without a
single obvious Branching instance

In other words, an implementation of branch for some type that's not
obviously equivalent to one of these definitions:

branchMonad mb t f = do { b - mb; if b then t else f }
branchApplicative = liftA3 (\b t f - if b then t else f)

I can certainly believe that such an example exists, but I can't think
of one. In particular, it doesn't seem to be possible for ZipList (the
obvious almost-instance does not quite do what you may think it does).

If memory serves me, sometimes the limited nature of Applicative
allows a more efficient implementation than Monad, and in such cases I
can easily believe that branch could be made more efficient than the
generic form based on Monad. But that's not terribly persuasive for
creating a type class, I don't think.

- C.

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


Re: [Haskell-cafe] Can it be proven there are no intermediate useful type classes between Applicative Functors Monads?

2011-06-06 Thread Matthew Steele
On Mon, Jun 6, 2011 at 3:39 PM, Casey McCann syntaxgli...@gmail.com wrote:
 On Mon, Jun 6, 2011 at 12:19 PM, Brent Yorgey byor...@seas.upenn.edu wrote:
 The idea is that Applicative computations
 have a fixed structure which is independent of intermediate results;
 Monad computations correspond to (potentially) infinitely branching
 trees, since intermediate results (which could be of an infinite-sized
 type) can be used to compute the next action; but Branching
 computations correspond to *finitely* branching trees, since future
 computation can depend on intermediate results, but only one binary
 choice at a time.

 Is this truly an intermediate variety of structure, though? Or just
 different operations on existing structures? With Applicative, there
 are examples of useful structures that truly can't work as a Monad,
 the usual example being arbitrary lists with liftA2 (,) giving zip,
 not the cartesian product. Do you know any examples of both:

 1) Something with a viable instance for Branching, but either no Monad
 instance, or multiple distinct Monad instances compatible with the
 Branching instance

I think Branching is to Monad what ArrowChoice is to ArrowApply.
Branching allows the shape of the computation to depend on run-time
values (which you can't do with Applicative), but still allows only a
finite number of computation paths.  By purposely making a functor an
instance of Branching but _not_ of Monad, you allow it to have some
amount of run-time flexibility while still retaining the ability to
statically analyze the effects of a computation in that functor.

 branchApplicative = liftA3 (\b t f - if b then t else f)

This definition doesn't satisfy the laws given for the Branching
class; it will execute the effects of both branches regardless of
which is chosen.

Cheers,
-Matt

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


Re: [Haskell-cafe] Can it be proven there are no intermediate useful type classes between Applicative Functors Monads?

2011-06-06 Thread Casey McCann
On Mon, Jun 6, 2011 at 5:32 PM, Matthew Steele mdste...@alum.mit.edu wrote:
 I think Branching is to Monad what ArrowChoice is to ArrowApply.
 Branching allows the shape of the computation to depend on run-time
 values (which you can't do with Applicative), but still allows only a
 finite number of computation paths.  By purposely making a functor an
 instance of Branching but _not_ of Monad, you allow it to have some
 amount of run-time flexibility while still retaining the ability to
 statically analyze the effects of a computation in that functor.

Yes, that's what I gathered as well. It's a straightforward concept.

My question is whether there exist instances of Branching that are
distinct in results from an implementation in terms of a Monad
instance, rather than merely allowing a more efficient implementation.
Not that the latter isn't worthwhile, but to make a case for something
like Branching as an intermediate between Applicative and Monad one
would expect it to differ from both in what types have possible
instances.

ArrowChoice and ArrowApply are conceptually distinct and I expect
there are instances of the former that have no possible instance for
the latter. Branching vs. Monad I am much less certain of.

 branchApplicative = liftA3 (\b t f - if b then t else f)

 This definition doesn't satisfy the laws given for the Branching
 class; it will execute the effects of both branches regardless of
 which is chosen.

How would it violate the laws for Identity or Reader?

- C.

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


[Haskell-cafe] Can it be proven there are no intermediate useful type classes between Applicative Functors Monads?

2011-06-05 Thread KC
If new intermediate classes crop up then there would be no point in fixing

class (Applicative m) = Monad m where

since it would have to be changed if new intermediate classes are found.

I realize non-existence proofs are hard.

-- 
--
Regards,
KC

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


Re: [Haskell-cafe] Can it be proven there are no intermediate useful type classes between Applicative Functors Monads?

2011-06-05 Thread Ben Lippmeier

On 06/06/2011, at 5:51 , KC wrote:

 If new intermediate classes crop up then there would be no point in fixing
 
 class (Applicative m) = Monad m where
 
 since it would have to be changed if new intermediate classes are found.
 
 I realize non-existence proofs are hard.

Not as hard as formalising useful.

Ben.


___
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] Testing Implementation vs Model - Records or Type Classes?

2011-04-09 Thread Heinrich Apfelmus

Twan van Laarhoven wrote:

For reference, here the full signature of the core combinators:

data Event a
data Behavior a

instance Functor Behavior
instance Applicative Behavior
instance Functor Event
instance Monoid (Event a)

filter :: (a - Bool) - Event a - Event a
apply :: Behavior (a - b) - Event a - Event b
accumB :: a - Event (a - a) - Behavior a


The apply and accumB functions are harder. Is the Behavior 
implementation for the model really different from the one of the 
implementation, which seems to be {initial::a, changes::Event a}? If 
not, you could just generalize that type by making the event type a 
parameter


data GenBehavior e a = GB a (E a)

If this is not the case,


I have changed the both implementations completely, so this no longer an 
option.


then instead of MPTCs you could also try type 
families,


class ... = FRP event where
data Behavior event
apply :: Behavior event (a - b) - event a - event b
accumB :: a - event (a - a) - Behavior event a

I don't know whether this is any better than the MPTC approach, though.


Data type families have the advantage that I don't run into problems 
with ambiguity. The following seems sensible to me:


class (Functor (Event f), Functor (Behavior f),
   Applicative (Behavior f)) = FRP f where
apply :: Behavior f (a - b) - Event f a - Event f b
...

where  f  is simply a dummy variable to index different FRP implementations.

The problem with this is that I need the  FlexibleContexts  extension to 
do that. There goes Haskell2010 compatibility.



Best regards,
Heinrich Apfelmus

--
http://apfelmus.nfshost.com


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


  1   2   3   4   5   6   7   >