[Haskell-cafe] FGL instance constraint

Jason Dagit dagit at codersbase.com
Sat May 1 03:12:39 EDT 2010


On Fri, Apr 30, 2010 at 11:53 PM, Ivan Lazar Miljenovic <
ivan.miljenovic at gmail.com> wrote:

> Jason Dagit <dagit at codersbase.com> writes:
>
> > On Fri, Apr 30, 2010 at 11:08 PM, Ivan Lazar Miljenovic <
> > ivan.miljenovic at gmail.com> wrote:
> >>
> >>
> >> You're putting the constraint in the wrong places: put the "(Cls a) => "
> >> in the actual functions where you need it.
> >>
> >
> > That's solid advice in general, but it's still not going to work here if
> any
> > of the functions needed for the instance of Graph require the type class
> > constraint.
>
> The Graph class doesn't care what the labels are, so it should matter
> about the constraint.
>

Perhaps this "working" example illustrates the change I want to make.
 Working in the sense that it type checks but it's a silly example just to
illustrate the point:

\begin{code}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE FlexibleInstances #-}
module Graph where

import Data.Graph.Inductive.Graph hiding (Graph)

-- Defive some arbitrary class, and give it a 'boring'
-- reason to use it.
class Cls a where
  boring :: a

data Blah = Blah

-- Make sure we have at least one instance, but not really needed for this
example
instance Cls Blah where
  boring = Blah

data B a = B [a]

data GrB a b = GrB (B a)

-- Just copy the bits from FGL that are interesting here
class Graph gr a b where
  empty     :: gr a b
  -- | True if the given 'Graph' is empty.
  isEmpty   :: gr a b -> Bool
  -- | Create a 'Graph' from the list of 'LNode's and 'LEdge's.
  mkGraph   :: [LNode a] -> [LEdge b] -> gr a b
  -- | A list of all 'LNode's in the 'Graph'.
  labNodes  :: gr a b -> [LNode a]

instance Cls a => Graph GrB a b where
  empty = GrB (B [boring])
  isEmpty (GrB (B [])) = True
  isEmpty _            = False
  mkGraph _ _ = GrB (B [])
  labNodes _ = []
\end{code}

The Graph class is actually unchanged other than mentioning 'a' and 'b'.
 This mention of 'a' and 'b' allows instance writers to add contexts other
than () when defining instances.

Jason
-------------- next part --------------
An HTML attachment was scrubbed...
URL: http://www.haskell.org/pipermail/haskell-cafe/attachments/20100501/dbe11747/attachment.html


More information about the Haskell-Cafe mailing list