[Haskell-cafe] FGL instance constraint

Kevin Quick quick at sparq.org
Sat May 1 16:17:19 EDT 2010


On Fri, 30 Apr 2010 23:30:21 -0700, Jason Dagit <dagit at codersbase.com> wrote:

> 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.

I need to use Cls methods in the Graph methods: see below.  More specifically, the Node decorators (type 'a') need to be of class Cls as well, but I can't figure out how to do this.

> 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.

Yes.

> A solution to the monad problem I just mentioned is outlined here as
> 'restricted monads':
> http://okmij.org/ftp/Haskell/types.html#restricted-datatypes

I'll read this, but my brain has low Oleg-ability, so it may take me some time to begin to understand.  Thanks for the reference though.

> Perhaps you can try either associated types or the restricted monad
> approach?  Unfortunately, I think both of them require you to change FGL
> instead of just your code, although maybe not with the restricted monad
> stuff.  I don't recall how invasive that approach is.

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).

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

main = putStrLn "ok"


Perhaps I need some alternative method here, or perhaps as has been suggested I'm trying to use something that's older/Haskell-98 specific that can't support this.

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.

-- 
-KQ


More information about the Haskell-Cafe mailing list