{-# LANGUAGE BangPatterns #-}
{-# LANGUAGE BlockArguments #-}
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE DeriveDataTypeable #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE PolyKinds #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE UnboxedTuples #-}
{-# LANGUAGE UnicodeSyntax #-}
module Data.Enum.Set.Base
(
EnumSet
, empty
, singleton
, fromFoldable
, insert
, delete
, member
, notMember
, null
, size
, isSubsetOf
, union
, difference
, (\\)
, symmetricDifference
, intersection
, filter
, partition
, map
, map'
, foldl, foldl', foldr, foldr'
, foldl1, foldl1', foldr1, foldr1'
, foldMap
, traverse
, any
, all
, minimum
, maximum
, deleteMin
, deleteMax
, minView
, maxView
, toList
, fromRaw
, toRaw
) where
import qualified GHC.Exts
import qualified Data.Foldable as F
import Prelude hiding (all, any, filter, foldl, foldl1, foldMap, foldr, foldr1, map, maximum, minimum, null, traverse)
import Control.Applicative (liftA2)
import Control.DeepSeq (NFData)
import Data.Aeson (ToJSON(..))
import Data.Bits
import Data.Data (Data)
import Data.Vector.Unboxed (Vector, MVector, Unbox)
import Foreign.Storable (Storable)
import GHC.Exts (IsList(Item), build)
import Text.Read
import qualified Data.Vector.Generic as G
import qualified Data.Vector.Generic.Mutable as M
import qualified Data.Vector.Primitive as P
import qualified Data.Containers
import Data.Containers (SetContainer, IsSet)
import qualified Data.MonoTraversable
import Data.MonoTraversable (Element, GrowingAppend, MonoFoldable, MonoFunctor, MonoPointed, MonoTraversable)
newtype EnumSet word a = EnumSet word
deriving (EnumSet word a -> EnumSet word a -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
forall word k (a :: k).
Eq word =>
EnumSet word a -> EnumSet word a -> Bool
/= :: EnumSet word a -> EnumSet word a -> Bool
$c/= :: forall word k (a :: k).
Eq word =>
EnumSet word a -> EnumSet word a -> Bool
== :: EnumSet word a -> EnumSet word a -> Bool
$c== :: forall word k (a :: k).
Eq word =>
EnumSet word a -> EnumSet word a -> Bool
Eq, EnumSet word a -> EnumSet word a -> Bool
EnumSet word a -> EnumSet word a -> Ordering
EnumSet word a -> EnumSet word a -> EnumSet word a
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
forall {word} {k} {a :: k}. Ord word => Eq (EnumSet word a)
forall word k (a :: k).
Ord word =>
EnumSet word a -> EnumSet word a -> Bool
forall word k (a :: k).
Ord word =>
EnumSet word a -> EnumSet word a -> Ordering
forall word k (a :: k).
Ord word =>
EnumSet word a -> EnumSet word a -> EnumSet word a
min :: EnumSet word a -> EnumSet word a -> EnumSet word a
$cmin :: forall word k (a :: k).
Ord word =>
EnumSet word a -> EnumSet word a -> EnumSet word a
max :: EnumSet word a -> EnumSet word a -> EnumSet word a
$cmax :: forall word k (a :: k).
Ord word =>
EnumSet word a -> EnumSet word a -> EnumSet word a
>= :: EnumSet word a -> EnumSet word a -> Bool
$c>= :: forall word k (a :: k).
Ord word =>
EnumSet word a -> EnumSet word a -> Bool
> :: EnumSet word a -> EnumSet word a -> Bool
$c> :: forall word k (a :: k).
Ord word =>
EnumSet word a -> EnumSet word a -> Bool
<= :: EnumSet word a -> EnumSet word a -> Bool
$c<= :: forall word k (a :: k).
Ord word =>
EnumSet word a -> EnumSet word a -> Bool
< :: EnumSet word a -> EnumSet word a -> Bool
$c< :: forall word k (a :: k).
Ord word =>
EnumSet word a -> EnumSet word a -> Bool
compare :: EnumSet word a -> EnumSet word a -> Ordering
$ccompare :: forall word k (a :: k).
Ord word =>
EnumSet word a -> EnumSet word a -> Ordering
Ord, EnumSet word a -> DataType
EnumSet word a -> Constr
forall a.
Typeable a
-> (forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall {word} {k} {a :: k}.
(Typeable a, Typeable k, Data word) =>
Typeable (EnumSet word a)
forall word k (a :: k).
(Typeable a, Typeable k, Data word) =>
EnumSet word a -> DataType
forall word k (a :: k).
(Typeable a, Typeable k, Data word) =>
EnumSet word a -> Constr
forall word k (a :: k).
(Typeable a, Typeable k, Data word) =>
(forall b. Data b => b -> b) -> EnumSet word a -> EnumSet word a
forall word k (a :: k) u.
(Typeable a, Typeable k, Data word) =>
Int -> (forall d. Data d => d -> u) -> EnumSet word a -> u
forall word k (a :: k) u.
(Typeable a, Typeable k, Data word) =>
(forall d. Data d => d -> u) -> EnumSet word a -> [u]
forall word k (a :: k) r r'.
(Typeable a, Typeable k, Data word) =>
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> EnumSet word a -> r
forall word k (a :: k) r r'.
(Typeable a, Typeable k, Data word) =>
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> EnumSet word a -> r
forall word k (a :: k) (m :: * -> *).
(Typeable a, Typeable k, Data word, Monad m) =>
(forall d. Data d => d -> m d)
-> EnumSet word a -> m (EnumSet word a)
forall word k (a :: k) (m :: * -> *).
(Typeable a, Typeable k, Data word, MonadPlus m) =>
(forall d. Data d => d -> m d)
-> EnumSet word a -> m (EnumSet word a)
forall word k (a :: k) (c :: * -> *).
(Typeable a, Typeable k, Data word) =>
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (EnumSet word a)
forall word k (a :: k) (c :: * -> *).
(Typeable a, Typeable k, Data word) =>
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> EnumSet word a -> c (EnumSet word a)
forall word k (a :: k) (t :: * -> *) (c :: * -> *).
(Typeable a, Typeable k, Data word, Typeable t) =>
(forall d. Data d => c (t d)) -> Maybe (c (EnumSet word a))
forall word k (a :: k) (t :: * -> * -> *) (c :: * -> *).
(Typeable a, Typeable k, Data word, Typeable t) =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (EnumSet word a))
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (EnumSet word a)
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> EnumSet word a -> c (EnumSet word a)
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> EnumSet word a -> m (EnumSet word a)
$cgmapMo :: forall word k (a :: k) (m :: * -> *).
(Typeable a, Typeable k, Data word, MonadPlus m) =>
(forall d. Data d => d -> m d)
-> EnumSet word a -> m (EnumSet word a)
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> EnumSet word a -> m (EnumSet word a)
$cgmapMp :: forall word k (a :: k) (m :: * -> *).
(Typeable a, Typeable k, Data word, MonadPlus m) =>
(forall d. Data d => d -> m d)
-> EnumSet word a -> m (EnumSet word a)
gmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> EnumSet word a -> m (EnumSet word a)
$cgmapM :: forall word k (a :: k) (m :: * -> *).
(Typeable a, Typeable k, Data word, Monad m) =>
(forall d. Data d => d -> m d)
-> EnumSet word a -> m (EnumSet word a)
gmapQi :: forall u.
Int -> (forall d. Data d => d -> u) -> EnumSet word a -> u
$cgmapQi :: forall word k (a :: k) u.
(Typeable a, Typeable k, Data word) =>
Int -> (forall d. Data d => d -> u) -> EnumSet word a -> u
gmapQ :: forall u. (forall d. Data d => d -> u) -> EnumSet word a -> [u]
$cgmapQ :: forall word k (a :: k) u.
(Typeable a, Typeable k, Data word) =>
(forall d. Data d => d -> u) -> EnumSet word a -> [u]
gmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> EnumSet word a -> r
$cgmapQr :: forall word k (a :: k) r r'.
(Typeable a, Typeable k, Data word) =>
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> EnumSet word a -> r
gmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> EnumSet word a -> r
$cgmapQl :: forall word k (a :: k) r r'.
(Typeable a, Typeable k, Data word) =>
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> EnumSet word a -> r
gmapT :: (forall b. Data b => b -> b) -> EnumSet word a -> EnumSet word a
$cgmapT :: forall word k (a :: k).
(Typeable a, Typeable k, Data word) =>
(forall b. Data b => b -> b) -> EnumSet word a -> EnumSet word a
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (EnumSet word a))
$cdataCast2 :: forall word k (a :: k) (t :: * -> * -> *) (c :: * -> *).
(Typeable a, Typeable k, Data word, Typeable t) =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (EnumSet word a))
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c (EnumSet word a))
$cdataCast1 :: forall word k (a :: k) (t :: * -> *) (c :: * -> *).
(Typeable a, Typeable k, Data word, Typeable t) =>
(forall d. Data d => c (t d)) -> Maybe (c (EnumSet word a))
dataTypeOf :: EnumSet word a -> DataType
$cdataTypeOf :: forall word k (a :: k).
(Typeable a, Typeable k, Data word) =>
EnumSet word a -> DataType
toConstr :: EnumSet word a -> Constr
$ctoConstr :: forall word k (a :: k).
(Typeable a, Typeable k, Data word) =>
EnumSet word a -> Constr
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (EnumSet word a)
$cgunfold :: forall word k (a :: k) (c :: * -> *).
(Typeable a, Typeable k, Data word) =>
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (EnumSet word a)
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> EnumSet word a -> c (EnumSet word a)
$cgfoldl :: forall word k (a :: k) (c :: * -> *).
(Typeable a, Typeable k, Data word) =>
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> EnumSet word a -> c (EnumSet word a)
Data, Ptr (EnumSet word a) -> IO (EnumSet word a)
Ptr (EnumSet word a) -> Int -> IO (EnumSet word a)
Ptr (EnumSet word a) -> Int -> EnumSet word a -> IO ()
Ptr (EnumSet word a) -> EnumSet word a -> IO ()
EnumSet word a -> Int
forall b. Ptr b -> Int -> IO (EnumSet word a)
forall b. Ptr b -> Int -> EnumSet word a -> IO ()
forall a.
(a -> Int)
-> (a -> Int)
-> (Ptr a -> Int -> IO a)
-> (Ptr a -> Int -> a -> IO ())
-> (forall b. Ptr b -> Int -> IO a)
-> (forall b. Ptr b -> Int -> a -> IO ())
-> (Ptr a -> IO a)
-> (Ptr a -> a -> IO ())
-> Storable a
forall word k (a :: k).
Storable word =>
Ptr (EnumSet word a) -> IO (EnumSet word a)
forall word k (a :: k).
Storable word =>
Ptr (EnumSet word a) -> Int -> IO (EnumSet word a)
forall word k (a :: k).
Storable word =>
Ptr (EnumSet word a) -> Int -> EnumSet word a -> IO ()
forall word k (a :: k).
Storable word =>
Ptr (EnumSet word a) -> EnumSet word a -> IO ()
forall word k (a :: k). Storable word => EnumSet word a -> Int
forall word k (a :: k) b.
Storable word =>
Ptr b -> Int -> IO (EnumSet word a)
forall word k (a :: k) b.
Storable word =>
Ptr b -> Int -> EnumSet word a -> IO ()
poke :: Ptr (EnumSet word a) -> EnumSet word a -> IO ()
$cpoke :: forall word k (a :: k).
Storable word =>
Ptr (EnumSet word a) -> EnumSet word a -> IO ()
peek :: Ptr (EnumSet word a) -> IO (EnumSet word a)
$cpeek :: forall word k (a :: k).
Storable word =>
Ptr (EnumSet word a) -> IO (EnumSet word a)
pokeByteOff :: forall b. Ptr b -> Int -> EnumSet word a -> IO ()
$cpokeByteOff :: forall word k (a :: k) b.
Storable word =>
Ptr b -> Int -> EnumSet word a -> IO ()
peekByteOff :: forall b. Ptr b -> Int -> IO (EnumSet word a)
$cpeekByteOff :: forall word k (a :: k) b.
Storable word =>
Ptr b -> Int -> IO (EnumSet word a)
pokeElemOff :: Ptr (EnumSet word a) -> Int -> EnumSet word a -> IO ()
$cpokeElemOff :: forall word k (a :: k).
Storable word =>
Ptr (EnumSet word a) -> Int -> EnumSet word a -> IO ()
peekElemOff :: Ptr (EnumSet word a) -> Int -> IO (EnumSet word a)
$cpeekElemOff :: forall word k (a :: k).
Storable word =>
Ptr (EnumSet word a) -> Int -> IO (EnumSet word a)
alignment :: EnumSet word a -> Int
$calignment :: forall word k (a :: k). Storable word => EnumSet word a -> Int
sizeOf :: EnumSet word a -> Int
$csizeOf :: forall word k (a :: k). Storable word => EnumSet word a -> Int
Storable, EnumSet word a -> ()
forall a. (a -> ()) -> NFData a
forall word k (a :: k). NFData word => EnumSet word a -> ()
rnf :: EnumSet word a -> ()
$crnf :: forall word k (a :: k). NFData word => EnumSet word a -> ()
NFData, Addr# -> Int# -> EnumSet word a
ByteArray# -> Int# -> EnumSet word a
EnumSet word a -> Int#
forall s.
Addr# -> Int# -> Int# -> EnumSet word a -> State# s -> State# s
forall s.
Addr# -> Int# -> State# s -> (# State# s, EnumSet word a #)
forall s. Addr# -> Int# -> EnumSet word a -> State# s -> State# s
forall s.
MutableByteArray# s
-> Int# -> Int# -> EnumSet word a -> State# s -> State# s
forall s.
MutableByteArray# s
-> Int# -> State# s -> (# State# s, EnumSet word a #)
forall s.
MutableByteArray# s
-> Int# -> EnumSet word a -> State# s -> State# s
forall a.
(a -> Int#)
-> (a -> Int#)
-> (ByteArray# -> Int# -> a)
-> (forall s.
MutableByteArray# s -> Int# -> State# s -> (# State# s, a #))
-> (forall s.
MutableByteArray# s -> Int# -> a -> State# s -> State# s)
-> (forall s.
MutableByteArray# s -> Int# -> Int# -> a -> State# s -> State# s)
-> (Addr# -> Int# -> a)
-> (forall s. Addr# -> Int# -> State# s -> (# State# s, a #))
-> (forall s. Addr# -> Int# -> a -> State# s -> State# s)
-> (forall s. Addr# -> Int# -> Int# -> a -> State# s -> State# s)
-> Prim a
forall word k (a :: k).
Prim word =>
Addr# -> Int# -> EnumSet word a
forall word k (a :: k).
Prim word =>
ByteArray# -> Int# -> EnumSet word a
forall word k (a :: k). Prim word => EnumSet word a -> Int#
forall word k (a :: k) s.
Prim word =>
Addr# -> Int# -> Int# -> EnumSet word a -> State# s -> State# s
forall word k (a :: k) s.
Prim word =>
Addr# -> Int# -> State# s -> (# State# s, EnumSet word a #)
forall word k (a :: k) s.
Prim word =>
Addr# -> Int# -> EnumSet word a -> State# s -> State# s
forall word k (a :: k) s.
Prim word =>
MutableByteArray# s
-> Int# -> Int# -> EnumSet word a -> State# s -> State# s
forall word k (a :: k) s.
Prim word =>
MutableByteArray# s
-> Int# -> State# s -> (# State# s, EnumSet word a #)
forall word k (a :: k) s.
Prim word =>
MutableByteArray# s
-> Int# -> EnumSet word a -> State# s -> State# s
setOffAddr# :: forall s.
Addr# -> Int# -> Int# -> EnumSet word a -> State# s -> State# s
$csetOffAddr# :: forall word k (a :: k) s.
Prim word =>
Addr# -> Int# -> Int# -> EnumSet word a -> State# s -> State# s
writeOffAddr# :: forall s. Addr# -> Int# -> EnumSet word a -> State# s -> State# s
$cwriteOffAddr# :: forall word k (a :: k) s.
Prim word =>
Addr# -> Int# -> EnumSet word a -> State# s -> State# s
readOffAddr# :: forall s.
Addr# -> Int# -> State# s -> (# State# s, EnumSet word a #)
$creadOffAddr# :: forall word k (a :: k) s.
Prim word =>
Addr# -> Int# -> State# s -> (# State# s, EnumSet word a #)
indexOffAddr# :: Addr# -> Int# -> EnumSet word a
$cindexOffAddr# :: forall word k (a :: k).
Prim word =>
Addr# -> Int# -> EnumSet word a
setByteArray# :: forall s.
MutableByteArray# s
-> Int# -> Int# -> EnumSet word a -> State# s -> State# s
$csetByteArray# :: forall word k (a :: k) s.
Prim word =>
MutableByteArray# s
-> Int# -> Int# -> EnumSet word a -> State# s -> State# s
writeByteArray# :: forall s.
MutableByteArray# s
-> Int# -> EnumSet word a -> State# s -> State# s
$cwriteByteArray# :: forall word k (a :: k) s.
Prim word =>
MutableByteArray# s
-> Int# -> EnumSet word a -> State# s -> State# s
readByteArray# :: forall s.
MutableByteArray# s
-> Int# -> State# s -> (# State# s, EnumSet word a #)
$creadByteArray# :: forall word k (a :: k) s.
Prim word =>
MutableByteArray# s
-> Int# -> State# s -> (# State# s, EnumSet word a #)
indexByteArray# :: ByteArray# -> Int# -> EnumSet word a
$cindexByteArray# :: forall word k (a :: k).
Prim word =>
ByteArray# -> Int# -> EnumSet word a
alignment# :: EnumSet word a -> Int#
$calignment# :: forall word k (a :: k). Prim word => EnumSet word a -> Int#
sizeOf# :: EnumSet word a -> Int#
$csizeOf# :: forall word k (a :: k). Prim word => EnumSet word a -> Int#
P.Prim, forall a. Vector Vector a -> MVector MVector a -> Unbox a
forall {word} {k} {a :: k}.
Prim word =>
Vector Vector (EnumSet word a)
forall {word} {k} {a :: k}.
Prim word =>
MVector MVector (EnumSet word a)
Unbox)
newtype instance MVector s (EnumSet word a) = MV_EnumSet (P.MVector s (EnumSet word a))
newtype instance Vector (EnumSet word a) = V_EnumSet (P.Vector (EnumSet word a))
instance P.Prim word => M.MVector MVector (EnumSet word a) where
basicLength :: forall s. MVector s (EnumSet word a) -> Int
basicLength (MV_EnumSet MVector s (EnumSet word a)
v) = forall (v :: * -> * -> *) a s. MVector v a => v s a -> Int
M.basicLength MVector s (EnumSet word a)
v
{-# INLINE basicLength #-}
basicUnsafeSlice :: forall s.
Int
-> Int -> MVector s (EnumSet word a) -> MVector s (EnumSet word a)
basicUnsafeSlice Int
i Int
n (MV_EnumSet MVector s (EnumSet word a)
v) = forall k s word (a :: k).
MVector s (EnumSet word a) -> MVector s (EnumSet word a)
MV_EnumSet forall a b. (a -> b) -> a -> b
$ forall (v :: * -> * -> *) a s.
MVector v a =>
Int -> Int -> v s a -> v s a
M.basicUnsafeSlice Int
i Int
n MVector s (EnumSet word a)
v
{-# INLINE basicUnsafeSlice #-}
basicOverlaps :: forall s.
MVector s (EnumSet word a) -> MVector s (EnumSet word a) -> Bool
basicOverlaps (MV_EnumSet MVector s (EnumSet word a)
v1) (MV_EnumSet MVector s (EnumSet word a)
v2) = forall (v :: * -> * -> *) a s.
MVector v a =>
v s a -> v s a -> Bool
M.basicOverlaps MVector s (EnumSet word a)
v1 MVector s (EnumSet word a)
v2
{-# INLINE basicOverlaps #-}
basicUnsafeNew :: forall (m :: * -> *).
PrimMonad m =>
Int -> m (MVector (PrimState m) (EnumSet word a))
basicUnsafeNew Int
n = forall k s word (a :: k).
MVector s (EnumSet word a) -> MVector s (EnumSet word a)
MV_EnumSet forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (v :: * -> * -> *) a (m :: * -> *).
(MVector v a, PrimMonad m) =>
Int -> m (v (PrimState m) a)
M.basicUnsafeNew Int
n
{-# INLINE basicUnsafeNew #-}
basicInitialize :: forall (m :: * -> *).
PrimMonad m =>
MVector (PrimState m) (EnumSet word a) -> m ()
basicInitialize (MV_EnumSet MVector (PrimState m) (EnumSet word a)
v) = forall (v :: * -> * -> *) a (m :: * -> *).
(MVector v a, PrimMonad m) =>
v (PrimState m) a -> m ()
M.basicInitialize MVector (PrimState m) (EnumSet word a)
v
{-# INLINE basicInitialize #-}
basicUnsafeReplicate :: forall (m :: * -> *).
PrimMonad m =>
Int -> EnumSet word a -> m (MVector (PrimState m) (EnumSet word a))
basicUnsafeReplicate Int
n EnumSet word a
x = forall k s word (a :: k).
MVector s (EnumSet word a) -> MVector s (EnumSet word a)
MV_EnumSet forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (v :: * -> * -> *) a (m :: * -> *).
(MVector v a, PrimMonad m) =>
Int -> a -> m (v (PrimState m) a)
M.basicUnsafeReplicate Int
n EnumSet word a
x
{-# INLINE basicUnsafeReplicate #-}
basicUnsafeRead :: forall (m :: * -> *).
PrimMonad m =>
MVector (PrimState m) (EnumSet word a) -> Int -> m (EnumSet word a)
basicUnsafeRead (MV_EnumSet MVector (PrimState m) (EnumSet word a)
v) Int
i = forall (v :: * -> * -> *) a (m :: * -> *).
(MVector v a, PrimMonad m) =>
v (PrimState m) a -> Int -> m a
M.basicUnsafeRead MVector (PrimState m) (EnumSet word a)
v Int
i
{-# INLINE basicUnsafeRead #-}
basicUnsafeWrite :: forall (m :: * -> *).
PrimMonad m =>
MVector (PrimState m) (EnumSet word a)
-> Int -> EnumSet word a -> m ()
basicUnsafeWrite (MV_EnumSet MVector (PrimState m) (EnumSet word a)
v) Int
i EnumSet word a
x = forall (v :: * -> * -> *) a (m :: * -> *).
(MVector v a, PrimMonad m) =>
v (PrimState m) a -> Int -> a -> m ()
M.basicUnsafeWrite MVector (PrimState m) (EnumSet word a)
v Int
i EnumSet word a
x
{-# INLINE basicUnsafeWrite #-}
basicClear :: forall (m :: * -> *).
PrimMonad m =>
MVector (PrimState m) (EnumSet word a) -> m ()
basicClear (MV_EnumSet MVector (PrimState m) (EnumSet word a)
v) = forall (v :: * -> * -> *) a (m :: * -> *).
(MVector v a, PrimMonad m) =>
v (PrimState m) a -> m ()
M.basicClear MVector (PrimState m) (EnumSet word a)
v
{-# INLINE basicClear #-}
basicSet :: forall (m :: * -> *).
PrimMonad m =>
MVector (PrimState m) (EnumSet word a) -> EnumSet word a -> m ()
basicSet (MV_EnumSet MVector (PrimState m) (EnumSet word a)
v) EnumSet word a
x = forall (v :: * -> * -> *) a (m :: * -> *).
(MVector v a, PrimMonad m) =>
v (PrimState m) a -> a -> m ()
M.basicSet MVector (PrimState m) (EnumSet word a)
v EnumSet word a
x
{-# INLINE basicSet #-}
basicUnsafeCopy :: forall (m :: * -> *).
PrimMonad m =>
MVector (PrimState m) (EnumSet word a)
-> MVector (PrimState m) (EnumSet word a) -> m ()
basicUnsafeCopy (MV_EnumSet MVector (PrimState m) (EnumSet word a)
v1) (MV_EnumSet MVector (PrimState m) (EnumSet word a)
v2) = forall (v :: * -> * -> *) a (m :: * -> *).
(MVector v a, PrimMonad m) =>
v (PrimState m) a -> v (PrimState m) a -> m ()
M.basicUnsafeCopy MVector (PrimState m) (EnumSet word a)
v1 MVector (PrimState m) (EnumSet word a)
v2
{-# INLINE basicUnsafeCopy #-}
basicUnsafeMove :: forall (m :: * -> *).
PrimMonad m =>
MVector (PrimState m) (EnumSet word a)
-> MVector (PrimState m) (EnumSet word a) -> m ()
basicUnsafeMove (MV_EnumSet MVector (PrimState m) (EnumSet word a)
v1) (MV_EnumSet MVector (PrimState m) (EnumSet word a)
v2) = forall (v :: * -> * -> *) a (m :: * -> *).
(MVector v a, PrimMonad m) =>
v (PrimState m) a -> v (PrimState m) a -> m ()
M.basicUnsafeMove MVector (PrimState m) (EnumSet word a)
v1 MVector (PrimState m) (EnumSet word a)
v2
{-# INLINE basicUnsafeMove #-}
basicUnsafeGrow :: forall (m :: * -> *).
PrimMonad m =>
MVector (PrimState m) (EnumSet word a)
-> Int -> m (MVector (PrimState m) (EnumSet word a))
basicUnsafeGrow (MV_EnumSet MVector (PrimState m) (EnumSet word a)
v) Int
n = forall k s word (a :: k).
MVector s (EnumSet word a) -> MVector s (EnumSet word a)
MV_EnumSet forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (v :: * -> * -> *) a (m :: * -> *).
(MVector v a, PrimMonad m) =>
v (PrimState m) a -> Int -> m (v (PrimState m) a)
M.basicUnsafeGrow MVector (PrimState m) (EnumSet word a)
v Int
n
{-# INLINE basicUnsafeGrow #-}
instance P.Prim word => G.Vector Vector (EnumSet word a) where
basicUnsafeFreeze :: forall (m :: * -> *).
PrimMonad m =>
Mutable Vector (PrimState m) (EnumSet word a)
-> m (Vector (EnumSet word a))
basicUnsafeFreeze (MV_EnumSet MVector (PrimState m) (EnumSet word a)
v) = forall k word (a :: k).
Vector (EnumSet word a) -> Vector (EnumSet word a)
V_EnumSet forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (v :: * -> *) a (m :: * -> *).
(Vector v a, PrimMonad m) =>
Mutable v (PrimState m) a -> m (v a)
G.basicUnsafeFreeze MVector (PrimState m) (EnumSet word a)
v
{-# INLINE basicUnsafeFreeze #-}
basicUnsafeThaw :: forall (m :: * -> *).
PrimMonad m =>
Vector (EnumSet word a)
-> m (Mutable Vector (PrimState m) (EnumSet word a))
basicUnsafeThaw (V_EnumSet Vector (EnumSet word a)
v) = forall k s word (a :: k).
MVector s (EnumSet word a) -> MVector s (EnumSet word a)
MV_EnumSet forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (v :: * -> *) a (m :: * -> *).
(Vector v a, PrimMonad m) =>
v a -> m (Mutable v (PrimState m) a)
G.basicUnsafeThaw Vector (EnumSet word a)
v
{-# INLINE basicUnsafeThaw #-}
basicLength :: Vector (EnumSet word a) -> Int
basicLength (V_EnumSet Vector (EnumSet word a)
v) = forall (v :: * -> *) a. Vector v a => v a -> Int
G.basicLength Vector (EnumSet word a)
v
{-# INLINE basicLength #-}
basicUnsafeSlice :: Int -> Int -> Vector (EnumSet word a) -> Vector (EnumSet word a)
basicUnsafeSlice Int
i Int
n (V_EnumSet Vector (EnumSet word a)
v) = forall k word (a :: k).
Vector (EnumSet word a) -> Vector (EnumSet word a)
V_EnumSet forall a b. (a -> b) -> a -> b
$ forall (v :: * -> *) a. Vector v a => Int -> Int -> v a -> v a
G.basicUnsafeSlice Int
i Int
n Vector (EnumSet word a)
v
{-# INLINE basicUnsafeSlice #-}
basicUnsafeIndexM :: forall (m :: * -> *).
Monad m =>
Vector (EnumSet word a) -> Int -> m (EnumSet word a)
basicUnsafeIndexM (V_EnumSet Vector (EnumSet word a)
v) Int
i = forall (v :: * -> *) a (m :: * -> *).
(Vector v a, Monad m) =>
v a -> Int -> m a
G.basicUnsafeIndexM Vector (EnumSet word a)
v Int
i
{-# INLINE basicUnsafeIndexM #-}
basicUnsafeCopy :: forall (m :: * -> *).
PrimMonad m =>
Mutable Vector (PrimState m) (EnumSet word a)
-> Vector (EnumSet word a) -> m ()
basicUnsafeCopy (MV_EnumSet MVector (PrimState m) (EnumSet word a)
mv) (V_EnumSet Vector (EnumSet word a)
v) = forall (v :: * -> *) a (m :: * -> *).
(Vector v a, PrimMonad m) =>
Mutable v (PrimState m) a -> v a -> m ()
G.basicUnsafeCopy MVector (PrimState m) (EnumSet word a)
mv Vector (EnumSet word a)
v
{-# INLINE basicUnsafeCopy #-}
elemseq :: forall b. Vector (EnumSet word a) -> EnumSet word a -> b -> b
elemseq Vector (EnumSet word a)
_ = seq :: forall a b. a -> b -> b
seq
{-# INLINE elemseq #-}
instance Bits w => Semigroup (EnumSet w a) where
<> :: EnumSet w a -> EnumSet w a -> EnumSet w a
(<>) = forall k w (a :: k).
Bits w =>
EnumSet w a -> EnumSet w a -> EnumSet w a
union
{-# INLINE (<>) #-}
instance Bits w => Monoid (EnumSet w a) where
mempty :: EnumSet w a
mempty = forall k w (a :: k). Bits w => EnumSet w a
empty
{-# INLINE mempty #-}
instance (Bits w, Enum a) => MonoPointed (EnumSet w a) where
opoint :: Element (EnumSet w a) -> EnumSet w a
opoint = forall w a. (Bits w, Enum a) => a -> EnumSet w a
singleton
{-# INLINE opoint #-}
instance (FiniteBits w, Num w, Enum a) => IsList (EnumSet w a) where
type Item (EnumSet w a) = a
fromList :: [Item (EnumSet w a)] -> EnumSet w a
fromList = forall (f :: * -> *) w a.
(Foldable f, Bits w, Enum a) =>
f a -> EnumSet w a
fromFoldable
{-# INLINE fromList #-}
toList :: EnumSet w a -> [Item (EnumSet w a)]
toList = forall w a. (FiniteBits w, Num w, Enum a) => EnumSet w a -> [a]
toList
{-# INLINE toList #-}
instance (FiniteBits w, Num w, Enum a, ToJSON a) => ToJSON (EnumSet w a) where
toJSON :: EnumSet w a -> Value
toJSON = forall a. ToJSON a => a -> Value
toJSON forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall w a. (FiniteBits w, Num w, Enum a) => EnumSet w a -> [a]
toList
{-# INLINE toJSON #-}
toEncoding :: EnumSet w a -> Encoding
toEncoding = forall a. ToJSON a => a -> Encoding
toEncoding forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall w a. (FiniteBits w, Num w, Enum a) => EnumSet w a -> [a]
toList
{-# INLINE toEncoding #-}
type instance Element (EnumSet w a) = a
instance (FiniteBits w, Num w, Enum a) => MonoFunctor (EnumSet w a) where
omap :: (Element (EnumSet w a) -> Element (EnumSet w a))
-> EnumSet w a -> EnumSet w a
omap = forall w a b.
(FiniteBits w, Num w, Enum a, Enum b) =>
(a -> b) -> EnumSet w a -> EnumSet w b
map
{-# INLINE omap #-}
instance (FiniteBits w, Num w, Enum a) => MonoFoldable (EnumSet w a) where
ofoldMap :: forall m.
Monoid m =>
(Element (EnumSet w a) -> m) -> EnumSet w a -> m
ofoldMap = forall m w a.
(Monoid m, FiniteBits w, Num w, Enum a) =>
(a -> m) -> EnumSet w a -> m
foldMap
{-# INLINE ofoldMap #-}
ofoldr :: forall b.
(Element (EnumSet w a) -> b -> b) -> b -> EnumSet w a -> b
ofoldr = forall w a b.
(FiniteBits w, Num w, Enum a) =>
(a -> b -> b) -> b -> EnumSet w a -> b
foldr
{-# INLINE ofoldr #-}
ofoldl' :: forall a.
(a -> Element (EnumSet w a) -> a) -> a -> EnumSet w a -> a
ofoldl' = forall w a b.
(FiniteBits w, Num w, Enum a) =>
(b -> a -> b) -> b -> EnumSet w a -> b
foldl'
{-# INLINE ofoldl' #-}
ofoldr1Ex :: (Element (EnumSet w a)
-> Element (EnumSet w a) -> Element (EnumSet w a))
-> EnumSet w a -> Element (EnumSet w a)
ofoldr1Ex = forall w a.
(FiniteBits w, Num w, Enum a) =>
(a -> a -> a) -> EnumSet w a -> a
foldr1
{-# INLINE ofoldr1Ex #-}
ofoldl1Ex' :: (Element (EnumSet w a)
-> Element (EnumSet w a) -> Element (EnumSet w a))
-> EnumSet w a -> Element (EnumSet w a)
ofoldl1Ex' = forall w a.
(FiniteBits w, Num w, Enum a) =>
(a -> a -> a) -> EnumSet w a -> a
foldl1'
{-# INLINE ofoldl1Ex' #-}
otoList :: EnumSet w a -> [Element (EnumSet w a)]
otoList = forall w a. (FiniteBits w, Num w, Enum a) => EnumSet w a -> [a]
toList
{-# INLINE otoList #-}
oall :: (Element (EnumSet w a) -> Bool) -> EnumSet w a -> Bool
oall = forall w a.
(FiniteBits w, Num w, Enum a) =>
(a -> Bool) -> EnumSet w a -> Bool
all
{-# INLINE oall #-}
oany :: (Element (EnumSet w a) -> Bool) -> EnumSet w a -> Bool
oany = forall w a.
(FiniteBits w, Num w, Enum a) =>
(a -> Bool) -> EnumSet w a -> Bool
any
{-# INLINE oany #-}
onull :: EnumSet w a -> Bool
onull = forall {k} w (a :: k). Bits w => EnumSet w a -> Bool
null
{-# INLINE onull #-}
olength :: EnumSet w a -> Int
olength = forall {k} w (a :: k). (Bits w, Num w) => EnumSet w a -> Int
size
{-# INLINE olength #-}
olength64 :: EnumSet w a -> Int64
olength64 EnumSet w a
w = forall a b. (Integral a, Num b) => a -> b
fromIntegral forall a b. (a -> b) -> a -> b
$ forall {k} w (a :: k). (Bits w, Num w) => EnumSet w a -> Int
size EnumSet w a
w
{-# INLINE olength64 #-}
headEx :: EnumSet w a -> Element (EnumSet w a)
headEx = forall w a. (FiniteBits w, Num w, Enum a) => EnumSet w a -> a
minimum
{-# INLINE headEx #-}
lastEx :: EnumSet w a -> Element (EnumSet w a)
lastEx = forall w a. (FiniteBits w, Num w, Enum a) => EnumSet w a -> a
maximum
{-# INLINE lastEx #-}
oelem :: Eq (Element (EnumSet w a)) =>
Element (EnumSet w a) -> EnumSet w a -> Bool
oelem = forall w a. (Bits w, Enum a) => a -> EnumSet w a -> Bool
member
{-# INLINE oelem #-}
onotElem :: Eq (Element (EnumSet w a)) =>
Element (EnumSet w a) -> EnumSet w a -> Bool
onotElem Element (EnumSet w a)
x = Bool -> Bool
not forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall w a. (Bits w, Enum a) => a -> EnumSet w a -> Bool
member Element (EnumSet w a)
x
{-# INLINE onotElem #-}
instance (FiniteBits w, Num w, Enum a) => GrowingAppend (EnumSet w a)
instance (FiniteBits w, Num w, Enum a) => MonoTraversable (EnumSet w a) where
otraverse :: forall (m :: * -> *).
Applicative m =>
(Element (EnumSet w a) -> m (Element (EnumSet w a)))
-> EnumSet w a -> m (EnumSet w a)
otraverse = forall (f :: * -> *) w a.
(Applicative f, FiniteBits w, Num w, Enum a) =>
(a -> f a) -> EnumSet w a -> f (EnumSet w a)
traverse
{-# INLINE otraverse #-}
instance (FiniteBits w, Num w, Eq a, Enum a) => SetContainer (EnumSet w a) where
type ContainerKey (EnumSet w a) = a
member :: ContainerKey (EnumSet w a) -> EnumSet w a -> Bool
member = forall w a. (Bits w, Enum a) => a -> EnumSet w a -> Bool
member
{-# INLINE member #-}
notMember :: ContainerKey (EnumSet w a) -> EnumSet w a -> Bool
notMember = forall w a. (Bits w, Enum a) => a -> EnumSet w a -> Bool
notMember
{-# INLINE notMember #-}
union :: EnumSet w a -> EnumSet w a -> EnumSet w a
union = forall k w (a :: k).
Bits w =>
EnumSet w a -> EnumSet w a -> EnumSet w a
union
{-# INLINE union #-}
difference :: EnumSet w a -> EnumSet w a -> EnumSet w a
difference = forall k w (a :: k).
Bits w =>
EnumSet w a -> EnumSet w a -> EnumSet w a
difference
{-# INLINE difference #-}
intersection :: EnumSet w a -> EnumSet w a -> EnumSet w a
intersection = forall k w (a :: k).
Bits w =>
EnumSet w a -> EnumSet w a -> EnumSet w a
intersection
{-# INLINE intersection #-}
keys :: EnumSet w a -> [ContainerKey (EnumSet w a)]
keys = forall w a. (FiniteBits w, Num w, Enum a) => EnumSet w a -> [a]
toList
{-# INLINE keys #-}
instance (FiniteBits w, Num w, Eq a, Enum a) => IsSet (EnumSet w a) where
insertSet :: Element (EnumSet w a) -> EnumSet w a -> EnumSet w a
insertSet = forall w a. (Bits w, Enum a) => a -> EnumSet w a -> EnumSet w a
insert
{-# INLINE insertSet #-}
deleteSet :: Element (EnumSet w a) -> EnumSet w a -> EnumSet w a
deleteSet = forall w a. (Bits w, Enum a) => a -> EnumSet w a -> EnumSet w a
delete
{-# INLINE deleteSet #-}
singletonSet :: Element (EnumSet w a) -> EnumSet w a
singletonSet = forall w a. (Bits w, Enum a) => a -> EnumSet w a
singleton
{-# INLINE singletonSet #-}
setFromList :: [Element (EnumSet w a)] -> EnumSet w a
setFromList = forall (f :: * -> *) w a.
(Foldable f, Bits w, Enum a) =>
f a -> EnumSet w a
fromFoldable
{-# INLINE setFromList #-}
setToList :: EnumSet w a -> [Element (EnumSet w a)]
setToList = forall w a. (FiniteBits w, Num w, Enum a) => EnumSet w a -> [a]
toList
{-# INLINE setToList #-}
filterSet :: (Element (EnumSet w a) -> Bool) -> EnumSet w a -> EnumSet w a
filterSet = forall w a.
(FiniteBits w, Num w, Enum a) =>
(a -> Bool) -> EnumSet w a -> EnumSet w a
filter
{-# INLINE filterSet #-}
instance (FiniteBits w, Num w, Enum x, Show x) => Show (EnumSet w x) where
showsPrec :: Int -> EnumSet w x -> ShowS
showsPrec Int
p EnumSet w x
xs = Bool -> ShowS -> ShowS
showParen (Int
p forall a. Ord a => a -> a -> Bool
> Int
10) forall a b. (a -> b) -> a -> b
$
String -> ShowS
showString String
"fromList " forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Show a => a -> ShowS
shows (forall w a. (FiniteBits w, Num w, Enum a) => EnumSet w a -> [a]
toList EnumSet w x
xs)
{-# INLINABLE showsPrec #-}
instance (Bits w, Num w, Enum x, Read x) => Read (EnumSet w x) where
readPrec :: ReadPrec (EnumSet w x)
readPrec = forall a. ReadPrec a -> ReadPrec a
parens forall a b. (a -> b) -> a -> b
$ forall a. Int -> ReadPrec a -> ReadPrec a
prec Int
10 do
Ident String
"fromList" <- ReadPrec Lexeme
lexP
forall (f :: * -> *) w a.
(Foldable f, Bits w, Enum a) =>
f a -> EnumSet w a
fromFoldable forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (forall a. Read a => ReadPrec a
readPrec :: ReadPrec [x])
{-# INLINABLE readPrec #-}
readListPrec :: ReadPrec [EnumSet w x]
readListPrec = forall a. Read a => ReadPrec [a]
readListPrecDefault
{-# INLINABLE readListPrec #-}
empty :: ∀ w a. Bits w
=> EnumSet w a
empty :: forall k w (a :: k). Bits w => EnumSet w a
empty = forall {k} word (a :: k). word -> EnumSet word a
EnumSet forall a. Bits a => a
zeroBits
{-# INLINE empty #-}
singleton :: ∀ w a. (Bits w, Enum a)
=> a -> EnumSet w a
singleton :: forall w a. (Bits w, Enum a) => a -> EnumSet w a
singleton = forall {k} word (a :: k). word -> EnumSet word a
EnumSet forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Bits a => Int -> a
bit forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Enum a => a -> Int
fromEnum
{-# INLINE singleton #-}
fromFoldable :: ∀ f w a. (Foldable f, Bits w, Enum a)
=> f a -> EnumSet w a
fromFoldable :: forall (f :: * -> *) w a.
(Foldable f, Bits w, Enum a) =>
f a -> EnumSet w a
fromFoldable = forall {k} word (a :: k). word -> EnumSet word a
EnumSet forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (t :: * -> *) b a.
Foldable t =>
(b -> a -> b) -> b -> t a -> b
F.foldl' (forall a b c. (a -> b -> c) -> b -> a -> c
flip forall a b. (a -> b) -> a -> b
$ forall a. Bits a => a -> a -> a
(.|.) forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Bits a => Int -> a
bit forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Enum a => a -> Int
fromEnum) forall a. Bits a => a
zeroBits
insert :: ∀ w a. (Bits w, Enum a)
=> a -> EnumSet w a -> EnumSet w a
insert :: forall w a. (Bits w, Enum a) => a -> EnumSet w a -> EnumSet w a
insert !a
x (EnumSet w
w) = forall {k} word (a :: k). word -> EnumSet word a
EnumSet forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Bits a => a -> Int -> a
setBit w
w forall a b. (a -> b) -> a -> b
$ forall a. Enum a => a -> Int
fromEnum a
x
delete :: ∀ w a. (Bits w, Enum a)
=> a -> EnumSet w a -> EnumSet w a
delete :: forall w a. (Bits w, Enum a) => a -> EnumSet w a -> EnumSet w a
delete !a
x (EnumSet w
w) = forall {k} word (a :: k). word -> EnumSet word a
EnumSet forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Bits a => a -> Int -> a
clearBit w
w forall a b. (a -> b) -> a -> b
$ forall a. Enum a => a -> Int
fromEnum a
x
member :: ∀ w a. (Bits w, Enum a)
=> a -> EnumSet w a -> Bool
member :: forall w a. (Bits w, Enum a) => a -> EnumSet w a -> Bool
member !a
x (EnumSet w
w) = forall a. Bits a => a -> Int -> Bool
testBit w
w forall a b. (a -> b) -> a -> b
$ forall a. Enum a => a -> Int
fromEnum a
x
notMember :: ∀ w a. (Bits w, Enum a)
=> a -> EnumSet w a -> Bool
notMember :: forall w a. (Bits w, Enum a) => a -> EnumSet w a -> Bool
notMember !a
x = Bool -> Bool
not forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall w a. (Bits w, Enum a) => a -> EnumSet w a -> Bool
member a
x
null :: ∀ w a. Bits w
=> EnumSet w a -> Bool
null :: forall {k} w (a :: k). Bits w => EnumSet w a -> Bool
null (EnumSet w
w) = forall a. Bits a => a
zeroBits forall a. Eq a => a -> a -> Bool
== w
w
{-# INLINE null #-}
size :: ∀ w a. (Bits w, Num w)
=> EnumSet w a -> Int
size :: forall {k} w (a :: k). (Bits w, Num w) => EnumSet w a -> Int
size (EnumSet !w
w) = forall a. Bits a => a -> Int
popCount w
w
isSubsetOf :: ∀ w a. (Bits w)
=> EnumSet w a -> EnumSet w a -> Bool
isSubsetOf :: forall {k} w (a :: k). Bits w => EnumSet w a -> EnumSet w a -> Bool
isSubsetOf (EnumSet w
x) (EnumSet w
y) = w
x forall a. Bits a => a -> a -> a
.|. w
y forall a. Eq a => a -> a -> Bool
== w
y
{-# INLINE isSubsetOf #-}
union :: ∀ w a. Bits w
=> EnumSet w a -> EnumSet w a -> EnumSet w a
union :: forall k w (a :: k).
Bits w =>
EnumSet w a -> EnumSet w a -> EnumSet w a
union (EnumSet w
x) (EnumSet w
y) = forall {k} word (a :: k). word -> EnumSet word a
EnumSet forall a b. (a -> b) -> a -> b
$ w
x forall a. Bits a => a -> a -> a
.|. w
y
{-# INLINE union #-}
difference :: ∀ w a. Bits w
=> EnumSet w a -> EnumSet w a -> EnumSet w a
difference :: forall k w (a :: k).
Bits w =>
EnumSet w a -> EnumSet w a -> EnumSet w a
difference (EnumSet w
x) (EnumSet w
y) = forall {k} word (a :: k). word -> EnumSet word a
EnumSet forall a b. (a -> b) -> a -> b
$ (w
x forall a. Bits a => a -> a -> a
.|. w
y) forall a. Bits a => a -> a -> a
`xor` w
y
{-# INLINE difference #-}
(\\) :: ∀ w a. Bits w
=> EnumSet w a -> EnumSet w a -> EnumSet w a
\\ :: forall k w (a :: k).
Bits w =>
EnumSet w a -> EnumSet w a -> EnumSet w a
(\\) = forall k w (a :: k).
Bits w =>
EnumSet w a -> EnumSet w a -> EnumSet w a
difference
infixl 9 \\
{-# INLINE (\\) #-}
symmetricDifference :: ∀ w a. Bits w
=> EnumSet w a -> EnumSet w a -> EnumSet w a
symmetricDifference :: forall k w (a :: k).
Bits w =>
EnumSet w a -> EnumSet w a -> EnumSet w a
symmetricDifference (EnumSet w
x) (EnumSet w
y) = forall {k} word (a :: k). word -> EnumSet word a
EnumSet forall a b. (a -> b) -> a -> b
$ w
x forall a. Bits a => a -> a -> a
`xor` w
y
{-# INLINE symmetricDifference #-}
intersection :: ∀ w a. Bits w
=> EnumSet w a -> EnumSet w a -> EnumSet w a
intersection :: forall k w (a :: k).
Bits w =>
EnumSet w a -> EnumSet w a -> EnumSet w a
intersection (EnumSet w
x) (EnumSet w
y) = forall {k} word (a :: k). word -> EnumSet word a
EnumSet forall a b. (a -> b) -> a -> b
$ w
x forall a. Bits a => a -> a -> a
.&. w
y
{-# INLINE intersection #-}
filter :: ∀ w a. (FiniteBits w, Num w, Enum a)
=> (a -> Bool) -> EnumSet w a -> EnumSet w a
filter :: forall w a.
(FiniteBits w, Num w, Enum a) =>
(a -> Bool) -> EnumSet w a -> EnumSet w a
filter a -> Bool
p (EnumSet w
w) = forall {k} word (a :: k). word -> EnumSet word a
EnumSet forall a b. (a -> b) -> a -> b
$ forall w a. (FiniteBits w, Num w) => (a -> Int -> a) -> a -> w -> a
foldlBits' w -> Int -> w
f w
0 w
w
where
f :: w -> Int -> w
f w
z Int
i
| a -> Bool
p forall a b. (a -> b) -> a -> b
$ forall a. Enum a => Int -> a
toEnum Int
i = forall a. Bits a => a -> Int -> a
setBit w
z Int
i
| Bool
otherwise = w
z
{-# INLINE f #-}
partition :: ∀ w a. (FiniteBits w, Num w, Enum a)
=> (a -> Bool) -> EnumSet w a -> (EnumSet w a, EnumSet w a)
partition :: forall w a.
(FiniteBits w, Num w, Enum a) =>
(a -> Bool) -> EnumSet w a -> (EnumSet w a, EnumSet w a)
partition a -> Bool
p (EnumSet w
w) = (forall {k} word (a :: k). word -> EnumSet word a
EnumSet w
yay, forall {k} word (a :: k). word -> EnumSet word a
EnumSet w
nay)
where
(w
yay, w
nay) = forall w a. (FiniteBits w, Num w) => (a -> Int -> a) -> a -> w -> a
foldlBits' (w, w) -> Int -> (w, w)
f (w
0, w
0) w
w
f :: (w, w) -> Int -> (w, w)
f (w
x, w
y) Int
i
| a -> Bool
p forall a b. (a -> b) -> a -> b
$ forall a. Enum a => Int -> a
toEnum Int
i = (forall a. Bits a => a -> Int -> a
setBit w
x Int
i, w
y)
| Bool
otherwise = (w
x, forall a. Bits a => a -> Int -> a
setBit w
y Int
i)
{-# INLINE f #-}
map :: ∀ w a b. (FiniteBits w, Num w, Enum a, Enum b)
=> (a -> b) -> EnumSet w a -> EnumSet w b
map :: forall w a b.
(FiniteBits w, Num w, Enum a, Enum b) =>
(a -> b) -> EnumSet w a -> EnumSet w b
map = forall v w a b.
(FiniteBits v, FiniteBits w, Num v, Num w, Enum a, Enum b) =>
(a -> b) -> EnumSet v a -> EnumSet w b
map'
{-# INLINE map #-}
map' :: ∀ v w a b. (FiniteBits v, FiniteBits w, Num v, Num w, Enum a, Enum b)
=> (a -> b) -> EnumSet v a -> EnumSet w b
map' :: forall v w a b.
(FiniteBits v, FiniteBits w, Num v, Num w, Enum a, Enum b) =>
(a -> b) -> EnumSet v a -> EnumSet w b
map' a -> b
f0 (EnumSet v
w) = forall {k} word (a :: k). word -> EnumSet word a
EnumSet forall a b. (a -> b) -> a -> b
$ forall w a. (FiniteBits w, Num w) => (a -> Int -> a) -> a -> w -> a
foldlBits' w -> Int -> w
f w
0 v
w
where
f :: w -> Int -> w
f w
z Int
i = forall a. Bits a => a -> Int -> a
setBit w
z forall a b. (a -> b) -> a -> b
$ forall a. Enum a => a -> Int
fromEnum forall a b. (a -> b) -> a -> b
$ a -> b
f0 (forall a. Enum a => Int -> a
toEnum Int
i)
{-# INLINE f #-}
foldl :: ∀ w a b. (FiniteBits w, Num w, Enum a)
=> (b -> a -> b) -> b -> EnumSet w a -> b
foldl :: forall w a b.
(FiniteBits w, Num w, Enum a) =>
(b -> a -> b) -> b -> EnumSet w a -> b
foldl b -> a -> b
f b
z (EnumSet w
w) = forall w a. (FiniteBits w, Num w) => (a -> Int -> a) -> a -> w -> a
foldlBits ((forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Enum a => Int -> a
toEnum) forall b c a. (b -> c) -> (a -> b) -> a -> c
. b -> a -> b
f) b
z w
w
{-# INLINE foldl #-}
foldl' :: ∀ w a b. (FiniteBits w, Num w, Enum a)
=> (b -> a -> b) -> b -> EnumSet w a -> b
foldl' :: forall w a b.
(FiniteBits w, Num w, Enum a) =>
(b -> a -> b) -> b -> EnumSet w a -> b
foldl' b -> a -> b
f b
z (EnumSet w
w) = forall w a. (FiniteBits w, Num w) => (a -> Int -> a) -> a -> w -> a
foldlBits' ((forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Enum a => Int -> a
toEnum) forall b c a. (b -> c) -> (a -> b) -> a -> c
. b -> a -> b
f) b
z w
w
{-# INLINE foldl' #-}
foldr :: ∀ w a b. (FiniteBits w, Num w, Enum a)
=> (a -> b -> b) -> b -> EnumSet w a -> b
foldr :: forall w a b.
(FiniteBits w, Num w, Enum a) =>
(a -> b -> b) -> b -> EnumSet w a -> b
foldr a -> b -> b
f b
z (EnumSet w
w) = forall w a. (FiniteBits w, Num w) => (Int -> a -> a) -> a -> w -> a
foldrBits (a -> b -> b
f forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Enum a => Int -> a
toEnum) b
z w
w
{-# INLINE foldr #-}
foldr' :: ∀ w a b. (FiniteBits w, Num w, Enum a)
=> (a -> b -> b) -> b -> EnumSet w a -> b
foldr' :: forall w a b.
(FiniteBits w, Num w, Enum a) =>
(a -> b -> b) -> b -> EnumSet w a -> b
foldr' a -> b -> b
f b
z (EnumSet w
w) = forall w a. (FiniteBits w, Num w) => (Int -> a -> a) -> a -> w -> a
foldrBits' (a -> b -> b
f forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Enum a => Int -> a
toEnum) b
z w
w
{-# INLINE foldr' #-}
foldl1 :: ∀ w a. (FiniteBits w, Num w, Enum a)
=> (a -> a -> a) -> EnumSet w a -> a
foldl1 :: forall w a.
(FiniteBits w, Num w, Enum a) =>
(a -> a -> a) -> EnumSet w a -> a
foldl1 a -> a -> a
f = forall w a.
(Bits w, Num w, Enum a) =>
(w -> Int) -> (a -> w -> a) -> EnumSet w a -> a
fold1Aux forall w. (FiniteBits w, Num w) => w -> Int
lsb forall a b. (a -> b) -> a -> b
$ forall w a. (FiniteBits w, Num w) => (a -> Int -> a) -> a -> w -> a
foldlBits ((forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Enum a => Int -> a
toEnum) forall b c a. (b -> c) -> (a -> b) -> a -> c
. a -> a -> a
f)
{-# INLINE foldl1 #-}
foldl1' :: ∀ w a. (FiniteBits w, Num w, Enum a)
=> (a -> a -> a) -> EnumSet w a -> a
foldl1' :: forall w a.
(FiniteBits w, Num w, Enum a) =>
(a -> a -> a) -> EnumSet w a -> a
foldl1' a -> a -> a
f = forall w a.
(Bits w, Num w, Enum a) =>
(w -> Int) -> (a -> w -> a) -> EnumSet w a -> a
fold1Aux forall w. (FiniteBits w, Num w) => w -> Int
lsb forall a b. (a -> b) -> a -> b
$ forall w a. (FiniteBits w, Num w) => (a -> Int -> a) -> a -> w -> a
foldlBits' ((forall b c a. (b -> c) -> (a -> b) -> a -> c
.forall a. Enum a => Int -> a
toEnum) forall b c a. (b -> c) -> (a -> b) -> a -> c
. a -> a -> a
f)
{-# INLINE foldl1' #-}
foldr1 :: ∀ w a. (FiniteBits w, Num w, Enum a)
=> (a -> a -> a) -> EnumSet w a -> a
foldr1 :: forall w a.
(FiniteBits w, Num w, Enum a) =>
(a -> a -> a) -> EnumSet w a -> a
foldr1 a -> a -> a
f = forall w a.
(Bits w, Num w, Enum a) =>
(w -> Int) -> (a -> w -> a) -> EnumSet w a -> a
fold1Aux forall w. (FiniteBits w, Num w) => w -> Int
msb forall a b. (a -> b) -> a -> b
$ forall w a. (FiniteBits w, Num w) => (Int -> a -> a) -> a -> w -> a
foldrBits (a -> a -> a
f forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Enum a => Int -> a
toEnum)
{-# INLINE foldr1 #-}
foldr1' :: ∀ w a. (FiniteBits w, Num w, Enum a)
=> (a -> a -> a) -> EnumSet w a -> a
foldr1' :: forall w a.
(FiniteBits w, Num w, Enum a) =>
(a -> a -> a) -> EnumSet w a -> a
foldr1' a -> a -> a
f = forall w a.
(Bits w, Num w, Enum a) =>
(w -> Int) -> (a -> w -> a) -> EnumSet w a -> a
fold1Aux forall w. (FiniteBits w, Num w) => w -> Int
msb forall a b. (a -> b) -> a -> b
$ forall w a. (FiniteBits w, Num w) => (Int -> a -> a) -> a -> w -> a
foldrBits' (a -> a -> a
f forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Enum a => Int -> a
toEnum)
{-# INLINE foldr1' #-}
foldMap :: ∀ m w a. (Monoid m, FiniteBits w, Num w, Enum a)
=> (a -> m) -> EnumSet w a -> m
foldMap :: forall m w a.
(Monoid m, FiniteBits w, Num w, Enum a) =>
(a -> m) -> EnumSet w a -> m
foldMap a -> m
f (EnumSet w
w) = forall w a. (FiniteBits w, Num w) => (Int -> a -> a) -> a -> w -> a
foldrBits (forall a. Monoid a => a -> a -> a
mappend forall b c a. (b -> c) -> (a -> b) -> a -> c
. a -> m
f forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Enum a => Int -> a
toEnum) forall a. Monoid a => a
mempty w
w
{-# INLINE foldMap #-}
traverse :: ∀ f w a. (Applicative f, FiniteBits w, Num w, Enum a)
=> (a -> f a) -> EnumSet w a -> f (EnumSet w a)
traverse :: forall (f :: * -> *) w a.
(Applicative f, FiniteBits w, Num w, Enum a) =>
(a -> f a) -> EnumSet w a -> f (EnumSet w a)
traverse a -> f a
f (EnumSet w
w) = forall {k} word (a :: k). word -> EnumSet word a
EnumSet forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$>
forall w a. (FiniteBits w, Num w) => (Int -> a -> a) -> a -> w -> a
foldrBits
(forall (f :: * -> *) a b c.
Applicative f =>
(a -> b -> c) -> f a -> f b -> f c
liftA2 (forall a b c. (a -> b -> c) -> b -> a -> c
flip forall a. Bits a => a -> Int -> a
setBit) forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap forall a. Enum a => a -> Int
fromEnum forall b c a. (b -> c) -> (a -> b) -> a -> c
. a -> f a
f forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Enum a => Int -> a
toEnum)
(forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a. Bits a => a
zeroBits)
w
w
{-# INLINE traverse #-}
all :: ∀ w a. (FiniteBits w, Num w, Enum a)
=> (a -> Bool) -> EnumSet w a -> Bool
all :: forall w a.
(FiniteBits w, Num w, Enum a) =>
(a -> Bool) -> EnumSet w a -> Bool
all a -> Bool
p (EnumSet w
w) = let lb :: Int
lb = forall w. (FiniteBits w, Num w) => w -> Int
lsb w
w in Int -> w -> Bool
go Int
lb (w
w forall a. Bits a => a -> Int -> a
`unsafeShiftR` Int
lb)
where
go :: Int -> w -> Bool
go !Int
_ w
0 = Bool
True
go Int
bi w
n
| w
n forall a. Bits a => a -> Int -> Bool
`testBit` Int
0 Bool -> Bool -> Bool
&& Bool -> Bool
not (a -> Bool
p forall a b. (a -> b) -> a -> b
$ forall a. Enum a => Int -> a
toEnum Int
bi) = Bool
False
| Bool
otherwise = Int -> w -> Bool
go (Int
bi forall a. Num a => a -> a -> a
+ Int
1) (w
n forall a. Bits a => a -> Int -> a
`unsafeShiftR` Int
1)
any :: ∀ w a. (FiniteBits w, Num w, Enum a)
=> (a -> Bool) -> EnumSet w a -> Bool
any :: forall w a.
(FiniteBits w, Num w, Enum a) =>
(a -> Bool) -> EnumSet w a -> Bool
any a -> Bool
p (EnumSet w
w) = let lb :: Int
lb = forall w. (FiniteBits w, Num w) => w -> Int
lsb w
w in Int -> w -> Bool
go Int
lb (w
w forall a. Bits a => a -> Int -> a
`unsafeShiftR` Int
lb)
where
go :: Int -> w -> Bool
go !Int
_ w
0 = Bool
False
go Int
bi w
n
| w
n forall a. Bits a => a -> Int -> Bool
`testBit` Int
0 Bool -> Bool -> Bool
&& a -> Bool
p (forall a. Enum a => Int -> a
toEnum Int
bi) = Bool
True
| Bool
otherwise = Int -> w -> Bool
go (Int
bi forall a. Num a => a -> a -> a
+ Int
1) (w
n forall a. Bits a => a -> Int -> a
`unsafeShiftR` Int
1)
minimum :: ∀ w a. (FiniteBits w, Num w, Enum a)
=> EnumSet w a -> a
minimum :: forall w a. (FiniteBits w, Num w, Enum a) => EnumSet w a -> a
minimum (EnumSet w
0) = forall a. a
errorEmpty
minimum (EnumSet w
w) = forall a. Enum a => Int -> a
toEnum forall a b. (a -> b) -> a -> b
$ forall w. (FiniteBits w, Num w) => w -> Int
lsb w
w
maximum :: ∀ w a. (FiniteBits w, Num w, Enum a)
=> EnumSet w a -> a
maximum :: forall w a. (FiniteBits w, Num w, Enum a) => EnumSet w a -> a
maximum (EnumSet w
0) = forall a. a
errorEmpty
maximum (EnumSet w
w) = forall a. Enum a => Int -> a
toEnum forall a b. (a -> b) -> a -> b
$ forall w. (FiniteBits w, Num w) => w -> Int
msb w
w
deleteMin :: ∀ w a. (FiniteBits w, Num w)
=> EnumSet w a -> EnumSet w a
deleteMin :: forall {k} w (a :: k).
(FiniteBits w, Num w) =>
EnumSet w a -> EnumSet w a
deleteMin (EnumSet w
0) = forall {k} word (a :: k). word -> EnumSet word a
EnumSet w
0
deleteMin (EnumSet w
w) = forall {k} word (a :: k). word -> EnumSet word a
EnumSet forall a b. (a -> b) -> a -> b
$ forall a. Bits a => a -> Int -> a
clearBit w
w forall a b. (a -> b) -> a -> b
$ forall w. (FiniteBits w, Num w) => w -> Int
lsb w
w
deleteMax :: ∀ w a. (FiniteBits w, Num w)
=> EnumSet w a -> EnumSet w a
deleteMax :: forall {k} w (a :: k).
(FiniteBits w, Num w) =>
EnumSet w a -> EnumSet w a
deleteMax (EnumSet w
0) = forall {k} word (a :: k). word -> EnumSet word a
EnumSet w
0
deleteMax (EnumSet w
w) = forall {k} word (a :: k). word -> EnumSet word a
EnumSet forall a b. (a -> b) -> a -> b
$ forall a. Bits a => a -> Int -> a
clearBit w
w forall a b. (a -> b) -> a -> b
$ forall w. (FiniteBits w, Num w) => w -> Int
msb w
w
minView :: ∀ w a. (FiniteBits w, Num w, Enum a)
=> EnumSet w a -> Maybe (a, EnumSet w a)
minView :: forall w a.
(FiniteBits w, Num w, Enum a) =>
EnumSet w a -> Maybe (a, EnumSet w a)
minView (EnumSet w
0) = forall a. Maybe a
Nothing
minView (EnumSet w
w) = let i :: Int
i = forall w. (FiniteBits w, Num w) => w -> Int
lsb w
w in forall a. a -> Maybe a
Just (forall a. Enum a => Int -> a
toEnum Int
i, forall {k} word (a :: k). word -> EnumSet word a
EnumSet forall a b. (a -> b) -> a -> b
$ forall a. Bits a => a -> Int -> a
clearBit w
w Int
i)
maxView :: ∀ w a. (FiniteBits w, Num w, Enum a)
=> EnumSet w a -> Maybe (a, EnumSet w a)
maxView :: forall w a.
(FiniteBits w, Num w, Enum a) =>
EnumSet w a -> Maybe (a, EnumSet w a)
maxView (EnumSet w
0) = forall a. Maybe a
Nothing
maxView (EnumSet w
w) = let i :: Int
i = forall w. (FiniteBits w, Num w) => w -> Int
msb w
w in forall a. a -> Maybe a
Just (forall a. Enum a => Int -> a
toEnum Int
i, forall {k} word (a :: k). word -> EnumSet word a
EnumSet forall a b. (a -> b) -> a -> b
$ forall a. Bits a => a -> Int -> a
clearBit w
w Int
i)
toList :: ∀ w a. (FiniteBits w, Num w, Enum a)
=> EnumSet w a -> [a]
toList :: forall w a. (FiniteBits w, Num w, Enum a) => EnumSet w a -> [a]
toList (EnumSet w
w) = forall a. (forall b. (a -> b -> b) -> b -> b) -> [a]
build \a -> b -> b
c b
n -> forall w a. (FiniteBits w, Num w) => (Int -> a -> a) -> a -> w -> a
foldrBits (a -> b -> b
c forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Enum a => Int -> a
toEnum) b
n w
w
{-# INLINE toList #-}
fromRaw :: ∀ w a. w -> EnumSet w a
fromRaw :: forall {k} word (a :: k). word -> EnumSet word a
fromRaw = forall {k} word (a :: k). word -> EnumSet word a
EnumSet
{-# INLINE fromRaw #-}
toRaw :: ∀ w a. EnumSet w a -> w
toRaw :: forall {k} w (a :: k). EnumSet w a -> w
toRaw (EnumSet w
x) = w
x
{-# INLINE toRaw #-}
lsb :: ∀ w. (FiniteBits w, Num w) => w -> Int
lsb :: forall w. (FiniteBits w, Num w) => w -> Int
lsb = forall b. FiniteBits b => b -> Int
countTrailingZeros
{-# INLINE lsb #-}
msb :: ∀ w. (FiniteBits w, Num w) => w -> Int
msb :: forall w. (FiniteBits w, Num w) => w -> Int
msb w
w = forall b. FiniteBits b => b -> Int
finiteBitSize w
w forall a. Num a => a -> a -> a
- Int
1 forall a. Num a => a -> a -> a
- forall b. FiniteBits b => b -> Int
countLeadingZeros w
w
{-# INLINE msb #-}
foldlBits :: ∀ w a. (FiniteBits w, Num w) => (a -> Int -> a) -> a -> w -> a
foldlBits :: forall w a. (FiniteBits w, Num w) => (a -> Int -> a) -> a -> w -> a
foldlBits a -> Int -> a
f a
z w
w = let lb :: Int
lb = forall w. (FiniteBits w, Num w) => w -> Int
lsb w
w in Int -> a -> w -> a
go Int
lb a
z (w
w forall a. Bits a => a -> Int -> a
`unsafeShiftR` Int
lb)
where
go :: Int -> a -> w -> a
go !Int
_ a
acc w
0 = a
acc
go Int
bi a
acc w
n
| w
n forall a. Bits a => a -> Int -> Bool
`testBit` Int
0 = Int -> a -> w -> a
go (Int
bi forall a. Num a => a -> a -> a
+ Int
1) (a -> Int -> a
f a
acc Int
bi) (w
n forall a. Bits a => a -> Int -> a
`unsafeShiftR` Int
1)
| Bool
otherwise = Int -> a -> w -> a
go (Int
bi forall a. Num a => a -> a -> a
+ Int
1) a
acc (w
n forall a. Bits a => a -> Int -> a
`unsafeShiftR` Int
1)
{-# INLINE foldlBits #-}
foldlBits' :: ∀ w a. (FiniteBits w, Num w) => (a -> Int -> a) -> a -> w -> a
foldlBits' :: forall w a. (FiniteBits w, Num w) => (a -> Int -> a) -> a -> w -> a
foldlBits' a -> Int -> a
f a
z w
w = let lb :: Int
lb = forall w. (FiniteBits w, Num w) => w -> Int
lsb w
w in Int -> a -> w -> a
go Int
lb a
z (w
w forall a. Bits a => a -> Int -> a
`unsafeShiftR` Int
lb)
where
go :: Int -> a -> w -> a
go !Int
_ !a
acc w
0 = a
acc
go Int
bi a
acc w
n
| w
n forall a. Bits a => a -> Int -> Bool
`testBit` Int
0 = Int -> a -> w -> a
go (Int
bi forall a. Num a => a -> a -> a
+ Int
1) (a -> Int -> a
f a
acc Int
bi) (w
n forall a. Bits a => a -> Int -> a
`unsafeShiftR` Int
1)
| Bool
otherwise = Int -> a -> w -> a
go (Int
bi forall a. Num a => a -> a -> a
+ Int
1) a
acc (w
n forall a. Bits a => a -> Int -> a
`unsafeShiftR` Int
1)
{-# INLINE foldlBits' #-}
foldrBits :: ∀ w a. (FiniteBits w, Num w) => (Int -> a -> a) -> a -> w -> a
foldrBits :: forall w a. (FiniteBits w, Num w) => (Int -> a -> a) -> a -> w -> a
foldrBits Int -> a -> a
f a
z w
w = let lb :: Int
lb = forall w. (FiniteBits w, Num w) => w -> Int
lsb w
w in Int -> w -> a
go Int
lb (w
w forall a. Bits a => a -> Int -> a
`unsafeShiftR` Int
lb)
where
go :: Int -> w -> a
go !Int
_ w
0 = a
z
go Int
bi w
n
| w
n forall a. Bits a => a -> Int -> Bool
`testBit` Int
0 = Int -> a -> a
f Int
bi (Int -> w -> a
go (Int
bi forall a. Num a => a -> a -> a
+ Int
1) (w
n forall a. Bits a => a -> Int -> a
`unsafeShiftR` Int
1))
| Bool
otherwise = Int -> w -> a
go (Int
bi forall a. Num a => a -> a -> a
+ Int
1) (w
n forall a. Bits a => a -> Int -> a
`unsafeShiftR` Int
1)
{-# INLINE foldrBits #-}
foldrBits' :: ∀ w a. (FiniteBits w, Num w) => (Int -> a -> a) -> a -> w -> a
foldrBits' :: forall w a. (FiniteBits w, Num w) => (Int -> a -> a) -> a -> w -> a
foldrBits' Int -> a -> a
f a
z w
w = let lb :: Int
lb = forall w. (FiniteBits w, Num w) => w -> Int
lsb w
w in Int -> w -> a
go Int
lb (w
w forall a. Bits a => a -> Int -> a
`unsafeShiftR` Int
lb)
where
go :: Int -> w -> a
go !Int
_ w
0 = a
z
go Int
bi w
n
| w
n forall a. Bits a => a -> Int -> Bool
`testBit` Int
0 = Int -> a -> a
f Int
bi forall a b. (a -> b) -> a -> b
$! Int -> w -> a
go (Int
bi forall a. Num a => a -> a -> a
+ Int
1) (w
n forall a. Bits a => a -> Int -> a
`unsafeShiftR` Int
1)
| Bool
otherwise = Int -> w -> a
go (Int
bi forall a. Num a => a -> a -> a
+ Int
1) (w
n forall a. Bits a => a -> Int -> a
`unsafeShiftR` Int
1)
{-# INLINE foldrBits' #-}
fold1Aux :: ∀ w a. (Bits w, Num w, Enum a)
=> (w -> Int) -> (a -> w -> a) -> EnumSet w a -> a
fold1Aux :: forall w a.
(Bits w, Num w, Enum a) =>
(w -> Int) -> (a -> w -> a) -> EnumSet w a -> a
fold1Aux w -> Int
_ a -> w -> a
_ (EnumSet w
0) = forall a. a
errorEmpty
fold1Aux w -> Int
getBit a -> w -> a
f (EnumSet w
w) = a -> w -> a
f (forall a. Enum a => Int -> a
toEnum Int
gotBit) (forall a. Bits a => a -> Int -> a
clearBit w
w Int
gotBit)
where
gotBit :: Int
gotBit = w -> Int
getBit w
w
{-# INLINE fold1Aux #-}
errorEmpty :: a
errorEmpty :: forall a. a
errorEmpty = forall a. HasCallStack => String -> a
error String
"Data.Enum.Set: empty EnumSet"