Copyright | (c) 2016 Andrew Lelechenko |
---|---|
License | MIT |
Maintainer | Andrew Lelechenko <andrew.lelechenko@gmail.com> |
Safe Haskell | None |
Language | Haskell2010 |
This module provides an interface for defining and manipulating arithmetic functions. It also defines several most widespreaded arithmetic functions.
Synopsis
- data ArithmeticFunction n a where
- ArithmeticFunction :: Monoid m => (Prime n -> Word -> m) -> (m -> a) -> ArithmeticFunction n a
- runFunction :: UniqueFactorisation n => ArithmeticFunction n a -> n -> a
- runFunctionOnFactors :: ArithmeticFunction n a -> [(Prime n, Word)] -> a
- multiplicative :: Num a => (Prime n -> Word -> a) -> ArithmeticFunction n a
- divisors :: (UniqueFactorisation n, Ord n) => n -> Set n
- divisorsA :: (UniqueFactorisation n, Ord n) => ArithmeticFunction n (Set n)
- divisorsList :: UniqueFactorisation n => n -> [n]
- divisorsListA :: UniqueFactorisation n => ArithmeticFunction n [n]
- divisorsSmall :: Int -> IntSet
- divisorsSmallA :: ArithmeticFunction Int IntSet
- divisorCount :: (UniqueFactorisation n, Num a) => n -> a
- tau :: (UniqueFactorisation n, Num a) => n -> a
- tauA :: Num a => ArithmeticFunction n a
- sigma :: (UniqueFactorisation n, Integral n) => Word -> n -> n
- sigmaA :: (UniqueFactorisation n, Integral n) => Word -> ArithmeticFunction n n
- totient :: UniqueFactorisation n => n -> n
- totientA :: UniqueFactorisation n => ArithmeticFunction n n
- jordan :: UniqueFactorisation n => Word -> n -> n
- jordanA :: UniqueFactorisation n => Word -> ArithmeticFunction n n
- ramanujan :: Integer -> Integer
- ramanujanA :: ArithmeticFunction Integer Integer
- moebius :: UniqueFactorisation n => n -> Moebius
- moebiusA :: ArithmeticFunction n Moebius
- data Moebius
- runMoebius :: Num a => Moebius -> a
- liouville :: (UniqueFactorisation n, Num a) => n -> a
- liouvilleA :: Num a => ArithmeticFunction n a
- additive :: Num a => (Prime n -> Word -> a) -> ArithmeticFunction n a
- smallOmega :: (UniqueFactorisation n, Num a) => n -> a
- smallOmegaA :: Num a => ArithmeticFunction n a
- bigOmega :: UniqueFactorisation n => n -> Word
- bigOmegaA :: ArithmeticFunction n Word
- carmichael :: (UniqueFactorisation n, Integral n) => n -> n
- carmichaelA :: (UniqueFactorisation n, Integral n) => ArithmeticFunction n n
- expMangoldt :: UniqueFactorisation n => n -> n
- expMangoldtA :: UniqueFactorisation n => ArithmeticFunction n n
- isNFree :: UniqueFactorisation n => Word -> n -> Bool
- isNFreeA :: Word -> ArithmeticFunction n Bool
- nFrees :: forall a. Integral a => Word -> [a]
- nFreesBlock :: forall a. Integral a => Word -> a -> Word -> [a]
Documentation
data ArithmeticFunction n a where Source #
A typical arithmetic function operates on the canonical factorisation of a number into prime's powers and consists of two rules. The first one determines the values of the function on the powers of primes. The second one determines how to combine these values into final result.
In the following definition the first argument is the function on prime's
powers, the monoid instance determines a rule of combination (typically
Product
or Sum
), and the second argument is convenient for unwrapping
(typically, getProduct
or getSum
).
ArithmeticFunction :: Monoid m => (Prime n -> Word -> m) -> (m -> a) -> ArithmeticFunction n a |
Instances
runFunction :: UniqueFactorisation n => ArithmeticFunction n a -> n -> a Source #
Convert to a function. The value on 0 is undefined.
runFunctionOnFactors :: ArithmeticFunction n a -> [(Prime n, Word)] -> a Source #
Convert to a function on prime factorisation.
Multiplicative functions
multiplicative :: Num a => (Prime n -> Word -> a) -> ArithmeticFunction n a Source #
Create a multiplicative function from the function on prime's powers. See examples below.
divisorsA :: (UniqueFactorisation n, Ord n) => ArithmeticFunction n (Set n) Source #
The set of all (positive) divisors of an argument.
divisorsList :: UniqueFactorisation n => n -> [n] Source #
See divisorsListA
.
divisorsListA :: UniqueFactorisation n => ArithmeticFunction n [n] Source #
The unsorted list of all (positive) divisors of an argument, produced in lazy fashion.
divisorsSmall :: Int -> IntSet Source #
See divisorsSmallA
.
divisorsSmallA :: ArithmeticFunction Int IntSet Source #
Same as divisors
, but with better performance on cost of type restriction.
divisorCount :: (UniqueFactorisation n, Num a) => n -> a Source #
Synonym for tau
.
>>>
map divisorCount [1..10]
[1,2,2,3,2,4,2,4,3,4]
tauA :: Num a => ArithmeticFunction n a Source #
The number of (positive) divisors of an argument.
tauA = multiplicative (\_ k -> k + 1)
sigmaA :: (UniqueFactorisation n, Integral n) => Word -> ArithmeticFunction n n Source #
The sum of the k
-th powers of (positive) divisors of an argument.
sigmaA = multiplicative (\p k -> sum $ map (p ^) [0..k]) sigmaA 0 = tauA
totient :: UniqueFactorisation n => n -> n Source #
See totientA
.
totientA :: UniqueFactorisation n => ArithmeticFunction n n Source #
Calculates the totient of a positive number n
, i.e.
the number of k
with 1 <= k <= n
and
,
in other words, the order of the group of units in gcd
n k == 1ℤ/(n)
.
jordanA :: UniqueFactorisation n => Word -> ArithmeticFunction n n Source #
Calculates the k-th Jordan function of an argument.
jordanA 1 = totientA
ramanujanA :: ArithmeticFunction Integer Integer Source #
Calculates the Ramanujan tau function
of a positive number n
, using formulas given here
moebiusA :: ArithmeticFunction n Moebius Source #
Calculates the Möbius function of an argument.
Represents three possible values of Möbius function.
Instances
runMoebius :: Num a => Moebius -> a Source #
Convert to any numeric type.
liouville :: (UniqueFactorisation n, Num a) => n -> a Source #
See liouvilleA
.
liouvilleA :: Num a => ArithmeticFunction n a Source #
Calculates the Liouville function of an argument.
Additive functions
additive :: Num a => (Prime n -> Word -> a) -> ArithmeticFunction n a Source #
Create an additive function from the function on prime's powers. See examples below.
smallOmega :: (UniqueFactorisation n, Num a) => n -> a Source #
See smallOmegaA
.
smallOmegaA :: Num a => ArithmeticFunction n a Source #
Number of distinct prime factors.
smallOmegaA = additive (\_ _ -> 1)
bigOmegaA :: ArithmeticFunction n Word Source #
Number of prime factors, counted with multiplicity.
bigOmegaA = additive (\_ k -> k)
Misc
carmichael :: (UniqueFactorisation n, Integral n) => n -> n Source #
See carmichaelA
.
carmichaelA :: (UniqueFactorisation n, Integral n) => ArithmeticFunction n n Source #
Calculates the Carmichael function for a positive integer, that is,
the (smallest) exponent of the group of units in ℤ/(n)
.
expMangoldt :: UniqueFactorisation n => n -> n Source #
See expMangoldtA
.
expMangoldtA :: UniqueFactorisation n => ArithmeticFunction n n Source #
The exponent of von Mangoldt function. Use log expMangoldtA
to recover von Mangoldt function itself.
isNFreeA :: Word -> ArithmeticFunction n Bool Source #
Check if an integer is n
-free. An integer x
is n
-free if in its
factorisation into prime factors, no factor has an exponent larger than or
equal to n
.
:: Integral a | |
=> Word | Power |
-> [a] | Generated infinite list of |
For a given nonnegative integer power n
, generate all n
-free
numbers in ascending order, starting at 1
.
When n
is 0
or 1
, the resulting list is [1]
.
:: Integral a | |
=> Word | Power |
-> a | Starting number in the block. |
-> Word | Maximum length of the block to be generated. |
-> [a] | Generated list of |
Generate n
-free numbers in a block starting at a certain value.
The length of the list is determined by the value passed in as the third
argument. It will be lesser than or equal to this value.
This function should not be used with a negative lower bound. If it is, the result is undefined.
The block length cannot exceed maxBound :: Int
, this precondition is not
checked.
As with nFrees
, passing n = 0, 1
results in an empty list.