arithmoi-0.12.1.0: Efficient basic number-theoretic functions.
Copyright(c) 2020 Andrew Lelechenko
LicenseMIT
MaintainerAndrew Lelechenko <andrew.lelechenko@gmail.com>
Safe HaskellSafe-Inferred
LanguageHaskell2010

Math.NumberTheory.Primes.IntSet

Description

A newtype wrapper around IntSet.

This module is intended to be imported qualified, e. g.,

import Math.NumberTheory.Primes.IntSet (PrimeIntSet)
import qualified Math.NumberTheory.Primes.IntSet as PrimeIntSet
Synopsis

Set type

data PrimeIntSet Source #

A set of Prime integers.

Instances

Instances details
Data PrimeIntSet Source # 
Instance details

Defined in Math.NumberTheory.Primes.IntSet

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> PrimeIntSet -> c PrimeIntSet #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c PrimeIntSet #

toConstr :: PrimeIntSet -> Constr #

dataTypeOf :: PrimeIntSet -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c PrimeIntSet) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c PrimeIntSet) #

gmapT :: (forall b. Data b => b -> b) -> PrimeIntSet -> PrimeIntSet #

gmapQl :: (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 #

gmapQ :: (forall d. Data d => d -> u) -> PrimeIntSet -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> PrimeIntSet -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> PrimeIntSet -> m PrimeIntSet #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> PrimeIntSet -> m PrimeIntSet #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> PrimeIntSet -> m PrimeIntSet #

Monoid PrimeIntSet Source # 
Instance details

Defined in Math.NumberTheory.Primes.IntSet

Semigroup PrimeIntSet Source # 
Instance details

Defined in Math.NumberTheory.Primes.IntSet

IsList PrimeIntSet Source # 
Instance details

Defined in Math.NumberTheory.Primes.IntSet

Associated Types

type Item PrimeIntSet #

Show PrimeIntSet Source # 
Instance details

Defined in Math.NumberTheory.Primes.IntSet

NFData PrimeIntSet Source # 
Instance details

Defined in Math.NumberTheory.Primes.IntSet

Methods

rnf :: PrimeIntSet -> () #

Eq PrimeIntSet Source # 
Instance details

Defined in Math.NumberTheory.Primes.IntSet

Ord PrimeIntSet Source # 
Instance details

Defined in Math.NumberTheory.Primes.IntSet

type Item PrimeIntSet Source # 
Instance details

Defined in Math.NumberTheory.Primes.IntSet

unPrimeIntSet :: PrimeIntSet -> IntSet Source #

Convert to a set of integers.

Construction

Use mempty to create an empty set.

singleton :: Prime Int -> PrimeIntSet Source #

Build a singleton set.

fromList :: [Prime Int] -> PrimeIntSet Source #

Build a set from a list of primes.

fromAscList :: [Prime Int] -> PrimeIntSet Source #

Build a set from an ascending list of primes (the precondition is not checked).

fromDistinctAscList :: [Prime Int] -> PrimeIntSet Source #

Build a set from an ascending list of distinct primes (the precondition is not checked).

Insertion

insert :: Prime Int -> PrimeIntSet -> PrimeIntSet Source #

Insert a prime into the set.

Deletion

delete :: Int -> PrimeIntSet -> PrimeIntSet Source #

Delete an integer from the set.

Query

member :: Prime Int -> PrimeIntSet -> Bool Source #

Check whether the given prime is a member of the set.

notMember :: Prime Int -> PrimeIntSet -> Bool Source #

Check whether the given prime is not a member of the set.

lookupEQ :: Int -> PrimeIntSet -> Maybe (Prime Int) Source #

Find a prime in the set, equal to the given integer, if any exists.

lookupLT :: Int -> PrimeIntSet -> Maybe (Prime Int) Source #

Find the largest prime in the set, smaller than the given integer, if any exists.

lookupGT :: Int -> PrimeIntSet -> Maybe (Prime Int) Source #

Find the smallest prime in the set, greater than the given integer, if any exists.

lookupLE :: Int -> PrimeIntSet -> Maybe (Prime Int) Source #

Find the largest prime in the set, smaller or equal to the given integer, if any exists.

lookupGE :: Int -> PrimeIntSet -> Maybe (Prime Int) Source #

Find the smallest prime in the set, greater or equal to the given integer, if any exists.

null :: PrimeIntSet -> Bool Source #

Check whether the set is empty.

size :: PrimeIntSet -> Int Source #

Cardinality of the set.

isSubsetOf :: PrimeIntSet -> PrimeIntSet -> Bool Source #

Check whether the first argument is a subset of the second one.

isProperSubsetOf :: PrimeIntSet -> PrimeIntSet -> Bool Source #

Check whether the first argument is a proper subset of the second one.

disjoint :: PrimeIntSet -> PrimeIntSet -> Bool Source #

Check whether two sets are disjoint.

Combine

Use <> for unions.

difference :: PrimeIntSet -> IntSet -> PrimeIntSet Source #

Difference between a set of primes and a set of integers.

(\\) :: PrimeIntSet -> IntSet -> PrimeIntSet infixl 9 Source #

An alias to difference.

symmetricDifference :: PrimeIntSet -> PrimeIntSet -> PrimeIntSet Source #

Symmetric difference of two sets of primes.

intersection :: PrimeIntSet -> IntSet -> PrimeIntSet Source #

Intersection of a set of primes and a set of integers.

Filter

filter :: (Prime Int -> Bool) -> PrimeIntSet -> PrimeIntSet Source #

Filter primes satisfying a predicate.

partition :: (Prime Int -> Bool) -> PrimeIntSet -> (PrimeIntSet, PrimeIntSet) Source #

Partition primes according to a predicate.

split :: Int -> PrimeIntSet -> (PrimeIntSet, PrimeIntSet) Source #

Split into primes strictly less and strictly greater than the first argument.

splitRoot :: PrimeIntSet -> [PrimeIntSet] Source #

Decompose a set into pieces based on the structure of the underlying tree.

Folds

foldr :: forall b. (Prime Int -> b -> b) -> b -> PrimeIntSet -> b Source #

Fold a set using the given right-associative operator.

foldl :: forall a. (a -> Prime Int -> a) -> a -> PrimeIntSet -> a Source #

Fold a set using the given left-associative operator.

foldr' :: forall b. (Prime Int -> b -> b) -> b -> PrimeIntSet -> b Source #

A strict version of foldr.

foldl' :: forall a. (a -> Prime Int -> a) -> a -> PrimeIntSet -> a Source #

A strict version of foldl.

Min/Max

deleteMin :: PrimeIntSet -> PrimeIntSet Source #

Delete the smallest prime in the set.

deleteMax :: PrimeIntSet -> PrimeIntSet Source #

Delete the largest prime in the set.

minView :: PrimeIntSet -> Maybe (Prime Int, PrimeIntSet) Source #

Split a set into the smallest prime and the rest, if non-empty.

maxView :: PrimeIntSet -> Maybe (Prime Int, PrimeIntSet) Source #

Split a set into the largest prime and the rest, if non-empty.

Conversion

toAscList :: PrimeIntSet -> [Prime Int] Source #

Convert the set to a list of ascending primes.

toDescList :: PrimeIntSet -> [Prime Int] Source #

Convert the set to a list of descending primes.