[Haskell-cafe] FGL instance constraint

Ivan Lazar Miljenovic ivan.miljenovic at gmail.com
Sat May 1 18:42:09 EDT 2010


"Kevin Quick" <quick at sparq.org> writes:
> Yes, I was hoping to use FGL directly (or it's replacement as I've
> scanned some of the recent Cafe discussions and seen that Ivan in
> particular is undertaking this).

FGL isn't really set up for this kind of "the data type _must_ be
restricted" approach.

> The key here is that the decorators for the Node are of type a, and I
> need that type a to be of (Cls a) because I use the methods in Cls a
> to implement the Graph functionality.  I've attached a simple example
> below that attempts to demonstrate this need (and my numerous
> failures).
>
>
> {-# LANGUAGE RankNTypes #-}
>
> module Main where
>
> import Data.Graph.Inductive.Graph
>
> class Cls a where
>     int :: a -> Int   -- just to have something
>
> data (Cls a) => B a = B [a]
>
> -- The intent is that B is a collection of objects fulfilling the Cls
> -- class interface.  It is also the intent to represent B as a Graph
> -- object.  However, in order to create the Graph, the Cls operations
> -- are needed.
>
> -- To make a Graph representation of B, I need to convert my
> -- univariant B datatype into a bivariant type.  This is odd because:
> -- (1) I ignore/drop b because it's not needed, and (2) I have a
> -- constraint on a imposed by B.
>
> data GrB a b = GrB (B a)
> -- data (Cls a) => GrB a b = GrB (B a) -- no difference in compilation
> errors
>
> instance Graph GrB where
> -- instance (Cls a) => Graph GrB where -- error: ambiguous constraint, must mention type a
> -- instance (Cls a) => forall a. Graph GrB where -- error: malformed instance header
> -- instance (Cls a) Graph GrB | GrB -> a where -- error: parse error on |
>     -- empty :: (Cls a) => GrB a b -- error: Misplaced type signature (can't redefine the type)
>     empty = GrB (B []) -- error: could not deduce (Cls a) from context () for B
>
>     isEmpty (GrB (B l)) = null l
>
>     match _ g = (Nothing, g) -- Actually need Cls methods on 'a' type to generate the non-trivial case
>
>     mkGraph n e = GrB (B [])  -- TBD
>     labNodes g = []  -- TBD

Unless you have something else you haven't put here, I don't see any
reason why you have to have the constraint on the datatype rather than
on the actual functions (outside of the class instance) you need them
for later on.

> Thanks again for the advice and help.  Sorry I was rude in not
> answering for so long: shortly after my original post I realized sleep
> was needed.

Yeah, that pesky sleep thing...

-- 
Ivan Lazar Miljenovic
Ivan.Miljenovic at gmail.com
IvanMiljenovic.wordpress.com


More information about the Haskell-Cafe mailing list