{-# LANGUAGE FlexibleInstances, MultiParamTypeClasses #-}
module Data.Matroid.Algorithms.Greedy where
import Data.Matroid.Typeclass
import Data.Set (Set)
import qualified Data.Set as S
greedy :: Matroid m a =>
(m a)
-> [a]
-> Set a
greedy :: m a -> [a] -> Set a
greedy = Set a -> m a -> [a] -> Set a
forall (m :: * -> *) a. Matroid m a => Set a -> m a -> [a] -> Set a
greedyStep Set a
forall a. Set a
S.empty
where greedyStep :: Set a -> m a -> [a] -> Set a
greedyStep Set a
x0 m a
m (a
r:[a]
rs)
| m a -> Set a -> Bool
forall (m :: * -> *) a. Matroid m a => m a -> Set a -> Bool
indep m a
m Set a
x0r = Set a -> m a -> [a] -> Set a
greedyStep Set a
x0r m a
m [a]
rs
| Bool
otherwise = Set a -> m a -> [a] -> Set a
greedyStep Set a
x0 m a
m [a]
rs
where x0r :: Set a
x0r = a -> Set a -> Set a
forall a. Ord a => a -> Set a -> Set a
S.insert a
r Set a
x0
greedyStep Set a
x0 m a
_ [a]
_ = Set a
x0
greedy1 :: Matroid m a =>
(m a)
-> (Set a -> Maybe a)
-> Set a
greedy1 :: m a -> (Set a -> Maybe a) -> Set a
greedy1 m a
m Set a -> Maybe a
choice = Set a -> Set a -> Set a
greedyStep Set a
forall a. Set a
S.empty (Set a -> Set a) -> Set a -> Set a
forall a b. (a -> b) -> a -> b
$ m a -> Set a
forall (m :: * -> *) a. Matroid m a => m a -> Set a
loops m a
m
where e :: Set a
e = m a -> Set a
forall (m :: * -> *) a. Matroid m a => m a -> Set a
groundset m a
m
greedyStep :: Set a -> Set a -> Set a
greedyStep Set a
x0 Set a
clx0
| Maybe a
chosen Maybe a -> Maybe a -> Bool
forall a. Eq a => a -> a -> Bool
== Maybe a
forall a. Maybe a
Nothing = Set a
x0
| Bool
otherwise = Set a -> Set a -> Set a
greedyStep Set a
x0c Set a
clx0c
where chosen :: Maybe a
chosen = Set a -> Maybe a
choice (Set a -> Set a -> Set a
forall a. Ord a => Set a -> Set a -> Set a
S.difference Set a
e Set a
clx0)
Just a
c = Maybe a
chosen
x0c :: Set a
x0c = a -> Set a -> Set a
forall a. Ord a => a -> Set a -> Set a
S.insert a
c Set a
x0
clx0c :: Set a
clx0c = m a -> Set a -> Set a
forall (m :: * -> *) a. Matroid m a => m a -> Set a -> Set a
cl m a
m (Set a -> Set a) -> Set a -> Set a
forall a b. (a -> b) -> a -> b
$ a -> Set a -> Set a
forall a. Ord a => a -> Set a -> Set a
S.insert a
c Set a
clx0