{-|
Module      : Numeric.NumberTheory
Copyright   : Copyright (c) 2018 Vanessa McHale

This module provides fast number theoretic functions.
-}

module Numeric.NumberTheory ( totient
                            , tau
                            , littleOmega
                            , isPerfect
                            , sumDivisors
                            , isPrime
                            , radical
                            , isSemiprime
                            ) where

import           Foreign.C
import           Numeric.Common

foreign import ccall unsafe totient_ats :: CInt -> CInt
foreign import ccall unsafe count_divisors_ats :: CInt -> CInt
foreign import ccall unsafe sum_divisors_ats :: CInt -> CInt
foreign import ccall unsafe little_omega_ats :: CInt -> CInt
foreign import ccall unsafe is_perfect_ats :: CInt -> CBool
foreign import ccall unsafe is_prime_ats :: CInt -> CBool
foreign import ccall unsafe is_semiprime_ats :: CInt -> CBool
foreign import ccall unsafe radical_ats :: CInt -> CInt

-- | Radical of an integer
--
-- \( \text{rad}(n) = \displaystyle\prod_{p | n} p \)
radical :: Int -> Int
radical :: Int -> Int
radical = (CInt -> CInt) -> Int -> Int
forall a b. (Integral a, Integral b) => (CInt -> CInt) -> a -> b
conjugate CInt -> CInt
radical_ats

-- | \( O(\sqrt(n)) \)
isPrime :: Int -> Bool
isPrime :: Int -> Bool
isPrime = (CInt -> CBool) -> Int -> Bool
forall a. Integral a => (CInt -> CBool) -> a -> Bool
asTest CInt -> CBool
is_prime_ats

-- | @since 0.6.5.0
isSemiprime :: Int -> Bool
isSemiprime :: Int -> Bool
isSemiprime = (CInt -> CBool) -> Int -> Bool
forall a. Integral a => (CInt -> CBool) -> a -> Bool
asTest CInt -> CBool
is_semiprime_ats

-- | See [here](http://mathworld.wolfram.com/PerfectNumber.html)
isPerfect :: Int -> Bool
isPerfect :: Int -> Bool
isPerfect = (CInt -> CBool) -> Int -> Bool
forall a. Integral a => (CInt -> CBool) -> a -> Bool
asTest CInt -> CBool
is_perfect_ats

-- | Sum of proper divisors. May overflow.
sumDivisors :: Int -> Int
sumDivisors :: Int -> Int
sumDivisors = (CInt -> CInt) -> Int -> Int
forall a b. (Integral a, Integral b) => (CInt -> CInt) -> a -> b
conjugate CInt -> CInt
sum_divisors_ats

-- | Number of distinct prime factors
littleOmega :: Int -> Int
littleOmega :: Int -> Int
littleOmega = (CInt -> CInt) -> Int -> Int
forall a b. (Integral a, Integral b) => (CInt -> CInt) -> a -> b
conjugate CInt -> CInt
little_omega_ats

-- | Number of distinct divisors.
tau :: Int -> Int
tau :: Int -> Int
tau = (CInt -> CInt) -> Int -> Int
forall a b. (Integral a, Integral b) => (CInt -> CInt) -> a -> b
conjugate CInt -> CInt
count_divisors_ats

-- | Euler totient function.
totient :: Int -> Int
totient :: Int -> Int
totient = (CInt -> CInt) -> Int -> Int
forall a b. (Integral a, Integral b) => (CInt -> CInt) -> a -> b
conjugate CInt -> CInt
totient_ats