Type question in instance of a class

Hi, Why is this wrong? ---- class MyClass r where function :: r -> s data MyData u = MyData u instance MyClass (MyData v) where function (MyData a) = a ---- GHC says that the type of the result of 'function' is both determined by the "rigid type" from MyClass and the "rigid type" from MyData. But why can't both be the same? What am I doing wrong? Thanks for your help, Maurício

Hello Maurício, Monday, November 17, 2008, 12:32:11 AM, you wrote:
class MyClass r where function :: r -> s
this tells that f may return value of any type requested at the call site, i.e. one can write main = do print (f (Mydata 1) :: String) print (f (Mydata 1) :: [Bool]) print (f (Mydata 1) :: Either Double Float)
instance MyClass (MyData v) where function (MyData a) = a
this definition can return value of only one type, so it can't serve all the calls i mentioned above
GHC says that the type of the result of 'function' is both determined by the "rigid type" from MyClass and the "rigid type" from MyData. But why can't both be the same?
are you OOPer? :) ps: GHC error messages should be fired :) -- Best regards, Bulat mailto:Bulat.Ziganshin@gmail.com

On Mon, 2008-11-17 at 16:39 -0200, Maurício wrote:
(...)
GHC says that the type of the result of 'function' is both determined by the "rigid type" from MyClass and the "rigid type" from MyData. But why can't both be the same?
are you OOPer? :)
What is an OOPer?
Object-Oriented Programmer. A species that frequently finds Haskell type classes and polymorphism very confusing. (Hint: the similarity between Haskell type classes and OO classes pretty much begins and ends at the name. Similarly for Haskell/ML polymorphism and OO polymorphism. They have points of similarity, but on net the best plan is to simply never reason analogically from one to the other.) jcc

Jonathan Cast wrote:
[Functional and object-oriented programming] have points of similarity, but on net the best plan is to simply never reason analogically from one to the other.
Coming from the OO world, I found it very useful to see how the same solution is modeled using different paradigms. I don't recall where I found the following example, but copied it locally as compelling evidence that the functional solution can be much clearer and shorter than the same solution modeled with objects and inheritance. -- Arithmetic expression forms data Expr = Num Int | Add Expr Expr -- Evaluate expressions eval :: Expr -> Int eval (Num i) = i eval (Add l r ) = eval l + eval r -- Modify literals modulo v modn :: Expr -> Int -> Expr modn (Num i) v = Num (i 'mod' v) modn (Add l r) v = Add (modn l v) (modn r v) public abstract class Expr { public abstract int eval (); public abstract void modn(int v); } public class Num extends Expr { private int value; public Num(int value) { this.value = value; } public int eval () { return value; } public void modn(int v) { this.value = this.value % v; } public class Add extends Expr { private Expr left, right; public Add(Expr left, Expr right ) { this.left = left; this.right = right; } public int eval () { return left.eval () + right.eval (); } public void modn(int v) { left.modn(v); right.modn(v); } } -Greg

