Safe Haskell | None |
---|---|
Language | Haskell2010 |
Small sets represented as immutable bit arrays for fast membership checking.
Membership checking is O(1), but all other operations are O(n)
where n is the size of the element type.
The element type needs to implement Bounded
and Ix
.
Mimics the interface of Set
.
Import as:
import qualified Agda.Utils.SmallSet as SmallSet
import Agda.Utils.SmallSet (SmallSet)
Synopsis
- data SmallSet a
- class Ord a => Ix a
- (\\) :: SmallSetElement a => SmallSet a -> SmallSet a -> SmallSet a
- complement :: SmallSetElement a => SmallSet a -> SmallSet a
- delete :: SmallSetElement a => a -> SmallSet a -> SmallSet a
- difference :: SmallSetElement a => SmallSet a -> SmallSet a -> SmallSet a
- elems :: SmallSetElement a => SmallSet a -> [a]
- empty :: SmallSetElement a => SmallSet a
- fromList :: SmallSetElement a => [a] -> SmallSet a
- fromAscList :: SmallSetElement a => [a] -> SmallSet a
- fromDistinctAscList :: SmallSetElement a => [a] -> SmallSet a
- insert :: SmallSetElement a => a -> SmallSet a -> SmallSet a
- intersection :: SmallSetElement a => SmallSet a -> SmallSet a -> SmallSet a
- isSubsetOf :: SmallSetElement a => SmallSet a -> SmallSet a -> Bool
- mapMemberShip :: SmallSetElement a => (Bool -> Bool) -> SmallSet a -> SmallSet a
- member :: SmallSetElement a => a -> SmallSet a -> Bool
- notMember :: SmallSetElement a => a -> SmallSet a -> Bool
- null :: SmallSetElement a => SmallSet a -> Bool
- singleton :: SmallSetElement a => a -> SmallSet a
- toList :: SmallSetElement a => SmallSet a -> [a]
- toAscList :: SmallSetElement a => SmallSet a -> [a]
- total :: SmallSetElement a => SmallSet a
- union :: SmallSetElement a => SmallSet a -> SmallSet a -> SmallSet a
- zipMemberShipWith :: SmallSetElement a => (Bool -> Bool -> Bool) -> SmallSet a -> SmallSet a -> SmallSet a
Documentation
Instances
Ix a => Eq (SmallSet a) Source # | |
(Data a, Ix a) => Data (SmallSet a) Source # | |
Defined in Agda.Utils.SmallSet gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> SmallSet a -> c (SmallSet a) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (SmallSet a) # toConstr :: SmallSet a -> Constr # dataTypeOf :: SmallSet a -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (SmallSet a)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (SmallSet a)) # gmapT :: (forall b. Data b => b -> b) -> SmallSet a -> SmallSet a # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> SmallSet a -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> SmallSet a -> r # gmapQ :: (forall d. Data d => d -> u) -> SmallSet a -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> SmallSet a -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> SmallSet a -> m (SmallSet a) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> SmallSet a -> m (SmallSet a) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> SmallSet a -> m (SmallSet a) # | |
Ix a => Ord (SmallSet a) Source # | |
(Ix a, Show a) => Show (SmallSet a) Source # | |
The Ix
class is used to map a contiguous subrange of values in
a type onto integers. It is used primarily for array indexing
(see the array package).
The first argument (l,u)
of each of these operations is a pair
specifying the lower and upper bounds of a contiguous subrange of values.
An implementation is entitled to assume the following laws about these operations:
range, (index | unsafeIndex), inRange
Instances
complement :: SmallSetElement a => SmallSet a -> SmallSet a Source #
Time O(n).
fromAscList :: SmallSetElement a => [a] -> SmallSet a Source #
Time O(n).
fromDistinctAscList :: SmallSetElement a => [a] -> SmallSet a Source #
Time O(n).