arithmoi-0.5.0.0: Efficient basic number-theoretic functions.

Copyright(c) 2016 Andrew Lelechenko
LicenseMIT
MaintainerAndrew Lelechenko <andrew.lelechenko@gmail.com>
StabilityProvisional
PortabilityNon-portable (GHC extensions)
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 # 

Methods

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

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

Applicative (ArithmeticFunction n) Source # 
Floating a => Floating (ArithmeticFunction n a) Source # 
Fractional a => Fractional (ArithmeticFunction n a) Source # 
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'.

Semigroup a => Semigroup (ArithmeticFunction n a) Source # 
Monoid a => Monoid (ArithmeticFunction n a) Source # 

runFunction :: UniqueFactorisation n => ArithmeticFunction n a -> n -> a Source #

Convert to function. The value on 0 is undefined.

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.

divisors :: (UniqueFactorisation n, Num n, Ord n) => n -> Set n Source #

divisorsA :: forall n. (UniqueFactorisation n, Num n, Ord n) => ArithmeticFunction n (Set n) Source #

The set of all (positive) divisors of an argument.

divisorsSmallA :: forall n. Prime n ~ Prime Int => ArithmeticFunction n IntSet Source #

Same as divisors, but with better performance on cost of type restriction.

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

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

The number of (positive) divisors of an argument.

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

sigmaA :: forall n. (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 :: forall n. (UniqueFactorisation n, Integral 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 :: forall n. (UniqueFactorisation n, Integral n) => Word -> ArithmeticFunction n n Source #

Calculates the k-th Jordan function of an argument.

jordanA 1 = totientA

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

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

Calculates the Moebius function of an argument.

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 :: forall n. (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 :: forall n. (UniqueFactorisation n, Num n) => ArithmeticFunction n n Source #

The exponent of von Mangoldt function. Use log expMangoldtA to recover von Mangoldt function itself.