{-# LANGUAGE TypeFamilies #-}
module Cohort.IndexSet
( IndexSet
, Cohort.IndexSet.null
, Cohort.IndexSet.foldl'
, fromList
, toList
) where
import qualified Data.Set as Set (Set, foldl', null)
import EventDataTheory (Interval)
import GHC.Exts (IsList (..))
newtype IndexSet b
= MkIndexSet (Set.Set (Interval b))
deriving (IndexSet b -> IndexSet b -> Bool
forall b. Eq b => IndexSet b -> IndexSet b -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: IndexSet b -> IndexSet b -> Bool
$c/= :: forall b. Eq b => IndexSet b -> IndexSet b -> Bool
== :: IndexSet b -> IndexSet b -> Bool
$c== :: forall b. Eq b => IndexSet b -> IndexSet b -> Bool
Eq, Int -> IndexSet b -> ShowS
forall b. (Show b, Ord b) => Int -> IndexSet b -> ShowS
forall b. (Show b, Ord b) => [IndexSet b] -> ShowS
forall b. (Show b, Ord b) => IndexSet b -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [IndexSet b] -> ShowS
$cshowList :: forall b. (Show b, Ord b) => [IndexSet b] -> ShowS
show :: IndexSet b -> String
$cshow :: forall b. (Show b, Ord b) => IndexSet b -> String
showsPrec :: Int -> IndexSet b -> ShowS
$cshowsPrec :: forall b. (Show b, Ord b) => Int -> IndexSet b -> ShowS
Show)
instance (Ord b) => IsList (IndexSet b) where
type Item (IndexSet b) = (Interval b)
toList :: IndexSet b -> [Item (IndexSet b)]
toList (MkIndexSet Set (Interval b)
s) = forall l. IsList l => l -> [Item l]
toList Set (Interval b)
s
fromList :: [Item (IndexSet b)] -> IndexSet b
fromList [Item (IndexSet b)]
idxs = forall b. Set (Interval b) -> IndexSet b
MkIndexSet forall a b. (a -> b) -> a -> b
$ forall l. IsList l => [Item l] -> l
fromList [Item (IndexSet b)]
idxs
null :: IndexSet b -> Bool
null :: forall b. IndexSet b -> Bool
null (MkIndexSet Set (Interval b)
idxs) = forall a. Set a -> Bool
Set.null Set (Interval b)
idxs
foldl' :: (a -> Interval b -> a) -> a -> IndexSet b -> a
foldl' :: forall a b. (a -> Interval b -> a) -> a -> IndexSet b -> a
foldl' a -> Interval b -> a
f a
x0 (MkIndexSet Set (Interval b)
s) = forall a b. (a -> b -> a) -> a -> Set b -> a
Set.foldl' a -> Interval b -> a
f a
x0 Set (Interval b)
s