arithmoi-0.9.0.0: Efficient basic number-theoretic functions.

Copyright(c) 2016 Andrew Lelechenko
LicenseMIT
MaintainerAndrew Lelechenko <andrew.lelechenko@gmail.com>
Safe HaskellNone
LanguageHaskell2010

Math.NumberTheory.ArithmeticFunctions

Contents

Description

This module provides an interface for defining and manipulating arithmetic functions. It also defines several most widespreaded arithmetic functions.

Synopsis

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).

Constructors

ArithmeticFunction :: Monoid m => (Prime n -> Word -> m) -> (m -> a) -> ArithmeticFunction n a 
Instances
Functor (ArithmeticFunction n) Source # 
Instance details

Defined in Math.NumberTheory.ArithmeticFunctions.Class

Methods

fmap :: (a -> b) -> ArithmeticFunction n a -> ArithmeticFunction n b #

(<$) :: a -> ArithmeticFunction n b -> ArithmeticFunction n a #

Applicative (ArithmeticFunction n) Source # 
Instance details

Defined in Math.NumberTheory.ArithmeticFunctions.Class

Floating a => Floating (ArithmeticFunction n a) Source # 
Instance details

Defined in Math.NumberTheory.ArithmeticFunctions.Class

Fractional a => Fractional (ArithmeticFunction n a) Source # 
Instance details

Defined in Math.NumberTheory.ArithmeticFunctions.Class

Num a => Num (ArithmeticFunction n a) Source #

Factorisation is expensive, so it is better to avoid doing it twice. Write 'runFunction (f + g) n' instead of 'runFunction f n + runFunction g n'.

Instance details

Defined in Math.NumberTheory.ArithmeticFunctions.Class

Semigroup a => Semigroup (ArithmeticFunction n a) Source # 
Instance details

Defined in Math.NumberTheory.ArithmeticFunctions.Class

Monoid a => Monoid (ArithmeticFunction n a) Source # 
Instance details

Defined in Math.NumberTheory.ArithmeticFunctions.Class

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.

divisorsListA :: UniqueFactorisation n => ArithmeticFunction n [n] Source #

The unsorted list of all (positive) divisors of an argument, produced in lazy fashion.

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]

tau :: (UniqueFactorisation n, Num a) => n -> a Source #

See tauA.

tauA :: Num a => ArithmeticFunction n a Source #

The number of (positive) divisors of an argument.

tauA = multiplicative (\_ k -> k + 1)

sigma :: (UniqueFactorisation n, Integral n) => Word -> n -> n Source #

See sigmaA.

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

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 gcd n k == 1, in other words, the order of the group of units in ℤ/(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.

data Moebius Source #

Represents three possible values of Möbius function.

Instances
Eq Moebius Source # 
Instance details

Defined in Math.NumberTheory.ArithmeticFunctions.Moebius

Methods

(==) :: Moebius -> Moebius -> Bool #

(/=) :: Moebius -> Moebius -> Bool #

Ord Moebius Source # 
Instance details

Defined in Math.NumberTheory.ArithmeticFunctions.Moebius

Show Moebius Source # 
Instance details

Defined in Math.NumberTheory.ArithmeticFunctions.Moebius

Semigroup Moebius Source # 
Instance details

Defined in Math.NumberTheory.ArithmeticFunctions.Moebius

Monoid Moebius Source # 
Instance details

Defined in Math.NumberTheory.ArithmeticFunctions.Moebius

Unbox Moebius Source # 
Instance details

Defined in Math.NumberTheory.ArithmeticFunctions.Moebius

Vector Vector Moebius Source # 
Instance details

Defined in Math.NumberTheory.ArithmeticFunctions.Moebius

MVector MVector Moebius Source # 
Instance details

Defined in Math.NumberTheory.ArithmeticFunctions.Moebius

newtype Vector Moebius Source # 
Instance details

Defined in Math.NumberTheory.ArithmeticFunctions.Moebius

newtype MVector s Moebius Source # 
Instance details

Defined in Math.NumberTheory.ArithmeticFunctions.Moebius

runMoebius :: Num a => Moebius -> a Source #

Convert to any numeric type.

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.

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

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).

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.

nFrees Source #

Arguments

:: Integral a 
=> Word

Power n to be used to generate n-free numbers.

-> [a]

Generated infinite list of n-free numbers.

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].

nFreesBlock Source #

Arguments

:: Integral a 
=> Word

Power n to be used to generate n-free numbers.

-> a

Starting number in the block.

-> Word

Maximum length of the block to be generated.

-> [a]

Generated list of n-free numbers.

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.