[Haskell-cafe] Manual type-checking in graphs: Avoidable?

Francesco Ariis fa-ml at ariis.it
Fri Feb 19 06:29:48 UTC 2016


On Thu, Feb 18, 2016 at 09:28:24PM -0800, Jeffrey Brown wrote:
> I had not!
> 
> I'm not seeing how such a solution would work. The nodes in a graph all
> have to have the same type. If the phantom parameter distinguished two
> nodes, they could not be used together.
> 
> But maybe you see something there that I don't?

Argh, indeed you are correct. Maybe it can be worked around with
existential quantification like this?


{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE ExistentialQuantification #-}

data Person = Person
data Hamster = Hamster

data GraphNode a = P String -- hide these
                 | H String

-- coll. of vertices
data HumHamGraph = forall c . Test c => Gr [(c, c)]

findCritters :: HumHamGraph -> GraphNode Person -> GraphNode Hamster
findCritters = undefined

class Test a where
    name :: a -> String

instance Test (GraphNode Person) where
    name (P s) = s

instance Test (GraphNode Hamster) where
    name (H s) = s

toast = [(P "a,ga", H "beta"), (H "cas", P "cds")]


For sure it looks ugly :s


More information about the Haskell-Cafe mailing list