2

Say you want to implement very general operations on a directed graph making as few assumptions about the structure as possible.

It is impossible to make absolutely no assumptions, so I am still assuming that I will represent my graph as some sort of adjacency list, but the spirit is to try to be as opaque as possible about the nature of manipulated things.

Assume you have the two following operations: one operation to list all nodes in a graph, and one operation to list all outgoing edges from some vertex.

class List_Nodes graph list vertex where
    list_nodes :: graph -> list vertex
class List_Edges_From graph vertex list edge where
    list_edges_from :: graph -> vertex -> list edge

Then, just for the fun of it I decided I might want want to iterate over all edges

class List_Edges graph vertex list edge where
    list_edges :: graph -> list edge

No matter what the concrete implementation of a graph will be, I believe I can express very generally that listing edges can be understood as listing nodes, and listing edges from each of them. So I decided to write an instance as general as possible like this:

instance (
    Monad node_list,
    Monad edge_list,
    List_Nodes graph node_list vertex,
    List_Edges_From graph vertex edge_list edge
    ) => List_Edges graph vertex edge_list edge where
    list_edges graph = (list_nodes graph :: node_list vertex) >>= list_edges_from graph
-- I added  :: node_list vertex  to help GHC infer the type.

However, this code does not work as is. This code works only with an additional instance requirement that edge_list ~ node_list,. That's because binding happens only in one monad, the returned one: edge_list.

But to be as general as possible I do not want to assume that the way I store nodes, is necessarily the same way I store outgoing edges in a node. For example one might want to use a list to store nodes, and a vector to store edges out of a node.

Question: How can I express the monadic bind list_nodes graph >>= list_edges_from graph between two possibly different list like containers?

More generally, how can I say convert a list to a vector without being specific about them? I am only assuming they are "list-like" whatever that means. Somehow these list like things are themselves functors, so I'm looking to convert some functor into some other functor. Am I looking for natural transformations of category theory? How can I do this in Haskell?

Language extensions used and imports used:

{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE UndecidableInstances #-}
{-# LANGUAGE AllowAmbiguousTypes #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE ScopedTypeVariables #-}
module Lib () where
import Prelude
import Control.Monad
jam
  • 803
  • 5
  • 14

2 Answers2

0

If you want to be very general about the monad in which your nodes and edges are stored, you can't really do anything. Two monads in general do not compose with each other: what should the return type be if nodes are "stored" as IO String and edges as String -> Maybe String?

I would suggest doing a lot less of this work at the type level. There is little need for type classes: instead, define a concrete type that contains the functions that you need, and a single typeclass for converting to that canonical type. Then the various implementations of your graph type can simply create a "canonical view" of their graph, representing it in the type that you use to implement generic algorithms. This way, you have only one canonical representation to perform these algorithms on, despite having many representations for the graphs themselves.

The graph type can be as simple as

data Graph v e = Graph { nodes :: [v]
                       , edges :: v -> [e]
                       }

class AsGraph t v e where
  asGraph :: t v e -> Graph v e

and you can implement allEdges generically in terms of that quite easily. If you have a graph with vector edges, it can be converted to this generic graph type in order to participate in generic operations like allEdges:

{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE MultiParamTypeClasses #-}

import Data.Foldable (toList)

data Graph v e = Graph { nodes :: [v]
                       , edges :: v -> [e]
                       }

class AsGraph t v e where
  asGraph :: t v e -> Graph v e

data VectorEdges v e = VectorEdges { vs :: [v]
                                   , es :: v -> Vector e
                                   }

instance AsGraph VectorEdges v e where
  asGraph g = Graph (vs g) (toList . es g)

allEdges :: AsGraph t v e => t v e -> [e]
allEdges g = let g' = asGraph g
  in nodes g' >>= edges g'
amalloy
  • 89,153
  • 8
  • 140
  • 205
0

There does not seem to be something standard in Haskell to achieve my purpose, so I ended up adding a class specific for list conversion leaving me room to implement it for what I believe should be convertable lists.

class Convert_List list1 list2 element where
    convert_list :: list1 element -> list2 element

Then I am free to implement it on my own.

The advantage of having such a class is that you can then write the graph operation like this:

class List_Nodes graph list vertex where
    list_nodes :: graph -> list vertex
class List_Edges_From graph vertex list edge where
    list_edges_from :: graph -> vertex -> list edge

class List_Edges graph vertex list edge where
    list_edges :: graph -> list edge
instance (
    Monad list,
    List_Nodes graph l1 vertex,
    List_Edges_From graph vertex l2 edge,
    Convert_List l1 list vertex,
    Convert_List l2 list edge 
    ) => List_Edges graph vertex list edge where
    list_edges graph = 
        convert_list (list_nodes graph :: l1 vertex) >>= \u -> 
            convert_list (list_edges_from graph u :: l2 edge)

Here you see that I implement list_edge in an very general way making few assumptions, i'm not even assuming the return list has to be the same as the graph internal representation.

This is also why I splitted each operation in its own class. Although this may seem counterintuitive at first I believe that there is more potential for factorization as shown here. If I had only one class containing the 3 operations, I could not implement only list_edges without enforcing constraints on the other operations as well. It's only my opinion, but I believe more and more this sort of approach for code design has more potential for factoring.

jam
  • 803
  • 5
  • 14