Haskell 101 on classes .... duh ..... :^)

Hello, I am trying to model multigraphs ....but getting errors with ghci and can't figure out why.... I have a serious blind spot .... {-# LANGUAGE MultiParamTypeClasses, FunctionalDependencies #-} module Bonzo where class Graph arrow node where source :: arrow -> node target :: arrow -> node data Arrow = Arrow (Int, Int) instance Graph Arrow Int where source Arrow = fst Arrow target Arrow = snd Arrow ~ ~ {-# LANGUAGE MultiParamTypeClasses, FunctionalDependencies #-} module Bonzo where class Graph arrow node where source :: arrow -> node target :: arrow -> node data Arrow = Arrow (Int, Int) instance Graph Arrow Int where source Arrow = fst Arrow target Arrow = snd Arrow ~ ~ ghci> :load junk1.hs [1 of 1] Compiling Bonzo ( junk1.hs, interpreted ) junk1.hs:19:12: Constructor `Arrow' should have 1 argument, but has been given 0 In the pattern: Arrow In the definition of `source': source Arrow = fst Arrow In the instance declaration for `Graph Arrow Int' junk1.hs:21:12: Constructor `Arrow' should have 1 argument, but has been given 0 In the pattern: Arrow In the definition of `target': target Arrow = snd Arrow In the instance declaration for `Graph Arrow Int' Regards, Vasili

On 13 September 2011 14:08, Vasili I. Galchin
Hello,
I am trying to model multigraphs ....but getting errors with ghci and can't figure out why.... I have a serious blind spot ....
{-# LANGUAGE MultiParamTypeClasses, FunctionalDependencies #-}
module Bonzo where
class Graph arrow node where
source :: arrow -> node
target :: arrow -> node
You probably want a fundep there: "class Graph arrow node | arrow -> node where ..."
data Arrow = Arrow (Int, Int)
instance Graph Arrow Int where
source Arrow = fst Arrow
target Arrow = snd Arrow
Ummm.... that doesn't make sense. Consider this: newtype Arrow = Arrow { arrowPair :: (Int, Int) } instance Graph Arrow Int where source = fst . arrowPair target = snd . arrowPair (Implemented just to be similar to how you've done it; it's not how I would do it in actual code.) Alternatively, you could have kept the data definition as is and had the method instances look like "source (Arrow arr) = fst arr", etc.
ghci> :load junk1.hs [1 of 1] Compiling Bonzo ( junk1.hs, interpreted )
junk1.hs:19:12: Constructor `Arrow' should have 1 argument, but has been given 0 In the pattern: Arrow In the definition of `source': source Arrow = fst Arrow In the instance declaration for `Graph Arrow Int'
junk1.hs:21:12: Constructor `Arrow' should have 1 argument, but has been given 0 In the pattern: Arrow In the definition of `target': target Arrow = snd Arrow In the instance declaration for `Graph Arrow Int'
This is just from the errors in your method instances. -- Ivan Lazar Miljenovic Ivan.Miljenovic@gmail.com IvanMiljenovic.wordpress.com

On Tue, Sep 13, 2011 at 00:08, Vasili I. Galchin
I am trying to model multigraphs ....but getting errors with ghci and can't figure out why.... I have a serious blind spot ....
Why do you need to use classes for this? (Note: forget everything you know about classes from OOP. Haskell typeclasses have approximately nothing to do with OOP.) junk1.hs:19:12:
Constructor `Arrow' should have 1 argument, but has been given 0 In the pattern: Arrow In the definition of `source': source Arrow = fst Arrow In the instance declaration for `Graph Arrow Int'
It's asking "Arrow *what*?" You specified Arrow as taking a tuple argument; if you want to use it here, you need to provide that argument (or a placeholder, but in this case you clearly want the tuple).
source (Arrow p) = fst p target (Arrow p) = snd p
Or you can use pattern matching to deconstruct the tuple as well:
source (Arrow (f,_)) = f target (Arrow (_,t)) = t
-- brandon s allbery allbery.b@gmail.com wandering unix systems administrator (available) (412) 475-9364 vm/sms

Hi Brandon,
Here is Ivan's web site. http://ivanmiljenovic.wordpress.com/ ...... I
have written in Haskell before ... a POSIX Realtime hackage package. It is
true I am little rusty now .... because industry is too stubborn except in
places like Silicon Valley, Wall Street, Virginia (defence industry) to use
FPLs ... have to pay the bills sadly...
Vasili
On Tue, Sep 13, 2011 at 9:57 AM, Brandon Allbery
On Tue, Sep 13, 2011 at 00:08, Vasili I. Galchin
wrote: I am trying to model multigraphs ....but getting errors with ghci and can't figure out why.... I have a serious blind spot ....
Why do you need to use classes for this? (Note: forget everything you know about classes from OOP. Haskell typeclasses have approximately nothing to do with OOP.)
junk1.hs:19:12:
Constructor `Arrow' should have 1 argument, but has been given 0 In the pattern: Arrow In the definition of `source': source Arrow = fst Arrow In the instance declaration for `Graph Arrow Int'
It's asking "Arrow *what*?" You specified Arrow as taking a tuple argument; if you want to use it here, you need to provide that argument (or a placeholder, but in this case you clearly want the tuple).
source (Arrow p) = fst p target (Arrow p) = snd p
Or you can use pattern matching to deconstruct the tuple as well:
source (Arrow (f,_)) = f target (Arrow (_,t)) = t
-- brandon s allbery allbery.b@gmail.com wandering unix systems administrator (available) (412) 475-9364 vm/sms
participants (3)
-
Brandon Allbery
-
Ivan Lazar Miljenovic
-
Vasili I. Galchin