arithmoi-0.13.2.0: Efficient basic number-theoretic functions.
Copyright(c) 2016-2018 Andrew.Lelechenko
LicenseMIT
MaintainerAndrew Lelechenko <andrew.lelechenko@gmail.com>
Safe HaskellNone
LanguageHaskell2010

Math.NumberTheory.Primes

Description

Synopsis

Documentation

data Prime a Source #

Wrapper for prime elements of a. It is supposed to be constructed by nextPrime / precPrime . and eliminated by unPrime .

One can leverage Enum instance to generate lists of primes. Here are some examples.

  • Generate primes from the given interval:
>>> :set -XFlexibleContexts
>>> [nextPrime 101 .. precPrime 130]
[Prime 101,Prime 103,Prime 107,Prime 109,Prime 113,Prime 127]
  • Generate an infinite list of primes:
[nextPrime 101 ..]
[Prime 101,Prime 103,Prime 107,Prime 109,Prime 113,Prime 127...
  • Generate primes from the given interval of form p = 6k+5:
>>> [nextPrime 101, nextPrime 107 .. precPrime 150]
[Prime 101,Prime 107,Prime 113,Prime 131,Prime 137,Prime 149]
  • Get next prime:
>>> succ (nextPrime 101)
Prime 103
  • Get previous prime:
>>> pred (nextPrime 101)
Prime 97
>>> fromEnum (precPrime 100)
25
>>> toEnum 25 :: Prime Int
Prime 97

Instances

Instances details
Vector Vector a => Vector Vector (Prime a) Source #
Instance details

Defined in Math.NumberTheory.Primes.Types

Methods

basicUnsafeFreeze :: Mutable Vector s (Prime a) -> ST s (Vector (Prime a))

basicUnsafeThaw :: Vector (Prime a) -> ST s (Mutable Vector s (Prime a))

basicLength :: Vector (Prime a) -> Int

basicUnsafeSlice :: Int -> Int -> Vector (Prime a) -> Vector (Prime a)

basicUnsafeIndexM :: Vector (Prime a) -> Int -> Box (Prime a)

basicUnsafeCopy :: Mutable Vector s (Prime a) -> Vector (Prime a) -> ST s ()

elemseq :: Vector (Prime a) -> Prime a -> b -> b

MVector MVector a => MVector MVector (Prime a) Source #
Instance details

Defined in Math.NumberTheory.Primes.Types

Methods

basicLength :: MVector s (Prime a) -> Int

basicUnsafeSlice :: Int -> Int -> MVector s (Prime a) -> MVector s (Prime a)

basicOverlaps :: MVector s (Prime a) -> MVector s (Prime a) -> Bool

basicUnsafeNew :: Int -> ST s (MVector s (Prime a))

basicInitialize :: MVector s (Prime a) -> ST s ()

basicUnsafeReplicate :: Int -> Prime a -> ST s (MVector s (Prime a))

basicUnsafeRead :: MVector s (Prime a) -> Int -> ST s (Prime a)

basicUnsafeWrite :: MVector s (Prime a) -> Int -> Prime a -> ST s ()

basicClear :: MVector s (Prime a) -> ST s ()

basicSet :: MVector s (Prime a) -> Prime a -> ST s ()

basicUnsafeCopy :: MVector s (Prime a) -> MVector s (Prime a) -> ST s ()

basicUnsafeMove :: MVector s (Prime a) -> MVector s (Prime a) -> ST s ()

basicUnsafeGrow :: MVector s (Prime a) -> Int -> ST s (MVector s (Prime a))

Instance details

Defined in Math.NumberTheory.Primes

Instance details

Defined in Math.NumberTheory.Primes

Instance details

Defined in Math.NumberTheory.Primes.Types

Associated Types

type Rep (Prime a)
Instance details

Defined in Math.NumberTheory.Primes.Types

type Rep (Prime a) = D1 ('MetaData "Prime" "Math.NumberTheory.Primes.Types" "arithmoi-0.13.2.0-AwCKqZxCaASL4wirVJd5zg" 'True) (C1 ('MetaCons "Prime" 'PrefixI 'True) (S1 ('MetaSel ('Just "unPrime") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a)))

Methods

from :: Prime a -> Rep (Prime a) x #

to :: Rep (Prime a) x -> Prime a #

Show a => Show (Prime a) Source #
Instance details

Defined in Math.NumberTheory.Primes.Types

Methods

showsPrec :: Int -> Prime a -> ShowS #

show :: Prime a -> String #

showList :: [Prime a] -> ShowS #

NFData a => NFData (Prime a) Source #
Instance details

Defined in Math.NumberTheory.Primes.Types

Methods

rnf :: Prime a -> () #

Eq a => Eq (Prime a) Source #
Instance details

Defined in Math.NumberTheory.Primes.Types

Methods

(==) :: Prime a -> Prime a -> Bool #

(/=) :: Prime a -> Prime a -> Bool #

Ord a => Ord (Prime a) Source #
Instance details

Defined in Math.NumberTheory.Primes.Types

Methods

compare :: Prime a -> Prime a -> Ordering #

(<) :: Prime a -> Prime a -> Bool #

(<=) :: Prime a -> Prime a -> Bool #

(>) :: Prime a -> Prime a -> Bool #

(>=) :: Prime a -> Prime a -> Bool #

max :: Prime a -> Prime a -> Prime a #

min :: Prime a -> Prime a -> Prime a #

Unbox a => Unbox (Prime a) Source #
Instance details

Defined in Math.NumberTheory.Primes.Types

newtype MVector s (Prime a) Source #
Instance details

Defined in Math.NumberTheory.Primes.Types

newtype MVector s (Prime a) = MV_Prime (MVector s a)
type Rep (Prime a) Source #
Instance details

Defined in Math.NumberTheory.Primes.Types

type Rep (Prime a) = D1 ('MetaData "Prime" "Math.NumberTheory.Primes.Types" "arithmoi-0.13.2.0-AwCKqZxCaASL4wirVJd5zg" 'True) (C1 ('MetaCons "Prime" 'PrefixI 'True) (S1 ('MetaSel ('Just "unPrime") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a)))
newtype Vector (Prime a) Source #
Instance details

Defined in Math.NumberTheory.Primes.Types

newtype Vector (Prime a) = V_Prime (Vector a)

unPrime :: Prime a -> a Source #

Unwrap prime element.

toPrimeIntegral :: (Integral a, Integral b, Bits a, Bits b) => Prime a -> Maybe (Prime b) Source #

Convert between primes of different types, similar in spirit to toIntegralSized .

A simpler version of this function is:

toPrimeIntegral :: (Integral a, Integral b) => a -> Maybe b
toPrimeIntegral (Prime a)
 | toInteger a == b = Just (Prime (fromInteger b))
 | otherwise = Nothing
 where
 b = toInteger a

The point of toPrimeIntegral is to avoid redundant conversions and conditions, when it is safe to do so, determining type sizes statically with bitSizeMaybe . For example, toPrimeIntegral from Prime Int to Prime Word boils down to Just . fromIntegral .

nextPrime :: (Bits a, Integral a, UniqueFactorisation a) => a -> Prime a Source #

Smallest prime, greater or equal to argument.

nextPrime (-100) == 2
nextPrime 1000 == 1009
nextPrime 1009 == 1009

precPrime :: (Bits a, Integral a, UniqueFactorisation a) => a -> Prime a Source #

Largest prime, less or equal to argument. Undefined, when argument < 2.

precPrime 100 == 97
precPrime 97 == 97

class Num a => UniqueFactorisation a where Source #

A class for unique factorisation domains.

Methods

factorise :: a -> [(Prime a, Word)] Source #

Factorise a number into a product of prime powers. Factorisation of 0 is an undefined behaviour. Otherwise following invariants hold:

abs n == abs (product (map (\(p, k) -> unPrime p ^ k) (factorise n)))
all ((> 0) . snd) (factorise n)
>>> factorise (1 :: Integer)
[]
>>> factorise (-1 :: Integer)
[]
>>> factorise (6 :: Integer)
[(Prime 2,1),(Prime 3,1)]
>>> factorise (-108 :: Integer)
[(Prime 2,2),(Prime 3,3)]

This function is a replacement for factorise . If you were looking for the latter, please import Math.NumberTheory.Primes.Factorisation instead of this module.

Warning: there are no guarantees of any particular order of prime factors, do not expect them to be ascending. E. g.,

>>> factorise 10251562501
[(Prime 101701,1),(Prime 100801,1)]

isPrime :: a -> Maybe (Prime a) Source #

Check whether an argument is prime. If it is then return an associated prime.

>>> isPrime (3 :: Integer)
Just (Prime 3)
>>> isPrime (4 :: Integer)
Nothing
>>> isPrime (-5 :: Integer)
Just (Prime 5)

This function is a replacement for isPrime . If you were looking for the latter, please import Math.NumberTheory.Primes.Testing instead of this module.

Instances

Instances details
UniqueFactorisation EisensteinInteger Source #

See the source code and Haddock comments for the factorise and isPrime functions in this module (they are not exported) for implementation details.

Instance details

Defined in Math.NumberTheory.Primes

Instance details

Defined in Math.NumberTheory.Primes

Instance details

Defined in Math.NumberTheory.Primes

Instance details

Defined in Math.NumberTheory.Primes

factorBack :: Num a => [(Prime a, Word)] -> a Source #

Restore a number from its factorisation.

Old interface

primes :: Integral a => [Prime a] Source #

Ascending list of primes.

>>> take 10 primes
[Prime 2,Prime 3,Prime 5,Prime 7,Prime 11,Prime 13,Prime 17,Prime 19,Prime 23,Prime 29]

primes is a polymorphic list, so the results of computations are not retained in memory. Make it monomorphic to take advantages of memoization. Compare

>>> primes !! 1000000 :: Prime Int -- (5.32 secs, 6,945,267,496 bytes)
Prime 15485867
>>> primes !! 1000000 :: Prime Int -- (5.19 secs, 6,945,267,496 bytes)
Prime 15485867

against

>>> let primes' = primes :: [Prime Int]
>>> primes' !! 1000000 :: Prime Int -- (5.29 secs, 6,945,269,856 bytes)
Prime 15485867
>>> primes' !! 1000000 :: Prime Int -- (0.02 secs, 336,232 bytes)
Prime 15485867

Orphan instances

Instance details
Instance details

AltStyle によって変換されたページ (->オリジナル) /