module Math.SetCover.IntSet (Set, fromIntSet, findMin) where

import qualified Math.SetCover.Bit as Bit

import qualified Data.IntSet as IntSet
import Data.IntSet (IntSet)


data Set = Set {_complement :: Bool, _set :: IntSet}
   deriving (Eq, Ord)

fromIntSet :: IntSet -> Set
fromIntSet = Set False

findMin :: Set -> Int
findMin (Set c s) =
   if c
     then head $ dropWhile (flip IntSet.member s) [0..]
     else IntSet.findMin s

xor :: IntSet -> IntSet -> IntSet
xor x y = IntSet.difference (IntSet.union x y) (IntSet.intersection x y)

instance Bit.C Set where
   empty = fromIntSet IntSet.empty
   keepMinimum = fromIntSet . IntSet.singleton . findMin
   complement (Set c s) = Set (not c) s
   xor (Set c0 s0) (Set c1 s1) = Set (c0/=c1) (xor s0 s1)
   Set c0 s0 .&. Set c1 s1 =
      Set (c0&&c1) $
      case (c0,c1) of
         (False, False) -> IntSet.intersection s0 s1
         (False, True)  -> IntSet.difference s0 s1
         (True,  False) -> IntSet.difference s1 s0
         (True,  True)  -> IntSet.union s0 s1
   Set c0 s0 .|. Set c1 s1 =
      Set (c0||c1) $
      case (c0,c1) of
         (False, False) -> IntSet.union s0 s1
         (False, True)  -> IntSet.difference s1 s0
         (True,  False) -> IntSet.difference s0 s1
         (True,  True)  -> IntSet.intersection s0 s1