(...) I don't recall where I found the following example, but copied it locally as compelling evidence that the functional solution can be much clearer and shorter than the same solution modeled with objects and inheritance.
Greg, I desagree with you. Bjarne Stroustrup, the original creator of C++, is a sensible person and I share his peacefull opinion in this matter: http://www.research.att.com/~bs/bs_faq.html#compare Even with good intentions, I've never seen such kind of comparison not to fall into religious fights. (Although I'm not more than just a humble language user.)
-- Arithmetic expression forms data Expr = Num Int | Add Expr Expr
-- Evaluate expressions eval :: Expr -> Int (...)
public abstract class Expr { public abstract int eval (); public abstract void modn(int v);
Although I'm not good enough to judge anyone's Haskell code, the Haskell version seems nice. I don't know how someone who understands well object-oriented code would do that. But I did C++ until around 1998, when the first standard was set, and I can tell you for sure that, even at that time, no one who knows at least the basics of C++ would ever write that problem like this. Best, Maurício

On Mon, 2008-11-17 at 21:49 -0200, Maurício wrote:
(...) I don't recall where I found the following example, but copied it locally as compelling evidence that the functional solution can be much clearer and shorter than the same solution modeled with objects and inheritance.
Greg,
I desagree with you. Bjarne Stroustrup, the original creator of C++, is a sensible person
I think his creation of C++ is evidence against that view...
and I share his peacefull opinion in this matter:
http://www.research.att.com/~bs/bs_faq.html#compare
Even with good intentions, I've never seen such kind of comparison not to fall into religious fights.
How do you recommend selecting a language? Stroustrup, in my experience, seems to think the answer is `any method but technical merits', which would make me suspicious of the technical merits of his solution even if I knew nothing else about them (and I know all too much...). Ask yourself: what is he hiding?
-- Arithmetic expression forms data Expr = Num Int | Add Expr Expr
-- Evaluate expressions eval :: Expr -> Int (...)
public abstract class Expr { public abstract int eval (); public abstract void modn(int v);
Although I'm not good enough to judge anyone's Haskell code, the Haskell version seems nice. I don't know how someone who understands well object-oriented code would do that. But I did C++ until around 1998, when the first standard was set, and I can tell you for sure that, even at that time, no one who knows at least the basics of C++ would ever write that problem like this.
Of course not. But their solution wouldn't be object-oriented, either; this is just an example where OO solutions don't make sense. (And the example code is Java; I've been wracking my brain, but I can't come up with any other way to do it in that language). jcc

On Mon, 2008-11-17 at 16:04 -0800, Jonathan Cast wrote:
On Mon, 2008-11-17 at 21:49 -0200, Maurício wrote:
(...) I don't recall where I found the following example, but copied it locally as compelling evidence that the functional solution can be much clearer and shorter than the same solution modeled with objects and inheritance.
Greg,
I desagree with you. Bjarne Stroustrup, the original creator of C++, is a sensible person
I think his creation of C++ is evidence against that view...
and I share his peacefull opinion in this matter:
http://www.research.att.com/~bs/bs_faq.html#compare
Even with good intentions, I've never seen such kind of comparison not to fall into religious fights.
How do you recommend selecting a language? Stroustrup, in my experience, seems to think the answer is `any method but technical merits', which would make me suspicious of the technical merits of his solution even if I knew nothing else about them (and I know all too much...). Ask yourself: what is he hiding?
-- Arithmetic expression forms data Expr = Num Int | Add Expr Expr
-- Evaluate expressions eval :: Expr -> Int (...)
public abstract class Expr { public abstract int eval (); public abstract void modn(int v);
Although I'm not good enough to judge anyone's Haskell code, the Haskell version seems nice. I don't know how someone who understands well object-oriented code would do that. But I did C++ until around 1998, when the first standard was set, and I can tell you for sure that, even at that time, no one who knows at least the basics of C++ would ever write that problem like this.
Of course not. But their solution wouldn't be object-oriented, either; this is just an example where OO solutions don't make sense. (And the example code is Java; I've been wracking my brain, but I can't come up with any other way to do it in that language).
Jonathan is spot on. The OO solution is an elegant approach. I can definitely see a C++ programmer writing it. If they didn't write it that way, it would be because, as Jonathan says, they didn't use an OOP approach. Note that this particular example is usually used to show the duality between FP and OOP. To add a prettyPrint function to the FP version, one need simply write another function while the OOP version will require changes to all the classes. To add a Mul constructor to the OOP version, one need simply write another class while the FP version will require changes to all the functions. This example illustrates (and is the namesake of) the expression problem.

On Mon, Nov 17, 2008 at 9:49 PM, Maurício
(...) I don't recall where I found the following example, but copied it locally as compelling evidence that the functional solution can be much clearer and shorter than the same solution modeled with objects and inheritance.
Greg,
I desagree with you. Bjarne Stroustrup, the original creator of C++, is a sensible person and I share his peacefull opinion in this matter:
http://www.research.att.com/~bs/bs_faq.html#comparehttp://www.research.att.com/%7Ebs/bs_faq.html#compare
Even with good intentions, I've never seen such kind of comparison not to fall into religious fights. (Although I'm not more than just a humble language user.)
Functional languages are much more formalized than OO languages. The basics (i.e. lambda-calculus algebraic data-types, *morphisms) are well known and very composable. OO theory is a mess, classes and objects are different beasts on every OO language and they don't form an easily composable toolkit (e.g. the inheritance vs. composition debate, where to place methods, binary method choices). There are many (which by sheer amount of variance isn't a good sign) formalizations of OO but none that were well received by the most popular OOPLs (in contrast with FP theory and it's pervasiveness in FPLs). In this case it isn't a religious fight.
-- Arithmetic expression forms data Expr = Num Int | Add Expr Expr
-- Evaluate expressions eval :: Expr -> Int (...)
public abstract class Expr { public abstract int eval (); public abstract void modn(int v);
Although I'm not good enough to judge anyone's Haskell code, the Haskell version seems nice. I don't know how someone who understands well object-oriented code would do that. But I did C++ until around 1998, when the first standard was set, and I can tell you for sure that, even at that time, no one who knows at least the basics of C++ would ever write that problem like this.
Well, any OO programmer familiar with algebraic and coalgebraic datatypes would do that, it's the best way to model this problem (unless you mix it with extensible types but then we would fall in the expression problem territory and this isn't an easy problem to solve in any mainstream languages). Best,
Maurício
Best regards, Daniel Yokomizo

On 11/17/08 18:24, Daniel Yokomizo wrote:
On Mon, Nov 17, 2008 at 9:49 PM, Maurício
mailto:briqueabraque@yahoo.com> wrote: > (...) I don't recall where I found the following example, but copied
> it locally as compelling evidence that the functional solution can be > much clearer and shorter than the same solution modeled with objects > and inheritance.
[snip]
> -- Arithmetic expression forms data Expr = Num Int | Add Expr Expr > > -- Evaluate expressions > eval :: Expr -> Int > (...)
> public abstract class Expr { > public abstract int eval (); > public abstract void modn(int v);
[snip]
when the first standard was set, and I can tell you for sure
that, even
at that time, no one who knows at least the basics of C++
would ever
write that problem like this.
Mauri, I'm not sure what you mean. Do you mean: 1) No C++er would ever "structure" the problem like: -- Arithmetic expression forms data Expr = Num Int | Add Expr Expr -- Evaluate expressions eval :: Expr -> Int eval (Num i) = i eval (Add l r ) = eval l + eval r If so, then I'm unsure what you could mean since the closest counterpart to: date Expr = Num Int | Add Expr Expr in c++ is an abstract Expr class with derived classes, Int and Add, just as shown in Greg's Java counterpart to the haskell Expr. 2) No C++er would every solve the problem with a heirarchy of Expr classes with virtual functions. If so, then I'm really confused because that's exactly the way I would do it *except* if I wanted to avoid the overhead of virtual function dispatch. In this case, I would use template metaprogramming (WARNING: not for c++ template metaprogramming novices): http://www.boost.org/doc/libs/1_37_0/doc/html/proto/users_guide.html#boost_p... In the proto metaprogramming, AFAICT, the 1st element of the proto::expr template, the tag, corresponds to Expr constructor's, Num and Add, of Greg's haskell example code. The | separating the Expr constructor variants corresponds to the proto::or_ template. So, if template metaprogramming were used, then there are some very good c++ programmer which would structure their c++ code like the haskell code (although, as seen by the #boost_proto.users_guide.intermediate_form.expression_introspection.defining_dsel_grammars reference, it's "a bit obscured" by all the "scaffolding" needed to make it work). Another reference which *may* reflect the haskell structure is: http://research.microsoft.com/~akenn/generics/gadtoop.pdf I must admit I don't really understand it, but it seems to have some similarities to haskell's structure. The author even uses haskell code to compare with his corresponding extension to c#. In particular, page 9 contains an example use of his proposed switch statement extension which looks very similar to the way haskell would pattern match on an expression to dispatch to the appropriate case. [snip]

I wrote:
I don't recall where I found the following example
My apologies to Ralf Lammel and Ondrej Rypacek. Five seconds on
Google tells me I had copied that code verbatim from their paper, "The
expression lemma."
http://www.uni-koblenz.de/~laemmel/expression/long.pdf
Great paper, by the way!
-Greg
On Mon, Nov 17, 2008 at 11:00 AM, Greg Fitzgerald
Jonathan Cast wrote:
[Functional and object-oriented programming] have points of similarity, but on net the best plan is to simply never reason analogically from one to the other.
Coming from the OO world, I found it very useful to see how the same solution is modeled using different paradigms. I don't recall where I found the following example, but copied it locally as compelling evidence that the functional solution can be much clearer and shorter than the same solution modeled with objects and inheritance.
-- Arithmetic expression forms data Expr = Num Int | Add Expr Expr
-- Evaluate expressions eval :: Expr -> Int eval (Num i) = i eval (Add l r ) = eval l + eval r
-- Modify literals modulo v modn :: Expr -> Int -> Expr modn (Num i) v = Num (i 'mod' v) modn (Add l r) v = Add (modn l v) (modn r v)
public abstract class Expr { public abstract int eval (); public abstract void modn(int v); }
public class Num extends Expr { private int value; public Num(int value) { this.value = value; } public int eval () { return value; } public void modn(int v) { this.value = this.value % v; }
public class Add extends Expr { private Expr left, right; public Add(Expr left, Expr right ) { this.left = left; this.right = right; } public int eval () { return left.eval () + right.eval (); } public void modn(int v) { left.modn(v); right.modn(v); } }
-Greg

On Mon, Nov 17, 2008 at 10:39 AM, Maurício
(...)
GHC says that the type of the result of 'function' is both determined by
the "rigid type" from MyClass and the "rigid type" from MyData. But why can't both be the same?
are you OOPer? :)
What is an OOPer?
I think, from the OOP point of view, that it is useful to think of classes as collections of generic functions that may apply to different types, if they happen to implement that class of functions. (Would it then be fair to equate a Haskell class to a Java Interface, but not to a Java class?) Type are more about a range of values allowed than about functionality, as they are in OOP languages when defined by OOP classes. The class/data type system in Haskell really does feel to me to be more like CLOS than like C++/Java. But then I barely touched CLOS for a brief moment in time to feel that way, so it's not a strong feeling :-) Dave
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

David,
I had to bring up a parenthetical from your message because I think it
is often a point of confusion:
2008/11/17 David Leimbach
(Would it then be fair to equate a Haskell class to a Java Interface, but not to a Java class?)
This is a dangerous direction to go, because while there are some analogies, going this direction leads to many mistakes. A typeclass is similar to an interface, in that it defines the operations on some object, and you can call functions that use that typeclass polymorphically over any instance. But in the OOP model, interfaces are also a form of existential quantification. If I have an IPrintable object, I can put it on a list of IPrintables:
// psuedo-java: List<IPrintable> foo(List<IPrintable> tail) { String x = "hello"; // assume String is an instance of IPrintable return List.cons(x, tail); }
But in Haskell, this function doesn't typecheck:
foo :: Show a => [a] -> [a] foo xs = "hello" : xs
The type of "foo" says that its argument is a homogenous list of *some* instance of Show, but it doesn't specify which one. Of course, in Haskell you can make this work with existential types:
data AnyShow = forall a. Show a => ExistentialShow a foo2 :: [AnyShow] -> [AnyShow] foo2 xs = ExistentialShow "hello" : xs
foo3 :: Show a => [a] -> [AnyShow] foo3 xs = foo2 (map ExistentialShow xs)
There are a few other differences; for example,
poly :: Num a => a poly = fromInteger 1
The person *calling* poly determines what instance of Num they want returned; in OOP, poly would have to be called with a "factory" as an argument that told it how to construct the instance of the Num interface that the caller wants. This generalizes to code that would be much more difficult to write in an OOP style; consider:
poly2 :: Num a => a -> a poly2 x = x + 1 -- in Haskell, 1 here is implicitly 'fromInteger 1'
This is surprisingly hard to write in an OOP language, and almost certainly uglier than the Haskell solution. Either the arguments to plus have to be polymorphic, which is really difficult, or you need a special version of every operator that takes an Integer instead of the class in question, or you need some way to query the class for a factory which builds an instance of the class. In Haskell, (+) specifies that the arguments must be the same type, unlike the OOP solution where one argument is given privledged status as the method receiver. -- ryan

On Sun, Nov 16, 2008 at 1:32 PM, Maurício
Hi,
Why is this wrong?
---- class MyClass r where function :: r -> s
data MyData u = MyData u
instance MyClass (MyData v) where function (MyData a) = a ----
GHC says that the type of the result of 'function' is both determined by the "rigid type" from MyClass and the "rigid type" from MyData. But why can't both be the same?
As Bulat said, your type signature is equivalent to: function :: forall r s. r -> s whereas the result you're producing can't produce any s, but only particular s's. In essence, the result type is determined by the input type. One way to code this would be to use functional dependencies: class MyClass r s | r -> s where function :: r -> s data MyData u = MyData u instance MyClass (MyData v) v where function (MyData a) = a /g -- I am in here

Hello J., Monday, November 17, 2008, 12:56:02 AM, you wrote:
class MyClass r where function :: r -> s As Bulat said, your type signature is equivalent to:
function :: forall r s. r -> s
only function :: forall s. r -> s (r is fixed in class header) -- Best regards, Bulat mailto:Bulat.Ziganshin@gmail.com

Bulat Ziganshin wrote:
Hello J.,
Monday, November 17, 2008, 12:56:02 AM, you wrote:
class MyClass r where function :: r -> s As Bulat said, your type signature is equivalent to:
function :: forall r s. r -> s
only
function :: forall s. r -> s
(r is fixed in class header)
... and the only value the function can return is bottom. Is there any type system which would have more than one value which inhabits all types? Peter.

On Sun, Nov 16, 2008 at 5:06 PM, Peter Hercek
... and the only value the function can return is bottom. Is there any type system which would have more than one value which inhabits all types?
Well something like lazy C# might; i.e. every value has a _|_ (nontermination) and null (termination but undefined). Luke

On Sun, Nov 16, 2008 at 7:09 PM, Luke Palmer
On Sun, Nov 16, 2008 at 5:06 PM, Peter Hercek
wrote: ... and the only value the function can return is bottom. Is there any type system which would have more than one value which inhabits all types?
Well something like lazy C# might; i.e. every value has a _|_ (nontermination) and null (termination but undefined).
For that matter, Control.Exception allows you to distinguish
exceptional values from each other.
--
Dave Menendez

David Menendez wrote:
On Sun, Nov 16, 2008 at 7:09 PM, Luke Palmer
wrote: On Sun, Nov 16, 2008 at 5:06 PM, Peter Hercek
wrote: ... and the only value the function can return is bottom. Is there any type system which would have more than one value which inhabits all types? Well something like lazy C# might; i.e. every value has a _|_ (nontermination) and null (termination but undefined).
For that matter, Control.Exception allows you to distinguish exceptional values from each other.
OK, thanks for responses. I'm not sure I understand it well so I try to summarize: Control.Exception is an extension, also it probably cannot catch "error :: String -> a" since the report says so: http://www.haskell.org/onlinereport/exps.html#sect3.1 So Haskell'98 has only one value of all types (the bottom). But Haskell with Control.Exception extension has more values of all types since they can be thrown and later caught and investigated at that place. Maybe the last sentence of section 2.1 (_|_ Bottom) of "Haskell/Denotational semantics" should be clarified better. http://en.wikibooks.org/wiki/Haskell/Denotational_semantics#.E2.8A.A5_Bottom So when trying to use Curry-Howard isomorphism for something in Haskell, one sould be pretty carefull what features of are being used. Peter.

On Tue, 2008-11-18 at 19:05 +0100, Peter Hercek wrote:
David Menendez wrote:
On Sun, Nov 16, 2008 at 7:09 PM, Luke Palmer
wrote: On Sun, Nov 16, 2008 at 5:06 PM, Peter Hercek
wrote: ... and the only value the function can return is bottom. Is there any type system which would have more than one value which inhabits all types? Well something like lazy C# might; i.e. every value has a _|_ (nontermination) and null (termination but undefined).
For that matter, Control.Exception allows you to distinguish exceptional values from each other.
OK, thanks for responses. I'm not sure I understand it well so I try to summarize:
Control.Exception is an extension, also it probably cannot catch "error :: String -> a" since the report says so: http://www.haskell.org/onlinereport/exps.html#sect3.1
I think `cannot be caught by the user' is intended to be descriptive here; or, alternately, this is one place where GHC deviates from the spec. catch (error foo) h will certainly sometimes behave as h (UserError foo). Non-deterministically. jcc

Peter Hercek wrote:
But Haskell with Control.Exception extension has more values of all types since they can be thrown and later caught and investigated at that place.
Maybe the last sentence of section 2.1 (_|_ Bottom) of "Haskell/Denotational semantics" should be clarified better.
http://en.wikibooks.org/wiki/Haskell/Denotational_semantics#.E2.8A.A5_Bottom
So when trying to use Curry-Howard isomorphism for something in Haskell, one sould be pretty carefull what features of are being used.
Definitely. And that surfaces even in quite innocently looking programs and statements about them. The introductory example of the following technical report may be amusing in that respect: http://wwwtcs.inf.tu-dresden.de/~voigt/TUD-FI08-08.pdf Ciao, Janis. -- Dr. Janis Voigtlaender http://wwwtcs.inf.tu-dresden.de/~voigt/ mailto:voigt@tcs.inf.tu-dresden.de

On Sat, 22 Nov 2008, Janis Voigtlaender wrote:
Definitely. And that surfaces even in quite innocently looking programs and statements about them. The introductory example of the following technical report may be amusing in that respect:
In example 1, I don't see on the one hand, why 'takeWhile (null.tail)' could fail with "tail: empty list", since all lists in '[[i] | i <- [1..(div 1 0)]]' are non-empty (namely singletons). On the other hand, aren't those imprecise error problems not just proofs that mixing up errors and exceptions (here treating errors as exceptions) is a bad thing? 'error' is only a candy version of 'undefined' for simplifying debugging. If all 'error's are replaced by 'undefined' (plain bottom) then 'takeWhile p (map h l)' and 'map h (takeWhile (p.h) l)' behave also visually identical, don't they?

Henning Thielemann wrote:
On Sat, 22 Nov 2008, Janis Voigtlaender wrote:
Definitely. And that surfaces even in quite innocently looking programs and statements about them. The introductory example of the following technical report may be amusing in that respect:
In example 1, I don't see on the one hand, why 'takeWhile (null.tail)' could fail with "tail: empty list",
Because the (GHC) semantics described in the following paper: http://doi.acm.org/10.1145/301631.301637 says so. You can also check it by calculating with the definitions from Section 3 and Figure 8 of the above technical report. Or see it demonstrated on slide pages 32-38 of: http://wwwtcs.inf.tu-dresden.de/~voigt/nwpt2008-slides.pdf
since all lists in '[[i] | i <- [1..(div 1 0)]]' are non-empty (namely singletons).
This does not really have anything to do with the above, but I may just as well say that all lists in '[[i] | i <- [1..(div 1 0)]]' are empty. Or that they are all of length 17. Because there are no lists in '[[i] | i <- [1..(div 1 0)]]'. (Note that the "supply" [1..(div 1 0)] is itself erroneous.) The "tail: empty list" failure mentioned above really has nothing at all to do with the concrete expression '[[i] | i <- [1..(div 1 0)]]'. Any other erroneous expression, such as just 'error "div-by-0"' would lead to the same result.
On the other hand, aren't those imprecise error problems not just proofs that mixing up errors and exceptions (here treating errors as exceptions) is a bad thing? 'error' is only a candy version of 'undefined' for simplifying debugging. If all 'error's are replaced by 'undefined' (plain bottom) then 'takeWhile p (map h l)' and 'map h (takeWhile (p.h) l)' behave also visually identical, don't they?
Yes, if all 'error's are replaced by 'undefined', then the two expressions are semantically equivalent. But I don't buy this as a decisive argument in the "errors vs. exceptions" debate. Ciao, Janis. -- Dr. Janis Voigtlaender http://wwwtcs.inf.tu-dresden.de/~voigt/ mailto:voigt@tcs.inf.tu-dresden.de

Why is this wrong? (...)
(...) One way to code this would be to use functional dependencies:
class MyClass r s | r -> s where function :: r -> s data MyData u = MyData u instance MyClass (MyData v) v where function (MyData a) = a
One additional problem is that I (believe I) need that my class takes just one type, since I'm trying to derive it in a new type (using generalized newtype deriving). A good comparison would be a complex number over any float type. I could define a few operations like: makeComplex r i = ComplexNumber r i realPart (ComplexNumber r _) = r But then I would like to say: newtype ComplexWithDouble = ComplexWithDouble (ComplexNumber Double) deriving ... so that I could have: a :: ComplexWithDouble a = makeComplex 0.5 0.25 My first attempt was to try some kind of "type pattern match" :) like class ComplexBaseClass (c r) where ... but it seems that doesn't make sense. Thanks for your tips, Maurício

Hello Maurício, Monday, November 17, 2008, 9:38:06 PM, you wrote:
(...) One way to code this would be to use functional dependencies:
class MyClass r s | r -> s where function :: r -> s
One additional problem is that I (believe I) need that my class takes just one type
FDs with just one type parameter are called ATs :) (FDs = functional dependencies, ATs is a new feature of ghc 6.8/6.10) -- Best regards, Bulat mailto:Bulat.Ziganshin@gmail.com

(...) One way to code this would be to use functional dependencies:
class MyClass r s | r -> s where function :: r -> s
One additional problem is that I (believe I) need that my class takes just one type
FDs with just one type parameter are called ATs :)
(FDs = functional dependencies, ATs is a new feature of ghc 6.8/6.10)
Sorry for asking, but I tried to read 6.10 extension documentation in user's guide, as well as release notes for 6.10 and 6.8, and could not figure out what exactly are ATs. Can you give me a direction? Thanks, Maurício

ATs are "Associated Types", aka Type Families. They can be found in
the GHC 6.10 manual here:
http://haskell.org/ghc/docs/6.10.1/html/users_guide/type-families.html
As a starting point, you might want to try something like:
class Complex c where
type RealType c
realPart :: c -> RealType c
imagPart :: c -> RealType c
Cheers,
Reiner
On Tue, Nov 18, 2008 at 7:01 PM, Maurício
(...) One way to code this would be to use functional dependencies:
class MyClass r s | r -> s where function :: r -> s
One additional problem is that I (believe I) need that my class takes just one type
FDs with just one type parameter are called ATs :)
(FDs = functional dependencies, ATs is a new feature of ghc 6.8/6.10)
Sorry for asking, but I tried to read 6.10 extension documentation in user's guide, as well as release notes for 6.10 and 6.8, and could not figure out what exactly are ATs. Can you give me a direction?
Thanks, Maurício
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

On Tue, Nov 18, 2008 at 1:38 AM, Reiner Pope
ATs are "Associated Types", aka Type Families. They can be found in the GHC 6.10 manual here: http://haskell.org/ghc/docs/6.10.1/html/users_guide/type-families.html
As a starting point, you might want to try something like:
class Complex c where type RealType c realPart :: c -> RealType c imagPart :: c -> RealType c
I imagine that the generalized newtype deriving might be trickier to get working for this formulation. /g -- I am in here

On Mon, Nov 17, 2008 at 10:38 AM, Maurício
newtype ComplexWithDouble = ComplexWithDouble (ComplexNumber Double) deriving ...
Perhaps you want something like: class Complex r c | c -> r where makeComplex :: r -> r -> c realPart :: c -> r imagPart :: c -> r data ComplexNumber t = CN t t instance Complex t (ComplexNumber t) where makeComplex = CN realPart (CN r _) = r imagPart (CN _ i) = i newtype ComplexWithDouble = CWD (ComplexNumber Double) deriving (Complex Double) Having the parameters "backwards" is somewhat annoying, I suppose, but it's unavoidable if you're hoping to use generalized newtype deriving I believe. /g -- I am in here

Perhaps you want something like:
class Complex r c | c -> r where makeComplex :: r -> r -> c realPart :: c -> r imagPart :: c -> r
data ComplexNumber t = CN t t instance Complex t (ComplexNumber t) where makeComplex = CN realPart (CN r _) = r imagPart (CN _ i) = i
newtype ComplexWithDouble = CWD (ComplexNumber Double) deriving (Complex Double)
Having the parameters "backwards" is somewhat annoying, I suppose, but it's unavoidable if you're hoping to use generalized newtype deriving I believe.
Great! Actually, I would never imagine that (ComplexNumber Double) would yield a class with a single type variable... What is the logic behind that? I know about kinds (of types). Do classes have "kinds" of their own? Thanks, Maurício

Maurício wrote:
Hi,
Why is this wrong?
---- class MyClass r where function :: r -> s
data MyData u = MyData u
instance MyClass (MyData v) where function (MyData a) = a ----
GHC says that the type of the result of 'function' is both determined by the "rigid type" from MyClass and the "rigid type" from MyData. But why can't both be the same?
particular instances can't add extra restrictions (eg: "both types are the same") to the interface declared by the class (eg: "both types are arbitrary"). Compare this version: ----8<---- {-# LANGUAGE MultiParamTypeClasses, FlexibleInstances #-} module Test where class MyClass r s where function :: r -> s data MyData u = MyData u instance MyClass (MyData v) v where function (MyData a) = a ----8<---- And ghci session: ----8<---- *Test> function (MyData "hello") <interactive>:1:0: No instance for (MyClass (MyData [Char]) s) arising from a use of `function' at <interactive>:1:0-24 Possible fix: add an instance declaration for (MyClass (MyData [Char]) s) In the expression: function (MyData "hello") In the definition of `it': it = function (MyData "hello") *Test> :t function (MyData "hello") function (MyData "hello") :: (MyClass (MyData [Char]) s) => s *Test> function (MyData "hello") :: String "hello" ----8<---- I don't know how evil those language extensions are, though - I just fiddled until it worked...
What am I doing wrong?
Claude -- http://claudiusmaximus.goto10.org/

On Sun, Nov 16, 2008 at 2:01 PM, Claude Heiland-Allen < claudiusmaximus@goto10.org> wrote:
I don't know how evil those language extensions are, though - I just fiddled until it worked...
The only part of FlexibleInstances that you've used here is the ability to mention a type variable more than once in the instance. I really wish this came with MultiParamTypeClasses. My reasoning is this, FlexibleInstances turns on a lot of extra stuff, as do functional dependencies. And yet, once you have multiparam type classes one of the natural things you want is the ability to mention a type variable more than once but currently you have to enable a lot of extra baggage to get that ability. I'm not an expert, the way you've used them together seems quite sane and by using those extensions instead of some of the more powerful ones you've probably done yourself a favor :) Jason
participants (18)
-
Bulat Ziganshin
-
Claude Heiland-Allen
-
Daniel Yokomizo
-
David Leimbach
-
David Menendez
-
Derek Elkins
-
Greg Fitzgerald
-
Henning Thielemann
-
J. Garrett Morris
-
Janis Voigtlaender
-
Jason Dagit
-
Jonathan Cast
-
Larry Evans
-
Luke Palmer
-
Maurício
-
Peter Hercek
-
Reiner Pope
-
Ryan Ingram