Hypergraph module (Re: instance Ord FiniteMap)

Eray Ozkural erayo@cs.bilkent.edu.tr
Thu, 30 May 2002 18:32:09 +0300


--Boundary-00=_5Xk98DhFOsV6kPU
Content-Type: text/plain;
  charset="iso-8859-1"
Content-Transfer-Encoding: 8bit
Content-Disposition: inline

On Wednesday 29 May 2002 02:58, Hal Daume III wrote:
> Is there any particular reason FiniteMap (and hence Set) aren't instances
> of Ord?  I realize it's "weird" to define a map to be ordered, but even if
> the Ord definition were in some sense "nonsensical", being able to have,
> for instance, Sets of Sets of things would be really nice.

Check this out. It was working for me last time I used it.

Comments welcome,

-- 
Eray Ozkural (exa) <erayo@cs.bilkent.edu.tr>
Comp. Sci. Dept., Bilkent University, Ankara
www: http://www.cs.bilkent.edu.tr/~erayo  Malfunction: http://mp3.com/ariza
GPG public key fingerprint: 360C 852F 88B0 A745 F31B  EA0F 7C07 AE16 874D 539C

--Boundary-00=_5Xk98DhFOsV6kPU
Content-Type: text/plain;
  charset="iso-8859-1";
  name="Hypergraph.hs"
Content-Transfer-Encoding: 7bit
Content-Disposition: attachment; filename="Hypergraph.hs"

module Hypergraph where
import FiniteMap
import Set

-- A hypergraph is a family of sets which are subsets of a vertex set X
-- This implementation uses an edge list representation that
-- directly corresponds to the mathematical definition
-- n index type, w weight type
-- type Hypergraph n w = Array n [(n,w)]

-- show functions for set and finitemap

instance (Show a) => Show (Set a) where   
    show set = show (setToList set)

instance (Show a, Show b) => Show (FiniteMap a b) where   
    show vs = show (fmToList vs)

type HEdges l = FiniteMap l (Set l)

data Hypergraph l = Hypergraph (HEdges l) (HEdges l) deriving Show

-- hgraph constructor
-- takes a list of edges
hgraph list = let edges = hEdges list in
		  Hypergraph edges (dualEdges edges)

-- hgraph edge_list
--hEdges :: [ [a] ] -> HEdges a
hEdges el = listToFM (zip [1..length el] (map mkSet el))
--     = Hypergraph (listToFM . mkSet (edge_list)) (listToFM . mkSet (edge_list))

-- compute dual of a given hgraph

dualEdge (edgeIx, hEdge) = map (\x->(x, mkSet [edgeIx])) (setToList hEdge)

dualEdges hEdges = ( (addListToFM_C union emptyFM) . concat .
		     (map dualEdge) . fmToList )
		     hEdges
--hVertices el = (zip (map mkSet el) [1..length el])

-- hyper vertices are the dual of the hypergraph
--hVertices hEdges = (foldFM uni emptyFM). (mapFM dual)) hEdges
--		   where uni = plusFM_C 
--dual hEdges = ( listToFM . map (\(x,y)->(y,x)) . fmToList) hEdges


--Boundary-00=_5Xk98DhFOsV6kPU--