module Data.IntGraph.Undirected.Algorithms where import Prelude hiding (null) import Control.Applicative ((<|>)) import Data.Maybe (isJust, fromJust) import Data.IntGraph.Undirected -- | If there is a vertex cover of size k, returns the vertex cover -- | Otherwise Nothing -- | O(n*2^k) vertexCoverDec :: IntGraph -> Int -> Maybe [Node] vertexCoverDec graph k | nullEdges graph = Just [] | k == 0 = Nothing | otherwise = uCover <|> vCover where (u, v) = head $ edges graph uCover = (u :) <$> vertexCoverDec (removeNode u graph) (k - 1) vCover = (v :) <$> vertexCoverDec (removeNode v graph) (k - 1) -- | vertexCoverDec, but just returns true or false vertexCoverBool :: IntGraph -> Int -> Bool vertexCoverBool = (isJust .) . vertexCoverDec -- | Optimal vertex cover -- | Not all that efficient, just keeps trying difference values for k vertexCover :: IntGraph -> [Node] vertexCover graph = let f k = vertexCoverDec graph k <|> f (k + 1) in fromJust $ f 0