[Haskell-cafe] Haskell 101 on classes .... duh ..... :^)
Vasili I. Galchin
vigalchin at gmail.com
Tue Sep 13 06:08:27 CEST 2011
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
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://www.haskell.org/pipermail/haskell-cafe/attachments/20110912/33456d89/attachment.htm>
More information about the Haskell-Cafe
mailing list