Tips for converting Prolog to typeclasses?

Lately, in my quest to get a better understanding of the typeclass system, I've been writing my typeclass instance declarations in Prolog first, then when I've debugged them, I port them over back over to Haskell. The porting process involves a lot trial and error on my part trying to decide when to use functional dependencies and which compiler extension to enable ( -fallow-undecidable-instances, -fallow-overlapping-instances, etc.). Which might be okay, but I still can produce things that won't compile, and I don't necessarily know if I'm making a fundamental mistake in a program, or if there's something trivial that I'm not doing quite right. For example, there was a question on haskell-cafe last week about creating an "apply" function. My first solution ( http://www.haskell.org//pipermail/haskell-cafe/2006-May/015905.html ) was to use type classes and nested tuples for the collection of arguments. This works fine. But then I wanted to try to get closer to what the original poster wanted, namely to use regular homogenous lists to store the arguments. So I thought I could reuse the class definition and just provide new instances for a list type, instead of the nested tuple type. Here's the class definition...
class Apply a b c | a b -> c where apply :: a -> b -> c
...So I wrote the following Prolog snippets which seemed like they might properly describe the situation I was looking for... :- op(1000,xfy,=>). % use => instead of -> for arrow type app(A=>B,[A],C) :- app(B,[A],C). app(C,[A],C). ...which I translated into the following Haskell instances...
instance Apply b [a] c => Apply (a->b) [a] c where apply f [] = error "Not enough arguments" apply f (x:xs) = apply (f x) xs instance Apply c [a] c where apply f _ = f
...and here's a test program...
g :: Int -> Int -> Int -> Int -> Int g w x y z = w*x + y*z
main = do print $ apply g [1..]
...but I haven't been able to get GHC to accept this yet. So I'm wondering if there's an easy route to learning this stuff. Some sort of comprehensive tutorial out there which I should be reading that describes what should be possible with Haskell's typeclasses plus GHC extenstions, and when and where to enable these extentions. (Bonus points awarded if it explains things in terms of Prolog). Or is this just one of those things that requires reading lots of papers on each extentsion and possibly the source code of the implementation? Thanks, Greg Buchholz

On Wednesday 31 May 2006 08:22 pm, Greg Buchholz wrote:
Lately, in my quest to get a better understanding of the typeclass system, I've been writing my typeclass instance declarations in Prolog first, then when I've debugged them, I port them over back over to Haskell. The porting process involves a lot trial and error on my part trying to decide when to use functional dependencies and which compiler extension to enable ( -fallow-undecidable-instances, -fallow-overlapping-instances, etc.). Which might be okay, but I still can produce things that won't compile, and I don't necessarily know if I'm making a fundamental mistake in a program, or if there's something trivial that I'm not doing quite right.
For example, there was a question on haskell-cafe last week about creating an "apply" function. My first solution ( http://www.haskell.org//pipermail/haskell-cafe/2006-May/015905.html ) was to use type classes and nested tuples for the collection of arguments. This works fine. But then I wanted to try to get closer to what the original poster wanted, namely to use regular homogenous lists to store the arguments. So I thought I could reuse the class definition and just provide new instances for a list type, instead of the nested tuple type. Here's the class definition...
class Apply a b c | a b -> c where apply :: a -> b -> c
...So I wrote the following Prolog snippets which seemed like they might properly describe the situation I was looking for...
:- op(1000,xfy,=>). % use => instead of -> for arrow type
app(A=>B,[A],C) :- app(B,[A],C). app(C,[A],C).
...which I translated into the following Haskell instances...
instance Apply b [a] c => Apply (a->b) [a] c where apply f [] = error "Not enough arguments" apply f (x:xs) = apply (f x) xs instance Apply c [a] c where apply f _ = f
To make this work, you're going to have to convince the compiler to accept "overlapping instances" and then make sure they don't overlap :) In the second instance, what you really want to say is "instance c [a] c, only where c is not an application of (->)". As I recall, there is a way to express such type equality/unequality using typeclasses, but I don't remember how to do it offhand. A quick google turns up this page, which appears to address most of the questions at hand: http://okmij.org/ftp/Haskell/types.html
...and here's a test program...
g :: Int -> Int -> Int -> Int -> Int g w x y z = w*x + y*z
main = do print $ apply g [1..]
...but I haven't been able to get GHC to accept this yet. So I'm wondering if there's an easy route to learning this stuff. Some sort of comprehensive tutorial out there which I should be reading that describes what should be possible with Haskell's typeclasses plus GHC extenstions, and when and where to enable these extentions. (Bonus points awarded if it explains things in terms of Prolog). Or is this just one of those things that requires reading lots of papers on each extentsion and possibly the source code of the implementation?
Thanks,
Greg Buchholz
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
-- Rob Dockins Talk softly and drive a Sherman tank. Laugh hard, it's a long way to the bank. -- TMBG

Robert Dockins wrote:
To make this work, you're going to have to convince the compiler to accept "overlapping instances" and then make sure they don't overlap :) In the second instance, what you really want to say is "instance c [a] c, only where c is not an application of (->)". As I recall, there is a way to express such type equality/unequality using typeclasses, but I don't remember how to do it offhand.
Now that I think about it more, I see what you are saying. And I think we can be a little more general than "c is not an application of (->)". A better statement might be "c is not a function application which takes an 'a' as the first argument". That should allow us to have a function of type Int->Int->Double->String return a function Double->String when applied to a list of Int's. So in Prolog... :- op(1000,xfy,=>). app(A=>B,[A],C) :- app(B,[A],C). app(C,[A],C) :- not(isfuncwithhead(C,A)). isfuncwithhead(A=>B,A). ...Now I just need to figure out how to represent "not" without "cut". I'll take a look at what Oleg has done. Thanks, Greg Buchholz

Robert Dockins wrote: ] In the second instance, what you really want to say is "instance c [a] ] c, only where c is not an application of (->)". As I recall, there is ] a way to express such type equality/unequality using typeclasses, but ] I don't remember how to do it offhand. For those playing along at home, here's the less general version which uses Oleg Kiselyov's "IsFunction" relation and associated TypeCast machinery from the HList paper...
{-# OPTIONS -fglasgow-exts #-} {-# OPTIONS -fallow-undecidable-instances #-}
data HTrue data HFalse
class IsFunction a b | a -> b instance TypeCast f HTrue => IsFunction (x->y) f instance TypeCast f HFalse => IsFunction a f
class TypeCast a b | a -> b, b->a where typeCast :: a -> b class TypeCast' t a b | t a -> b, t b -> a where typeCast' :: t->a->b class TypeCast'' t a b | t a -> b, t b -> a where typeCast'' :: t->a->b instance TypeCast' () a b => TypeCast a b where typeCast x = typeCast' () x instance TypeCast'' t a b => TypeCast' t a b where typeCast' = typeCast'' instance TypeCast'' () a a where typeCast'' _ x = x
class Apply a b c where -- | a b -> c where apply :: a -> b -> c
instance Apply b [a] c => Apply (a->b) [a] c where apply f [] = error "Not enough arguments" apply f (x:xs) = apply (f x) xs
instance IsFunction c HFalse => Apply c [a] c where apply f _ = f
main = do print (apply g [(1::Int)..] ::String)
g :: Int -> Int -> Int -> Int -> String g w x y z = show $ w*x + y*z
participants (2)
-
Greg Buchholz
-
Robert Dockins