[Haskell-cafe] Haskell 101 on classes .... duh ..... :^)
Ivan Lazar Miljenovic
ivan.miljenovic at gmail.com
Tue Sep 13 06:20:07 CEST 2011
On 13 September 2011 14:08, Vasili I. Galchin <vigalchin at gmail.com> wrote:
> 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 at gmail.com
IvanMiljenovic.wordpress.com
More information about the Haskell-Cafe
mailing list