Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Prime number related functions.
Synopsis
- primes_list :: Integral i => [i]
- prime_k :: Integral a => a -> Maybe Int
- prime_k_err :: Integral a => a -> Int
- factor :: Integral i => [i] -> i -> [i]
- prime_factors :: Integral i => i -> [i]
- prime_limit :: Integral i => i -> i
- multiplicities :: Eq t => [t] -> [(t, Int)]
- multiplicities_pp :: Show t => [(t, Int)] -> String
- prime_factors_m :: Integral i => i -> [(i, Int)]
- prime_factors_m_pp :: (Show i, Integral i) => i -> String
- rat_prime_factors :: Integral i => (i, i) -> ([i], [i])
- rational_prime_factors :: Integral i => Ratio i -> ([i], [i])
- rat_prime_factors_sgn :: Integral i => (i, i) -> [i]
- rational_prime_factors_sgn :: Integral i => Ratio i -> [i]
- rat_prime_limit :: Integral i => (i, i) -> i
- rational_prime_limit :: Integral i => Ratio i -> i
- rat_pf_merge :: Ord t => [(t, Int)] -> [(t, Int)] -> [(t, Int)]
- rat_prime_factors_m :: Integral i => (i, i) -> [(i, Int)]
- rational_prime_factors_m :: Integral i => Ratio i -> [(i, Int)]
- rat_prime_factors_l :: Integral i => (i, i) -> [Int]
- rational_prime_factors_l :: Integral i => Ratio i -> [Int]
- rat_prime_factors_t :: (Integral i, Show i) => Int -> (i, i) -> [Int]
- rational_prime_factors_t :: (Integral i, Show i) => Int -> Ratio i -> [Int]
- rat_prime_factors_c :: (Integral i, Show i) => [i] -> (i, i) -> [Int]
- rational_prime_factors_c :: (Integral i, Show i) => [i] -> Ratio i -> [Int]
- prime_factors_pp :: [Integer] -> String
- prime_factors_pp_sup_ol :: Bool -> [Integer] -> String
Documentation
primes_list :: Integral i => [i] Source #
Alias for primes
.
take 12 primes_list == [2,3,5,7,11,13,17,19,23,29,31,37]
prime_k :: Integral a => a -> Maybe Int Source #
Give zero-index of prime, or Nothing if value is not prime.
map prime_k [2,3,5,7,11,13,17,19,23,29,31,37] == map Just [0 .. 11] map prime_k [1,4,6,8,9,10,12,14,15,16,18,20,21,22] == replicate 14 Nothing
factor :: Integral i => [i] -> i -> [i] Source #
Generate list of factors of n from x.
factor primes_list 315 == [3,3,5,7] Primes.primeFactors 315 == [3,3,5,7]
As a special case 1 gives the empty list.
factor primes_list 1 == [] Primes.primeFactors 1 == []
prime_factors :: Integral i => i -> [i] Source #
factor
of primes_list
.
map prime_factors [-1,0,1] == [[],[],[]] map prime_factors [1,4,231,315] == [[],[2,2],[3,7,11],[3,3,5,7]] map Primes.primeFactors [1,4,231,315] == [[],[2,2],[3,7,11],[3,3,5,7]]
prime_limit :: Integral i => i -> i Source #
map prime_limit [243,125] == [3,5] map prime_limit [0,1] == [1,1]
multiplicities :: Eq t => [t] -> [(t, Int)] Source #
Collect number of occurences of each element of a sorted list.
multiplicities [1,1,1,2,2,3] == [(1,3),(2,2),(3,1)]
multiplicities_pp :: Show t => [(t, Int)] -> String Source #
Pretty printer for histogram (multiplicites).
multiplicities_pp [(3,2),(5,1),(7,1)] == "3×2 5×1 7×1"
prime_factors_m :: Integral i => i -> [(i, Int)] Source #
multiplicities
of primeFactors
.
prime_factors_m 1 == [] prime_factors_m 315 == [(3,2),(5,1),(7,1)]
rat_prime_factors :: Integral i => (i, i) -> ([i], [i]) Source #
Prime factors of n and d.
rational_prime_factors :: Integral i => Ratio i -> ([i], [i]) Source #
Ratio
variant of rat_prime_factors
rat_prime_factors_sgn :: Integral i => (i, i) -> [i] Source #
Variant that writes factors of numerator as positive and factors for denominator as negative. Sorted by absolute value.
rat_prime_factors_sgn (3 * 5 * 7 * 11,1) == [3,5,7,11] rat_prime_factors_sgn (3 * 5,7 * 11) == [3,5,-7,-11] rat_prime_factors_sgn (3 * 7,5) == [3,-5,7]
rational_prime_factors_sgn :: Integral i => Ratio i -> [i] Source #
Rational variant.
rational_prime_factors_sgn (2 * 2 * 2 * 1/3 * 1/3 * 1/3 * 1/3 * 5) == [2,2,2,-3,-3,-3,-3,5]
rat_prime_limit :: Integral i => (i, i) -> i Source #
The largest prime factor of n/d.
rational_prime_limit :: Integral i => Ratio i -> i Source #
The largest prime factor of n.
rational_prime_limit (243/125) == 5
rat_pf_merge :: Ord t => [(t, Int)] -> [(t, Int)] -> [(t, Int)] Source #
Merge function for rat_prime_factors_m
rat_prime_factors_m :: Integral i => (i, i) -> [(i, Int)] Source #
Collect the prime factors in a rational number given as a numerator/ denominator pair (n,m). Prime factors are listed in ascending order with their positive or negative multiplicities, depending on whether the prime factor occurs in the numerator or the denominator (after cancelling out common factors).
rat_prime_factors_m (1,1) == [] rat_prime_factors_m (16,15) == [(2,4),(3,-1),(5,-1)] rat_prime_factors_m (10,9) == [(2,1),(3,-2),(5,1)] rat_prime_factors_m (81,64) == [(2,-6),(3,4)] rat_prime_factors_m (27,16) == [(2,-4),(3,3)] rat_prime_factors_m (12,7) == [(2,2),(3,1),(7,-1)] rat_prime_factors_m (5,31) == [(5,1),(31,-1)]
rational_prime_factors_m :: Integral i => Ratio i -> [(i, Int)] Source #
Ratio
variant of rat_prime_factors_m
rat_prime_factors_l :: Integral i => (i, i) -> [Int] Source #
Variant of rat_prime_factors_m
giving results in a list.
rat_prime_factors_l (1,1) == [] rat_prime_factors_l (2^5,9) == [5,-2] rat_prime_factors_l (2*2*3,7) == [2,1,0,-1] rat_prime_factors_l (3*3,11*13) == [0,2,0,0,-1,-1]
rational_prime_factors_l :: Integral i => Ratio i -> [Int] Source #
Ratio
variant of rat_prime_factors_l
map rational_prime_factors_l [1/31,256/243] == [[0,0,0,0,0,0,0,0,0,0,-1],[8,-5]]
rat_prime_factors_t :: (Integral i, Show i) => Int -> (i, i) -> [Int] Source #
Variant of rational_prime_factors_l
padding table to k places.
It is an error for k to indicate a prime less than the limit of x.
map (rat_prime_factors_t 6) [(5,13),(12,7)] == [[0,0,1,0,0,-1],[2,1,0,-1,0,0]] rat_prime_factors_t 3 (9,7) == undefined
rational_prime_factors_t :: (Integral i, Show i) => Int -> Ratio i -> [Int] Source #
Ratio
variant of rat_prime_factors_t
rat_prime_factors_c :: (Integral i, Show i) => [i] -> (i, i) -> [Int] Source #
Condense factors list to include only indicated places. It is an error if a deleted factor has a non-zero entry in the table.
rat_prime_factors_l (12,7) == [2,1,0,-1] rat_prime_factors_c [2,3,5,7] (12,7) == [2,1,0,-1] rat_prime_factors_c [2,3,7] (12,7) == [2,1,-1]
rational_prime_factors_c :: (Integral i, Show i) => [i] -> Ratio i -> [Int] Source #
Ratio
variant of rat_prime_factors_t
map (rational_prime_factors_c [3,5,31]) [3,5,31]
prime_factors_pp :: [Integer] -> String Source #
Pretty printer for prime factors. sup=superscript ol=overline