{-# LANGUAGE BangPatterns #-}
{-# LANGUAGE CPP #-}
{-# LANGUAGE DeriveDataTypeable #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TypeApplications #-}
{-# LANGUAGE TypeFamilies #-}
module Math.NumberTheory.Primes.IntSet
(
PrimeIntSet
, unPrimeIntSet
, singleton
, fromList
, fromAscList
, fromDistinctAscList
, insert
, delete
, member
, notMember
, lookupEQ
, lookupLT
, lookupGT
, lookupLE
, lookupGE
, null
, size
, isSubsetOf
, isProperSubsetOf
, disjoint
, difference
, (\\)
, symmetricDifference
, intersection
, filter
, partition
, split
, splitMember
, splitLookupEQ
, splitRoot
, foldr
, foldl
, foldr'
, foldl'
, deleteMin
, deleteMax
, minView
, maxView
, toAscList
, toDescList
) where
import Prelude (Eq, Ord, Show, Monoid, Bool, Maybe(..), Int, otherwise)
import Control.DeepSeq (NFData)
import Data.Coerce (coerce)
import Data.Data (Data)
import Data.IntSet (IntSet)
import qualified Data.IntSet.Internal as IS
import Data.Semigroup (Semigroup)
import qualified GHC.Exts (IsList(..))
import Math.NumberTheory.Primes.Types (Prime(..))
#if !MIN_VERSION_containers(0,8,0)
import Prelude ((>), (/=), (==), (-), Word)
import Data.Function (on)
import Math.NumberTheory.Utils.FromIntegral (wordToInt, intToWord)
import Data.Bits (Bits(..))
import Utils.Containers.Internal.BitUtil (highestBitMask)
#endif
newtype PrimeIntSet = PrimeIntSet {
PrimeIntSet -> IntSet
unPrimeIntSet :: IntSet
}
deriving (PrimeIntSet -> PrimeIntSet -> Bool
(PrimeIntSet -> PrimeIntSet -> Bool)
-> (PrimeIntSet -> PrimeIntSet -> Bool) -> Eq PrimeIntSet
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: PrimeIntSet -> PrimeIntSet -> Bool
== :: PrimeIntSet -> PrimeIntSet -> Bool
$c/= :: PrimeIntSet -> PrimeIntSet -> Bool
/= :: PrimeIntSet -> PrimeIntSet -> Bool
Eq, Eq PrimeIntSet
Eq PrimeIntSet =>
(PrimeIntSet -> PrimeIntSet -> Ordering)
-> (PrimeIntSet -> PrimeIntSet -> Bool)
-> (PrimeIntSet -> PrimeIntSet -> Bool)
-> (PrimeIntSet -> PrimeIntSet -> Bool)
-> (PrimeIntSet -> PrimeIntSet -> Bool)
-> (PrimeIntSet -> PrimeIntSet -> PrimeIntSet)
-> (PrimeIntSet -> PrimeIntSet -> PrimeIntSet)
-> Ord PrimeIntSet
PrimeIntSet -> PrimeIntSet -> Bool
PrimeIntSet -> PrimeIntSet -> Ordering
PrimeIntSet -> PrimeIntSet -> PrimeIntSet
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
$ccompare :: PrimeIntSet -> PrimeIntSet -> Ordering
compare :: PrimeIntSet -> PrimeIntSet -> Ordering
$c< :: PrimeIntSet -> PrimeIntSet -> Bool
< :: PrimeIntSet -> PrimeIntSet -> Bool
$c<= :: PrimeIntSet -> PrimeIntSet -> Bool
<= :: PrimeIntSet -> PrimeIntSet -> Bool
$c> :: PrimeIntSet -> PrimeIntSet -> Bool
> :: PrimeIntSet -> PrimeIntSet -> Bool
$c>= :: PrimeIntSet -> PrimeIntSet -> Bool
>= :: PrimeIntSet -> PrimeIntSet -> Bool
$cmax :: PrimeIntSet -> PrimeIntSet -> PrimeIntSet
max :: PrimeIntSet -> PrimeIntSet -> PrimeIntSet
$cmin :: PrimeIntSet -> PrimeIntSet -> PrimeIntSet
min :: PrimeIntSet -> PrimeIntSet -> PrimeIntSet
Ord, Typeable PrimeIntSet
Typeable PrimeIntSet =>
(forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> PrimeIntSet -> c PrimeIntSet)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c PrimeIntSet)
-> (PrimeIntSet -> Constr)
-> (PrimeIntSet -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c PrimeIntSet))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c PrimeIntSet))
-> ((forall b. Data b => b -> b) -> PrimeIntSet -> PrimeIntSet)
-> (forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> PrimeIntSet -> r)
-> (forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> PrimeIntSet -> r)
-> (forall u. (forall d. Data d => d -> u) -> PrimeIntSet -> [u])
-> (forall u.
Int -> (forall d. Data d => d -> u) -> PrimeIntSet -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> PrimeIntSet -> m PrimeIntSet)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> PrimeIntSet -> m PrimeIntSet)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> PrimeIntSet -> m PrimeIntSet)
-> Data PrimeIntSet
PrimeIntSet -> Constr
PrimeIntSet -> DataType
(forall b. Data b => b -> b) -> PrimeIntSet -> PrimeIntSet
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 u. Int -> (forall d. Data d => d -> u) -> PrimeIntSet -> u
forall u. (forall d. Data d => d -> u) -> PrimeIntSet -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> PrimeIntSet -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> PrimeIntSet -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> PrimeIntSet -> m PrimeIntSet
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> PrimeIntSet -> m PrimeIntSet
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c PrimeIntSet
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> PrimeIntSet -> c PrimeIntSet
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c PrimeIntSet)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c PrimeIntSet)
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> PrimeIntSet -> c PrimeIntSet
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> PrimeIntSet -> c PrimeIntSet
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c PrimeIntSet
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c PrimeIntSet
$ctoConstr :: PrimeIntSet -> Constr
toConstr :: PrimeIntSet -> Constr
$cdataTypeOf :: PrimeIntSet -> DataType
dataTypeOf :: PrimeIntSet -> DataType
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c PrimeIntSet)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c PrimeIntSet)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c PrimeIntSet)
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c PrimeIntSet)
$cgmapT :: (forall b. Data b => b -> b) -> PrimeIntSet -> PrimeIntSet
gmapT :: (forall b. Data b => b -> b) -> PrimeIntSet -> PrimeIntSet
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> PrimeIntSet -> r
gmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> PrimeIntSet -> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> PrimeIntSet -> r
gmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> PrimeIntSet -> r
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> PrimeIntSet -> [u]
gmapQ :: forall u. (forall d. Data d => d -> u) -> PrimeIntSet -> [u]
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> PrimeIntSet -> u
gmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> PrimeIntSet -> u
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> PrimeIntSet -> m PrimeIntSet
gmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> PrimeIntSet -> m PrimeIntSet
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> PrimeIntSet -> m PrimeIntSet
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> PrimeIntSet -> m PrimeIntSet
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> PrimeIntSet -> m PrimeIntSet
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> PrimeIntSet -> m PrimeIntSet
Data, Int -> PrimeIntSet -> ShowS
[PrimeIntSet] -> ShowS
PrimeIntSet -> String
(Int -> PrimeIntSet -> ShowS)
-> (PrimeIntSet -> String)
-> ([PrimeIntSet] -> ShowS)
-> Show PrimeIntSet
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> PrimeIntSet -> ShowS
showsPrec :: Int -> PrimeIntSet -> ShowS
$cshow :: PrimeIntSet -> String
show :: PrimeIntSet -> String
$cshowList :: [PrimeIntSet] -> ShowS
showList :: [PrimeIntSet] -> ShowS
Show, NonEmpty PrimeIntSet -> PrimeIntSet
PrimeIntSet -> PrimeIntSet -> PrimeIntSet
(PrimeIntSet -> PrimeIntSet -> PrimeIntSet)
-> (NonEmpty PrimeIntSet -> PrimeIntSet)
-> (forall b. Integral b => b -> PrimeIntSet -> PrimeIntSet)
-> Semigroup PrimeIntSet
forall b. Integral b => b -> PrimeIntSet -> PrimeIntSet
forall a.
(a -> a -> a)
-> (NonEmpty a -> a)
-> (forall b. Integral b => b -> a -> a)
-> Semigroup a
$c<> :: PrimeIntSet -> PrimeIntSet -> PrimeIntSet
<> :: PrimeIntSet -> PrimeIntSet -> PrimeIntSet
$csconcat :: NonEmpty PrimeIntSet -> PrimeIntSet
sconcat :: NonEmpty PrimeIntSet -> PrimeIntSet
$cstimes :: forall b. Integral b => b -> PrimeIntSet -> PrimeIntSet
stimes :: forall b. Integral b => b -> PrimeIntSet -> PrimeIntSet
Semigroup, Semigroup PrimeIntSet
PrimeIntSet
Semigroup PrimeIntSet =>
PrimeIntSet
-> (PrimeIntSet -> PrimeIntSet -> PrimeIntSet)
-> ([PrimeIntSet] -> PrimeIntSet)
-> Monoid PrimeIntSet
[PrimeIntSet] -> PrimeIntSet
PrimeIntSet -> PrimeIntSet -> PrimeIntSet
forall a.
Semigroup a =>
a -> (a -> a -> a) -> ([a] -> a) -> Monoid a
$cmempty :: PrimeIntSet
mempty :: PrimeIntSet
$cmappend :: PrimeIntSet -> PrimeIntSet -> PrimeIntSet
mappend :: PrimeIntSet -> PrimeIntSet -> PrimeIntSet
$cmconcat :: [PrimeIntSet] -> PrimeIntSet
mconcat :: [PrimeIntSet] -> PrimeIntSet
Monoid, PrimeIntSet -> ()
(PrimeIntSet -> ()) -> NFData PrimeIntSet
forall a. (a -> ()) -> NFData a
$crnf :: PrimeIntSet -> ()
rnf :: PrimeIntSet -> ()
NFData)
instance GHC.Exts.IsList PrimeIntSet where
type Item PrimeIntSet = Prime Int
fromList :: [Item PrimeIntSet] -> PrimeIntSet
fromList = ([Int] -> IntSet) -> [Prime Int] -> PrimeIntSet
forall a b. Coercible a b => a -> b
coerce [Int] -> IntSet
IS.fromList
toList :: PrimeIntSet -> [Item PrimeIntSet]
toList = (IntSet -> [Int]) -> PrimeIntSet -> [Prime Int]
forall a b. Coercible a b => a -> b
coerce IntSet -> [Int]
IS.toList
singleton :: Prime Int -> PrimeIntSet
singleton :: Prime Int -> PrimeIntSet
singleton = (Int -> IntSet) -> Prime Int -> PrimeIntSet
forall a b. Coercible a b => a -> b
coerce Int -> IntSet
IS.singleton
fromList :: [Prime Int] -> PrimeIntSet
fromList :: [Prime Int] -> PrimeIntSet
fromList = ([Int] -> IntSet) -> [Prime Int] -> PrimeIntSet
forall a b. Coercible a b => a -> b
coerce [Int] -> IntSet
IS.fromList
fromAscList :: [Prime Int] -> PrimeIntSet
fromAscList :: [Prime Int] -> PrimeIntSet
fromAscList = ([Int] -> IntSet) -> [Prime Int] -> PrimeIntSet
forall a b. Coercible a b => a -> b
coerce [Int] -> IntSet
IS.fromAscList
fromDistinctAscList :: [Prime Int] -> PrimeIntSet
fromDistinctAscList :: [Prime Int] -> PrimeIntSet
fromDistinctAscList = ([Int] -> IntSet) -> [Prime Int] -> PrimeIntSet
forall a b. Coercible a b => a -> b
coerce [Int] -> IntSet
IS.fromDistinctAscList
insert :: Prime Int -> PrimeIntSet -> PrimeIntSet
insert :: Prime Int -> PrimeIntSet -> PrimeIntSet
insert = (Int -> IntSet -> IntSet)
-> Prime Int -> PrimeIntSet -> PrimeIntSet
forall a b. Coercible a b => a -> b
coerce Int -> IntSet -> IntSet
IS.insert
delete :: Int -> PrimeIntSet -> PrimeIntSet
delete :: Int -> PrimeIntSet -> PrimeIntSet
delete = (Int -> IntSet -> IntSet) -> Int -> PrimeIntSet -> PrimeIntSet
forall a b. Coercible a b => a -> b
coerce Int -> IntSet -> IntSet
IS.delete
member :: Prime Int -> PrimeIntSet -> Bool
member :: Prime Int -> PrimeIntSet -> Bool
member = (Int -> IntSet -> Bool) -> Prime Int -> PrimeIntSet -> Bool
forall a b. Coercible a b => a -> b
coerce Int -> IntSet -> Bool
IS.member
notMember :: Prime Int -> PrimeIntSet -> Bool
notMember :: Prime Int -> PrimeIntSet -> Bool
notMember = (Int -> IntSet -> Bool) -> Prime Int -> PrimeIntSet -> Bool
forall a b. Coercible a b => a -> b
coerce Int -> IntSet -> Bool
IS.notMember
lookupEQ :: Int -> PrimeIntSet -> Maybe (Prime Int)
lookupEQ :: Int -> PrimeIntSet -> Maybe (Prime Int)
lookupEQ Int
x PrimeIntSet
xs
| (Prime Int -> PrimeIntSet -> Bool) -> Int -> PrimeIntSet -> Bool
forall a b. Coercible a b => a -> b
coerce Prime Int -> PrimeIntSet -> Bool
member Int
x PrimeIntSet
xs = Prime Int -> Maybe (Prime Int)
forall a. a -> Maybe a
Just (Int -> Prime Int
forall a. a -> Prime a
Prime Int
x)
| Bool
otherwise = Maybe (Prime Int)
forall a. Maybe a
Nothing
lookupLT :: Int -> PrimeIntSet -> Maybe (Prime Int)
lookupLT :: Int -> PrimeIntSet -> Maybe (Prime Int)
lookupLT = (Int -> IntSet -> Maybe Int)
-> Int -> PrimeIntSet -> Maybe (Prime Int)
forall a b. Coercible a b => a -> b
coerce Int -> IntSet -> Maybe Int
IS.lookupLT
lookupGT :: Int -> PrimeIntSet -> Maybe (Prime Int)
lookupGT :: Int -> PrimeIntSet -> Maybe (Prime Int)
lookupGT = (Int -> IntSet -> Maybe Int)
-> Int -> PrimeIntSet -> Maybe (Prime Int)
forall a b. Coercible a b => a -> b
coerce Int -> IntSet -> Maybe Int
IS.lookupGT
lookupLE :: Int -> PrimeIntSet -> Maybe (Prime Int)
lookupLE :: Int -> PrimeIntSet -> Maybe (Prime Int)
lookupLE = (Int -> IntSet -> Maybe Int)
-> Int -> PrimeIntSet -> Maybe (Prime Int)
forall a b. Coercible a b => a -> b
coerce Int -> IntSet -> Maybe Int
IS.lookupLE
lookupGE :: Int -> PrimeIntSet -> Maybe (Prime Int)
lookupGE :: Int -> PrimeIntSet -> Maybe (Prime Int)
lookupGE = (Int -> IntSet -> Maybe Int)
-> Int -> PrimeIntSet -> Maybe (Prime Int)
forall a b. Coercible a b => a -> b
coerce Int -> IntSet -> Maybe Int
IS.lookupGE
null :: PrimeIntSet -> Bool
null :: PrimeIntSet -> Bool
null = (IntSet -> Bool) -> PrimeIntSet -> Bool
forall a b. Coercible a b => a -> b
coerce IntSet -> Bool
IS.null
size :: PrimeIntSet -> Int
size :: PrimeIntSet -> Int
size = (IntSet -> Int) -> PrimeIntSet -> Int
forall a b. Coercible a b => a -> b
coerce IntSet -> Int
IS.size
isSubsetOf :: PrimeIntSet -> PrimeIntSet -> Bool
isSubsetOf :: PrimeIntSet -> PrimeIntSet -> Bool
isSubsetOf = (IntSet -> IntSet -> Bool) -> PrimeIntSet -> PrimeIntSet -> Bool
forall a b. Coercible a b => a -> b
coerce IntSet -> IntSet -> Bool
IS.isSubsetOf
isProperSubsetOf :: PrimeIntSet -> PrimeIntSet -> Bool
isProperSubsetOf :: PrimeIntSet -> PrimeIntSet -> Bool
isProperSubsetOf = (IntSet -> IntSet -> Bool) -> PrimeIntSet -> PrimeIntSet -> Bool
forall a b. Coercible a b => a -> b
coerce IntSet -> IntSet -> Bool
IS.isProperSubsetOf
disjoint :: PrimeIntSet -> PrimeIntSet -> Bool
disjoint :: PrimeIntSet -> PrimeIntSet -> Bool
disjoint = (IntSet -> IntSet -> Bool) -> PrimeIntSet -> PrimeIntSet -> Bool
forall a b. Coercible a b => a -> b
coerce IntSet -> IntSet -> Bool
IS.disjoint
difference :: PrimeIntSet -> IntSet -> PrimeIntSet
difference :: PrimeIntSet -> IntSet -> PrimeIntSet
difference = (IntSet -> IntSet -> IntSet)
-> PrimeIntSet -> IntSet -> PrimeIntSet
forall a b. Coercible a b => a -> b
coerce IntSet -> IntSet -> IntSet
IS.difference
(\\) :: PrimeIntSet -> IntSet -> PrimeIntSet
\\ :: PrimeIntSet -> IntSet -> PrimeIntSet
(\\) = (IntSet -> IntSet -> IntSet)
-> PrimeIntSet -> IntSet -> PrimeIntSet
forall a b. Coercible a b => a -> b
coerce IntSet -> IntSet -> IntSet
(IS.\\)
infixl 9 \\
symmetricDifference :: PrimeIntSet -> PrimeIntSet -> PrimeIntSet
#if MIN_VERSION_containers(0,8,0)
symmetricDifference = coerce IS.symmetricDifference
#else
symmetricDifference :: PrimeIntSet -> PrimeIntSet -> PrimeIntSet
symmetricDifference = (IntSet -> IntSet -> IntSet)
-> PrimeIntSet -> PrimeIntSet -> PrimeIntSet
forall a b. Coercible a b => a -> b
coerce IntSet -> IntSet -> IntSet
symmDiff
#endif
intersection :: PrimeIntSet -> IntSet -> PrimeIntSet
intersection :: PrimeIntSet -> IntSet -> PrimeIntSet
intersection = (IntSet -> IntSet -> IntSet)
-> PrimeIntSet -> IntSet -> PrimeIntSet
forall a b. Coercible a b => a -> b
coerce IntSet -> IntSet -> IntSet
IS.intersection
filter :: (Prime Int -> Bool) -> PrimeIntSet -> PrimeIntSet
filter :: (Prime Int -> Bool) -> PrimeIntSet -> PrimeIntSet
filter = ((Int -> Bool) -> IntSet -> IntSet)
-> (Prime Int -> Bool) -> PrimeIntSet -> PrimeIntSet
forall a b. Coercible a b => a -> b
coerce (Int -> Bool) -> IntSet -> IntSet
IS.filter
partition :: (Prime Int -> Bool) -> PrimeIntSet -> (PrimeIntSet, PrimeIntSet)
partition :: (Prime Int -> Bool) -> PrimeIntSet -> (PrimeIntSet, PrimeIntSet)
partition = ((Int -> Bool) -> IntSet -> (IntSet, IntSet))
-> (Prime Int -> Bool) -> PrimeIntSet -> (PrimeIntSet, PrimeIntSet)
forall a b. Coercible a b => a -> b
coerce (Int -> Bool) -> IntSet -> (IntSet, IntSet)
IS.partition
split :: Int -> PrimeIntSet -> (PrimeIntSet, PrimeIntSet)
split :: Int -> PrimeIntSet -> (PrimeIntSet, PrimeIntSet)
split = (Int -> IntSet -> (IntSet, IntSet))
-> Int -> PrimeIntSet -> (PrimeIntSet, PrimeIntSet)
forall a b. Coercible a b => a -> b
coerce Int -> IntSet -> (IntSet, IntSet)
IS.split
splitMember :: Prime Int -> PrimeIntSet -> (PrimeIntSet, Bool, PrimeIntSet)
splitMember :: Prime Int -> PrimeIntSet -> (PrimeIntSet, Bool, PrimeIntSet)
splitMember = (Int -> IntSet -> (IntSet, Bool, IntSet))
-> Prime Int -> PrimeIntSet -> (PrimeIntSet, Bool, PrimeIntSet)
forall a b. Coercible a b => a -> b
coerce Int -> IntSet -> (IntSet, Bool, IntSet)
IS.splitMember
splitLookupEQ :: Int -> PrimeIntSet -> (PrimeIntSet, Maybe (Prime Int), PrimeIntSet)
splitLookupEQ :: Int -> PrimeIntSet -> (PrimeIntSet, Maybe (Prime Int), PrimeIntSet)
splitLookupEQ Int
x PrimeIntSet
xs = (PrimeIntSet
lt, if Bool
eq then Prime Int -> Maybe (Prime Int)
forall a. a -> Maybe a
Just (Int -> Prime Int
forall a. a -> Prime a
Prime Int
x) else Maybe (Prime Int)
forall a. Maybe a
Nothing, PrimeIntSet
gt)
where
(PrimeIntSet
lt, Bool
eq, PrimeIntSet
gt) = (Int -> IntSet -> (IntSet, Bool, IntSet))
-> Int -> PrimeIntSet -> (PrimeIntSet, Bool, PrimeIntSet)
forall a b. Coercible a b => a -> b
coerce Int -> IntSet -> (IntSet, Bool, IntSet)
IS.splitMember Int
x PrimeIntSet
xs
splitRoot :: PrimeIntSet -> [PrimeIntSet]
splitRoot :: PrimeIntSet -> [PrimeIntSet]
splitRoot = (IntSet -> [IntSet]) -> PrimeIntSet -> [PrimeIntSet]
forall a b. Coercible a b => a -> b
coerce IntSet -> [IntSet]
IS.splitRoot
foldr :: forall b. (Prime Int -> b -> b) -> b -> PrimeIntSet -> b
foldr :: forall b. (Prime Int -> b -> b) -> b -> PrimeIntSet -> b
foldr = ((Int -> b -> b) -> b -> IntSet -> b)
-> (Prime Int -> b -> b) -> b -> PrimeIntSet -> b
forall a b. Coercible a b => a -> b
coerce (forall b. (Int -> b -> b) -> b -> IntSet -> b
IS.foldr @b)
foldl :: forall a. (a -> Prime Int -> a) -> a -> PrimeIntSet -> a
foldl :: forall a. (a -> Prime Int -> a) -> a -> PrimeIntSet -> a
foldl = ((a -> Int -> a) -> a -> IntSet -> a)
-> (a -> Prime Int -> a) -> a -> PrimeIntSet -> a
forall a b. Coercible a b => a -> b
coerce (forall a. (a -> Int -> a) -> a -> IntSet -> a
IS.foldl @a)
foldr' :: forall b. (Prime Int -> b -> b) -> b -> PrimeIntSet -> b
foldr' :: forall b. (Prime Int -> b -> b) -> b -> PrimeIntSet -> b
foldr' = ((Int -> b -> b) -> b -> IntSet -> b)
-> (Prime Int -> b -> b) -> b -> PrimeIntSet -> b
forall a b. Coercible a b => a -> b
coerce (forall b. (Int -> b -> b) -> b -> IntSet -> b
IS.foldr' @b)
foldl' :: forall a. (a -> Prime Int -> a) -> a -> PrimeIntSet -> a
foldl' :: forall a. (a -> Prime Int -> a) -> a -> PrimeIntSet -> a
foldl' = ((a -> Int -> a) -> a -> IntSet -> a)
-> (a -> Prime Int -> a) -> a -> PrimeIntSet -> a
forall a b. Coercible a b => a -> b
coerce (forall a. (a -> Int -> a) -> a -> IntSet -> a
IS.foldl' @a)
deleteMin :: PrimeIntSet -> PrimeIntSet
deleteMin :: PrimeIntSet -> PrimeIntSet
deleteMin = (IntSet -> IntSet) -> PrimeIntSet -> PrimeIntSet
forall a b. Coercible a b => a -> b
coerce IntSet -> IntSet
IS.deleteMin
deleteMax :: PrimeIntSet -> PrimeIntSet
deleteMax :: PrimeIntSet -> PrimeIntSet
deleteMax = (IntSet -> IntSet) -> PrimeIntSet -> PrimeIntSet
forall a b. Coercible a b => a -> b
coerce IntSet -> IntSet
IS.deleteMax
minView :: PrimeIntSet -> Maybe (Prime Int, PrimeIntSet)
minView :: PrimeIntSet -> Maybe (Prime Int, PrimeIntSet)
minView = (IntSet -> Maybe (Int, IntSet))
-> PrimeIntSet -> Maybe (Prime Int, PrimeIntSet)
forall a b. Coercible a b => a -> b
coerce IntSet -> Maybe (Int, IntSet)
IS.minView
maxView :: PrimeIntSet -> Maybe (Prime Int, PrimeIntSet)
maxView :: PrimeIntSet -> Maybe (Prime Int, PrimeIntSet)
maxView = (IntSet -> Maybe (Int, IntSet))
-> PrimeIntSet -> Maybe (Prime Int, PrimeIntSet)
forall a b. Coercible a b => a -> b
coerce IntSet -> Maybe (Int, IntSet)
IS.maxView
toAscList :: PrimeIntSet -> [Prime Int]
toAscList :: PrimeIntSet -> [Prime Int]
toAscList = (IntSet -> [Int]) -> PrimeIntSet -> [Prime Int]
forall a b. Coercible a b => a -> b
coerce IntSet -> [Int]
IS.toAscList
toDescList :: PrimeIntSet -> [Prime Int]
toDescList :: PrimeIntSet -> [Prime Int]
toDescList = (IntSet -> [Int]) -> PrimeIntSet -> [Prime Int]
forall a b. Coercible a b => a -> b
coerce IntSet -> [Int]
IS.toDescList
#if !MIN_VERSION_containers(0,8,0)
symmDiff :: IntSet -> IntSet -> IntSet
symmDiff :: IntSet -> IntSet -> IntSet
symmDiff IntSet
t1 IntSet
t2 = case IntSet
t1 of
IS.Bin Int
p1 Int
m1 IntSet
l1 IntSet
r1 -> case IntSet
t2 of
IS.Bin Int
p2 Int
m2 IntSet
l2 IntSet
r2
| Int -> Int -> Bool
shorter Int
m1 Int
m2 -> IntSet
symmDiff1
| Int -> Int -> Bool
shorter Int
m2 Int
m1 -> IntSet
symmDiff2
| Int
p1 Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
p2 -> Int -> Int -> IntSet -> IntSet -> IntSet
bin Int
p1 Int
m1 (IntSet -> IntSet -> IntSet
symmDiff IntSet
l1 IntSet
l2) (IntSet -> IntSet -> IntSet
symmDiff IntSet
r1 IntSet
r2)
| Bool
otherwise -> Int -> IntSet -> Int -> IntSet -> IntSet
link Int
p1 IntSet
t1 Int
p2 IntSet
t2
where
symmDiff1 :: IntSet
symmDiff1
| Int -> Int -> Int
mask Int
p2 Int
m1 Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
/= Int
p1 = Int -> IntSet -> Int -> IntSet -> IntSet
link Int
p1 IntSet
t1 Int
p2 IntSet
t2
| Int
p2 Int -> Int -> Int
forall a. Bits a => a -> a -> a
.&. Int
m1 Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
0 = Int -> Int -> IntSet -> IntSet -> IntSet
bin Int
p1 Int
m1 (IntSet -> IntSet -> IntSet
symmDiff IntSet
l1 IntSet
t2) IntSet
r1
| Bool
otherwise = Int -> Int -> IntSet -> IntSet -> IntSet
bin Int
p1 Int
m1 IntSet
l1 (IntSet -> IntSet -> IntSet
symmDiff IntSet
r1 IntSet
t2)
symmDiff2 :: IntSet
symmDiff2
| Int -> Int -> Int
mask Int
p1 Int
m2 Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
/= Int
p2 = Int -> IntSet -> Int -> IntSet -> IntSet
link Int
p1 IntSet
t1 Int
p2 IntSet
t2
| Int
p1 Int -> Int -> Int
forall a. Bits a => a -> a -> a
.&. Int
m2 Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
0 = Int -> Int -> IntSet -> IntSet -> IntSet
bin Int
p2 Int
m2 (IntSet -> IntSet -> IntSet
symmDiff IntSet
t1 IntSet
l2) IntSet
r2
| Bool
otherwise = Int -> Int -> IntSet -> IntSet -> IntSet
bin Int
p2 Int
m2 IntSet
l2 (IntSet -> IntSet -> IntSet
symmDiff IntSet
t1 IntSet
r2)
IS.Tip Int
kx Word
bm -> Int -> Word -> IntSet -> IntSet
symmDiffBM Int
kx Word
bm IntSet
t1
IntSet
IS.Nil -> IntSet
t1
IS.Tip Int
kx Word
bm -> Int -> Word -> IntSet -> IntSet
symmDiffBM Int
kx Word
bm IntSet
t2
IntSet
IS.Nil -> IntSet
t2
shorter :: Int -> Int -> Bool
shorter :: Int -> Int -> Bool
shorter = Word -> Word -> Bool
forall a. Ord a => a -> a -> Bool
(>) (Word -> Word -> Bool) -> (Int -> Word) -> Int -> Int -> Bool
forall b c a. (b -> b -> c) -> (a -> b) -> a -> a -> c
`on` Int -> Word
intToWord
symmDiffBM :: Int -> Word -> IntSet -> IntSet
symmDiffBM :: Int -> Word -> IntSet -> IntSet
symmDiffBM !Int
kx !Word
bm IntSet
t = case IntSet
t of
IS.Bin Int
p Int
m IntSet
l IntSet
r
| Int -> Int -> Int
mask Int
kx Int
m Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
/= Int
p -> Int -> IntSet -> Int -> IntSet -> IntSet
link Int
kx (Int -> Word -> IntSet
IS.Tip Int
kx Word
bm) Int
p IntSet
t
| Int
kx Int -> Int -> Int
forall a. Bits a => a -> a -> a
.&. Int
m Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
0 -> Int -> Int -> IntSet -> IntSet -> IntSet
bin Int
p Int
m (Int -> Word -> IntSet -> IntSet
symmDiffBM Int
kx Word
bm IntSet
l) IntSet
r
| Bool
otherwise -> Int -> Int -> IntSet -> IntSet -> IntSet
bin Int
p Int
m IntSet
l (Int -> Word -> IntSet -> IntSet
symmDiffBM Int
kx Word
bm IntSet
r)
IS.Tip Int
kx' Word
bm'
| Int
kx' Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
kx -> if Word
bm' Word -> Word -> Bool
forall a. Eq a => a -> a -> Bool
== Word
bm then IntSet
IS.Nil else Int -> Word -> IntSet
IS.Tip Int
kx (Word
bm' Word -> Word -> Word
forall a. Bits a => a -> a -> a
`xor` Word
bm)
| Bool
otherwise -> Int -> IntSet -> Int -> IntSet -> IntSet
link Int
kx (Int -> Word -> IntSet
IS.Tip Int
kx Word
bm) Int
kx' IntSet
t
IntSet
IS.Nil -> Int -> Word -> IntSet
IS.Tip Int
kx Word
bm
link :: Int -> IntSet -> Int -> IntSet -> IntSet
link :: Int -> IntSet -> Int -> IntSet -> IntSet
link Int
p1 IntSet
t1 Int
p2 IntSet
t2
| Int
p1 Int -> Int -> Int
forall a. Bits a => a -> a -> a
.&. Int
m Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
0 = Int -> Int -> IntSet -> IntSet -> IntSet
IS.Bin Int
p Int
m IntSet
t1 IntSet
t2
| Bool
otherwise = Int -> Int -> IntSet -> IntSet -> IntSet
IS.Bin Int
p Int
m IntSet
t2 IntSet
t1
where
m :: Int
m = Word -> Int
wordToInt (Word -> Word
highestBitMask (Int -> Word
intToWord Int
p1 Word -> Word -> Word
forall a. Bits a => a -> a -> a
`xor` Int -> Word
intToWord Int
p2))
p :: Int
p = Int -> Int -> Int
mask Int
p1 Int
m
{-# INLINE link #-}
bin :: Int -> Int -> IntSet -> IntSet -> IntSet
bin :: Int -> Int -> IntSet -> IntSet -> IntSet
bin Int
p Int
m IntSet
l IntSet
r = case IntSet
r of
IntSet
IS.Nil -> IntSet
l
IntSet
_ -> case IntSet
l of
IntSet
IS.Nil -> IntSet
r
IntSet
_ -> Int -> Int -> IntSet -> IntSet -> IntSet
IS.Bin Int
p Int
m IntSet
l IntSet
r
{-# INLINE bin #-}
mask :: Int -> Int -> Int
mask :: Int -> Int -> Int
mask Int
i Int
m = Int
i Int -> Int -> Int
forall a. Bits a => a -> a -> a
.&. (Int -> Int
forall a. Bits a => a -> a
complement (Int
m Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
1) Int -> Int -> Int
forall a. Bits a => a -> a -> a
`xor` Int
m)
{-# INLINE mask #-}
#endif