[Haskell-cafe] FGL instance constraint
Ivan Lazar Miljenovic
ivan.miljenovic at gmail.com
Sat May 1 03:23:41 EDT 2010
Hmmm.... this is an interesting way of doing it, but I would argue that
it's pointless: the fact that you're using MPTCs doesn't give you
anything extra that the original class. Furthermore, as I said earlier,
it doesn't make sense to constrain the label type just to make an
instance of a type class.
(Now, if we had other functions in there which _might_ depend on the
label types, this _would_ make sense; as it stands however, it doesn't.)
Jason Dagit <dagit at codersbase.com> writes:
> 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
--
Ivan Lazar Miljenovic
Ivan.Miljenovic at gmail.com
IvanMiljenovic.wordpress.com
More information about the Haskell-Cafe
mailing list