99 questions/Solutions/80

From HaskellWiki
< 99 questions‎ | Solutions
Revision as of 19:29, 22 November 2013 by Vict (talk | contribs) (created page w/ working solution)
(diff) ← Older revision | Latest revision (diff) | Newer revision → (diff)
Jump to navigation Jump to search
The printable version is no longer supported and may have rendering errors. Please update your browser bookmarks and please use the default browser print function instead.

(***) Conversions

Write predicates to convert between the different graph representations.

Here is a working solution for the graph-term, adjacency-list, and edge-clause / human-friendly forms for undirected, unweighted graphs.

data Graph a = Graph [a] [(a, a)]
               deriving (Show, Eq)
			  
data Adjacency a = Adj [(a, [a])]
		   deriving (Show, Eq)

data Friendly a = Edge [(a, a)]
		  deriving (Show, Eq)

graphToAdj :: (Eq a) => Graph a -> Adjacency a
graphToAdj (Graph [] _)	     = Adj []
graphToAdj (Graph (x:xs) ys) = Adj ((x, ys >>= f) : zs)
   where 
      f (a, b) 
         | a == x = [b]
         | b == x = [a]
         | otherwise = []
      Adj zs = graphToAdj (Graph xs ys)

adjToGraph :: (Eq a) => Adjacency a -> Graph a
adjToGraph (Adj [])          = Graph [] []
adjToGraph (Adj ((v, a):vs)) = Graph (v : xs) ((a >>= f) ++ ys)
   where
      f x = if (v, x) `elem` ys || (x, v) `elem` ys
            then []
            else [(v, x)]
      Graph xs ys = adjToGraph (Adj vs)

graphToFri :: (Eq a) => Graph a -> Friendly a
graphToFri (Graph [] _)  = Edge []
graphToFri (Graph xs ys) = Edge (ys ++ zip g g)
   where
      g = filter (\x -> all (\(a, b) -> x /= a && x /= b) ys) xs

friToGraph :: (Eq a) => Friendly a -> Graph a
friToGraph (Edge []) = Graph [] []
friToGraph (Edge vs) = Graph xs ys
   where
      xs = foldr acc [] $ concat $ map (\(a, b) -> [a, b]) vs
      ys = filter (uncurry (/=)) vs
      acc x xs = if x `elem` xs then xs else x : xs

adjToFri :: (Eq a) => Adjacency a -> Friendly a
adjToFri = graphToFri . adjToGraph

friToAdj :: (Eq a) => Friendly a -> Adjacency a
friToAdj = graphToAdj . friToGraph