-- |-- Module: Math.NumberTheory.ArithmeticFunctions.Standard-- Copyright: (c) 2016 Andrew Lelechenko-- Licence: MIT-- Maintainer: Andrew Lelechenko <andrew.lelechenko@gmail.com>---- Textbook arithmetic functions.--{-# LANGUAGE ScopedTypeVariables #-}moduleMath.NumberTheory.ArithmeticFunctions.Standard(-- * List divisorsdivisors ,divisorsA ,divisorsList ,divisorsListA ,divisorsSmall ,divisorsSmallA ,divisorsTo ,divisorsToA -- * Multiplicative functions,multiplicative ,divisorCount ,tau ,tauA ,sigma ,sigmaA ,totient ,totientA ,jordan ,jordanA ,ramanujan ,ramanujanA ,moebius ,moebiusA ,Moebius (..),runMoebius ,liouville ,liouvilleA -- * Additive functions,additive ,smallOmega ,smallOmegaA ,bigOmega ,bigOmegaA -- * Misc,carmichael ,carmichaelA ,expMangoldt ,expMangoldtA ,isNFree ,isNFreeA ,nFrees ,nFreesBlock )whereimportData.CoerceimportData.Euclidean(GcdDomain(divide))importData.IntSet(IntSet)importqualifiedData.IntSetasISimportData.MaybeimportData.Set(Set)importqualifiedData.SetasSimportData.SemigroupimportMath.NumberTheory.ArithmeticFunctions.Class importMath.NumberTheory.ArithmeticFunctions.Moebius importMath.NumberTheory.ArithmeticFunctions.NFreedom (nFrees ,nFreesBlock )importMath.NumberTheory.Primes importMath.NumberTheory.Utils.FromIntegral importNumeric.Natural-- | Create a multiplicative function from the function on prime's powers. See examples below.multiplicative ::Numa =>(Prime n ->Word->a )->ArithmeticFunction n a multiplicative :: forall a n.
Num a =>
(Prime n -> Word -> a) -> ArithmeticFunction n a
multiplicative Prime n -> Word -> a
f =(Prime n -> Word -> Product a)
-> (Product a -> a) -> ArithmeticFunction n a
forall m n a.
Monoid m =>
(Prime n -> Word -> m) -> (m -> a) -> ArithmeticFunction n a
ArithmeticFunction ((a -> Product a
forall a. a -> Product a
Product(a -> Product a) -> (Word -> a) -> Word -> Product a
forall b c a. (b -> c) -> (a -> b) -> a -> c
.)((Word -> a) -> Word -> Product a)
-> (Prime n -> Word -> a) -> Prime n -> Word -> Product a
forall b c a. (b -> c) -> (a -> b) -> a -> c
.Prime n -> Word -> a
f )Product a -> a
forall a. Product a -> a
getProduct-- | See 'divisorsA'.divisors ::(UniqueFactorisation n ,Ordn )=>n ->Setn divisors :: forall n. (UniqueFactorisation n, Ord n) => n -> Set n
divisors =ArithmeticFunction n (Set n) -> n -> Set n
forall n a.
UniqueFactorisation n =>
ArithmeticFunction n a -> n -> a
runFunction ArithmeticFunction n (Set n)
forall n. (Ord n, Num n) => ArithmeticFunction n (Set n)
divisorsA {-# SPECIALIZEdivisors ::Natural->SetNatural#-}{-# SPECIALIZEdivisors ::Integer->SetInteger#-}-- | The set of all (positive) divisors of an argument.divisorsA ::(Ordn ,Numn )=>ArithmeticFunction n (Setn )divisorsA :: forall n. (Ord n, Num n) => ArithmeticFunction n (Set n)
divisorsA =(Prime n -> Word -> SetProduct n)
-> (SetProduct n -> Set n) -> ArithmeticFunction n (Set n)
forall m n a.
Monoid m =>
(Prime n -> Word -> m) -> (m -> a) -> ArithmeticFunction n a
ArithmeticFunction (\Prime n
p ->Set n -> SetProduct n
forall a. Set a -> SetProduct a
SetProduct (Set n -> SetProduct n) -> (Word -> Set n) -> Word -> SetProduct n
forall b c a. (b -> c) -> (a -> b) -> a -> c
.n -> Word -> Set n
forall n. Num n => n -> Word -> Set n
divisorsHelper (Prime n -> n
forall a. Prime a -> a
unPrime Prime n
p ))(n -> Set n -> Set n
forall a. Ord a => a -> Set a -> Set a
S.insertn
1(Set n -> Set n)
-> (SetProduct n -> Set n) -> SetProduct n -> Set n
forall b c a. (b -> c) -> (a -> b) -> a -> c
.SetProduct n -> Set n
forall a. SetProduct a -> Set a
getSetProduct )divisorsHelper ::Numn =>n ->Word->Setn divisorsHelper :: forall n. Num n => n -> Word -> Set n
divisorsHelper n
_Word
0=Set n
forall a. Set a
S.emptydivisorsHelper n
p Word
1=n -> Set n
forall a. a -> Set a
S.singletonn
p divisorsHelper n
p Word
a =[n] -> Set n
forall a. [a] -> Set a
S.fromDistinctAscList([n] -> Set n) -> [n] -> Set n
forall a b. (a -> b) -> a -> b
$n
p n -> [n] -> [n]
forall a. a -> [a] -> [a]
:n
p n -> n -> n
forall a. Num a => a -> a -> a
*n
p n -> [n] -> [n]
forall a. a -> [a] -> [a]
:(Int -> n) -> [Int] -> [n]
forall a b. (a -> b) -> [a] -> [b]
map(n
p n -> Int -> n
forall a b. (Num a, Integral b) => a -> b -> a
^)[Int
3..Word -> Int
wordToInt Word
a ]{-# INLINEdivisorsHelper #-}-- | See 'divisorsListA'.divisorsList ::UniqueFactorisation n =>n ->[n ]divisorsList :: forall n. UniqueFactorisation n => n -> [n]
divisorsList =ArithmeticFunction n [n] -> n -> [n]
forall n a.
UniqueFactorisation n =>
ArithmeticFunction n a -> n -> a
runFunction ArithmeticFunction n [n]
forall n. Num n => ArithmeticFunction n [n]
divisorsListA -- | The unsorted list of all (positive) divisors of an argument, produced in lazy fashion.divisorsListA ::Numn =>ArithmeticFunction n [n ]divisorsListA :: forall n. Num n => ArithmeticFunction n [n]
divisorsListA =(Prime n -> Word -> ListProduct n)
-> (ListProduct n -> [n]) -> ArithmeticFunction n [n]
forall m n a.
Monoid m =>
(Prime n -> Word -> m) -> (m -> a) -> ArithmeticFunction n a
ArithmeticFunction (\Prime n
p ->[n] -> ListProduct n
forall a. [a] -> ListProduct a
ListProduct ([n] -> ListProduct n) -> (Word -> [n]) -> Word -> ListProduct n
forall b c a. (b -> c) -> (a -> b) -> a -> c
.n -> Word -> [n]
forall n. Num n => n -> Word -> [n]
divisorsListHelper (Prime n -> n
forall a. Prime a -> a
unPrime Prime n
p ))((n
1n -> [n] -> [n]
forall a. a -> [a] -> [a]
:)([n] -> [n]) -> (ListProduct n -> [n]) -> ListProduct n -> [n]
forall b c a. (b -> c) -> (a -> b) -> a -> c
.ListProduct n -> [n]
forall a. ListProduct a -> [a]
getListProduct )divisorsListHelper ::Numn =>n ->Word->[n ]divisorsListHelper :: forall n. Num n => n -> Word -> [n]
divisorsListHelper n
_Word
0=[]divisorsListHelper n
p Word
1=[n
p ]divisorsListHelper n
p Word
a =n
p n -> [n] -> [n]
forall a. a -> [a] -> [a]
:n
p n -> n -> n
forall a. Num a => a -> a -> a
*n
p n -> [n] -> [n]
forall a. a -> [a] -> [a]
:(Int -> n) -> [Int] -> [n]
forall a b. (a -> b) -> [a] -> [b]
map(n
p n -> Int -> n
forall a b. (Num a, Integral b) => a -> b -> a
^)[Int
3..Word -> Int
wordToInt Word
a ]{-# INLINEdivisorsListHelper #-}-- | See 'divisorsSmallA'.divisorsSmall ::Int->IntSet=ArithmeticFunction Int IntSet -> Int -> IntSet
forall n a.
UniqueFactorisation n =>
ArithmeticFunction n a -> n -> a
runFunction ArithmeticFunction Int IntSet
divisorsSmallA -- | Same as 'divisors', but with better performance on cost of type restriction.divisorsSmallA ::ArithmeticFunction IntIntSet=(Prime Int -> Word -> IntSetProduct)
-> (IntSetProduct -> IntSet) -> ArithmeticFunction Int IntSet
forall m n a.
Monoid m =>
(Prime n -> Word -> m) -> (m -> a) -> ArithmeticFunction n a
ArithmeticFunction (\Prime Int
p ->IntSet -> IntSetProduct
IntSetProduct (IntSet -> IntSetProduct)
-> (Word -> IntSet) -> Word -> IntSetProduct
forall b c a. (b -> c) -> (a -> b) -> a -> c
.Int -> Word -> IntSet
divisorsHelperSmall (Prime Int -> Int
forall a. Prime a -> a
unPrime Prime Int
p ))(Int -> IntSet -> IntSet
IS.insertInt
1(IntSet -> IntSet)
-> (IntSetProduct -> IntSet) -> IntSetProduct -> IntSet
forall b c a. (b -> c) -> (a -> b) -> a -> c
.IntSetProduct -> IntSet
getIntSetProduct )divisorsHelperSmall ::Int->Word->IntSetdivisorsHelperSmall :: Int -> Word -> IntSet
divisorsHelperSmall Int
_Word
0=IntSet
IS.emptydivisorsHelperSmall Int
p Word
1=Int -> IntSet
IS.singletonInt
p divisorsHelperSmall Int
p Word
a =[Int] -> IntSet
IS.fromDistinctAscList([Int] -> IntSet) -> [Int] -> IntSet
forall a b. (a -> b) -> a -> b
$Int
p Int -> [Int] -> [Int]
forall a. a -> [a] -> [a]
:Int
p Int -> Int -> Int
forall a. Num a => a -> a -> a
*Int
p Int -> [Int] -> [Int]
forall a. a -> [a] -> [a]
:(Int -> Int) -> [Int] -> [Int]
forall a b. (a -> b) -> [a] -> [b]
map(Int
p Int -> Int -> Int
forall a b. (Num a, Integral b) => a -> b -> a
^)[Int
3..Word -> Int
wordToInt Word
a ]{-# INLINEdivisorsHelperSmall #-}-- | See 'divisorsToA'.divisorsTo ::(UniqueFactorisation n ,Integraln )=>n ->n ->Setn divisorsTo :: forall n. (UniqueFactorisation n, Integral n) => n -> n -> Set n
divisorsTo n
to =ArithmeticFunction n (Set n) -> n -> Set n
forall n a.
UniqueFactorisation n =>
ArithmeticFunction n a -> n -> a
runFunction (n -> ArithmeticFunction n (Set n)
forall n.
(UniqueFactorisation n, Integral n) =>
n -> ArithmeticFunction n (Set n)
divisorsToA n
to )-- | The set of all (positive) divisors up to an inclusive bound.divisorsToA ::(UniqueFactorisation n ,Integraln )=>n ->ArithmeticFunction n (Setn )divisorsToA :: forall n.
(UniqueFactorisation n, Integral n) =>
n -> ArithmeticFunction n (Set n)
divisorsToA n
to =(Prime n -> Word -> BoundedSetProduct n)
-> (BoundedSetProduct n -> Set n) -> ArithmeticFunction n (Set n)
forall m n a.
Monoid m =>
(Prime n -> Word -> m) -> (m -> a) -> ArithmeticFunction n a
ArithmeticFunction Prime n -> Word -> BoundedSetProduct n
forall {a}.
(Ord a, Num a) =>
Prime a -> Word -> BoundedSetProduct a
f BoundedSetProduct n -> Set n
unwrap wheref :: Prime a -> Word -> BoundedSetProduct a
f Prime a
p Word
k =(a -> Set a) -> BoundedSetProduct a
forall a. (a -> Set a) -> BoundedSetProduct a
BoundedSetProduct (\a
bound ->a -> a -> Word -> Set a
forall n. (Ord n, Num n) => n -> n -> Word -> Set n
divisorsToHelper a
bound (Prime a -> a
forall a. Prime a -> a
unPrime Prime a
p )Word
k )unwrap :: BoundedSetProduct n -> Set n
unwrap (BoundedSetProduct n -> Set n
res )=ifn
1n -> n -> Bool
forall a. Ord a => a -> a -> Bool
<=n
to thenn -> Set n -> Set n
forall a. Ord a => a -> Set a -> Set a
S.insertn
1(n -> Set n
res n
to )elsen -> Set n
res n
to -- | Generate at most @a@ powers of @p@ up to an inclusive bound @b@.divisorsToHelper ::(Ordn ,Numn )=>n ->n ->Word->Setn divisorsToHelper :: forall n. (Ord n, Num n) => n -> n -> Word -> Set n
divisorsToHelper n
_n
_Word
0=Set n
forall a. Set a
S.emptydivisorsToHelper n
b n
p Word
1=ifn
p n -> n -> Bool
forall a. Ord a => a -> a -> Bool
<=n
b thenn -> Set n
forall a. a -> Set a
S.singletonn
p elseSet n
forall a. Set a
S.emptydivisorsToHelper n
b n
p Word
a =[n] -> Set n
forall a. [a] -> Set a
S.fromDistinctAscList([n] -> Set n) -> [n] -> Set n
forall a b. (a -> b) -> a -> b
$Int -> [n] -> [n]
forall a. Int -> [a] -> [a]
take(Word -> Int
wordToInt Word
a )([n] -> [n]) -> [n] -> [n]
forall a b. (a -> b) -> a -> b
$(n -> Bool) -> [n] -> [n]
forall a. (a -> Bool) -> [a] -> [a]
takeWhile(n -> n -> Bool
forall a. Ord a => a -> a -> Bool
<=n
b )([n] -> [n]) -> [n] -> [n]
forall a b. (a -> b) -> a -> b
$(n -> n) -> n -> [n]
forall a. (a -> a) -> a -> [a]
iterate(n
p n -> n -> n
forall a. Num a => a -> a -> a
*)n
p {-# INLINEdivisorsToHelper #-}-- | Synonym for 'tau'.---- >>> map divisorCount [1..10]-- [1,2,2,3,2,4,2,4,3,4]divisorCount ::(UniqueFactorisation n ,Numa )=>n ->a divisorCount :: forall n a. (UniqueFactorisation n, Num a) => n -> a
divisorCount =n -> a
forall n a. (UniqueFactorisation n, Num a) => n -> a
tau -- | See 'tauA'.tau ::(UniqueFactorisation n ,Numa )=>n ->a tau :: forall n a. (UniqueFactorisation n, Num a) => n -> a
tau =ArithmeticFunction n a -> n -> a
forall n a.
UniqueFactorisation n =>
ArithmeticFunction n a -> n -> a
runFunction ArithmeticFunction n a
forall a n. Num a => ArithmeticFunction n a
tauA -- | The number of (positive) divisors of an argument.---- > tauA = multiplicative (\_ k -> k + 1)tauA ::Numa =>ArithmeticFunction n a tauA :: forall a n. Num a => ArithmeticFunction n a
tauA =(Prime n -> Word -> a) -> ArithmeticFunction n a
forall a n.
Num a =>
(Prime n -> Word -> a) -> ArithmeticFunction n a
multiplicative ((Prime n -> Word -> a) -> ArithmeticFunction n a)
-> (Prime n -> Word -> a) -> ArithmeticFunction n a
forall a b. (a -> b) -> a -> b
$(Word -> a) -> Prime n -> Word -> a
forall a b. a -> b -> a
const(Word -> a
forall a b. (Integral a, Num b) => a -> b
fromIntegral(Word -> a) -> (Word -> Word) -> Word -> a
forall b c a. (b -> c) -> (a -> b) -> a -> c
.Word -> Word
forall a. Enum a => a -> a
succ)-- | See 'sigmaA'.sigma ::(UniqueFactorisation n ,Integraln ,Numa ,GcdDomaina )=>Word->n ->a sigma :: forall n a.
(UniqueFactorisation n, Integral n, Num a, GcdDomain a) =>
Word -> n -> a
sigma =ArithmeticFunction n a -> n -> a
forall n a.
UniqueFactorisation n =>
ArithmeticFunction n a -> n -> a
runFunction (ArithmeticFunction n a -> n -> a)
-> (Word -> ArithmeticFunction n a) -> Word -> n -> a
forall b c a. (b -> c) -> (a -> b) -> a -> c
.Word -> ArithmeticFunction n a
forall n a.
(Integral n, Num a, GcdDomain a) =>
Word -> ArithmeticFunction n a
sigmaA {-# INLINABLEsigma #-}-- | The sum of the @k@-th powers of (positive) divisors of an argument.---- > sigmaA = multiplicative (\p k -> sum $ map (p ^) [0..k])-- > sigmaA 0 = tauAsigmaA ::(Integraln ,Numa ,GcdDomaina )=>Word->ArithmeticFunction n a sigmaA :: forall n a.
(Integral n, Num a, GcdDomain a) =>
Word -> ArithmeticFunction n a
sigmaA Word
0=ArithmeticFunction n a
forall a n. Num a => ArithmeticFunction n a
tauA sigmaA Word
1=(Prime n -> Word -> a) -> ArithmeticFunction n a
forall a n.
Num a =>
(Prime n -> Word -> a) -> ArithmeticFunction n a
multiplicative ((Prime n -> Word -> a) -> ArithmeticFunction n a)
-> (Prime n -> Word -> a) -> ArithmeticFunction n a
forall a b. (a -> b) -> a -> b
$a -> Word -> a
forall a. (Num a, GcdDomain a) => a -> Word -> a
sigmaHelper (a -> Word -> a) -> (Prime n -> a) -> Prime n -> Word -> a
forall b c a. (b -> c) -> (a -> b) -> a -> c
.n -> a
forall a b. (Integral a, Num b) => a -> b
fromIntegral' (n -> a) -> (Prime n -> n) -> Prime n -> a
forall b c a. (b -> c) -> (a -> b) -> a -> c
.Prime n -> n
forall a. Prime a -> a
unPrime sigmaA Word
a =(Prime n -> Word -> a) -> ArithmeticFunction n a
forall a n.
Num a =>
(Prime n -> Word -> a) -> ArithmeticFunction n a
multiplicative ((Prime n -> Word -> a) -> ArithmeticFunction n a)
-> (Prime n -> Word -> a) -> ArithmeticFunction n a
forall a b. (a -> b) -> a -> b
$a -> Word -> a
forall a. (Num a, GcdDomain a) => a -> Word -> a
sigmaHelper (a -> Word -> a) -> (Prime n -> a) -> Prime n -> Word -> a
forall b c a. (b -> c) -> (a -> b) -> a -> c
.(a -> Int -> a
forall a b. (Num a, Integral b) => a -> b -> a
^Word -> Int
wordToInt Word
a )(a -> a) -> (Prime n -> a) -> Prime n -> a
forall b c a. (b -> c) -> (a -> b) -> a -> c
.n -> a
forall a b. (Integral a, Num b) => a -> b
fromIntegral' (n -> a) -> (Prime n -> n) -> Prime n -> a
forall b c a. (b -> c) -> (a -> b) -> a -> c
.Prime n -> n
forall a. Prime a -> a
unPrime {-# INLINABLEsigmaA #-}sigmaHelper ::(Numa ,GcdDomaina )=>a ->Word->a sigmaHelper :: forall a. (Num a, GcdDomain a) => a -> Word -> a
sigmaHelper a
pa Word
1=a
pa a -> a -> a
forall a. Num a => a -> a -> a
+a
1sigmaHelper a
pa Word
2=a
pa a -> a -> a
forall a. Num a => a -> a -> a
*a
pa a -> a -> a
forall a. Num a => a -> a -> a
+a
pa a -> a -> a
forall a. Num a => a -> a -> a
+a
1sigmaHelper a
pa Word
k =Maybe a -> a
forall a. HasCallStack => Maybe a -> a
fromJust((a
pa a -> Int -> a
forall a b. (Num a, Integral b) => a -> b -> a
^Word -> Int
wordToInt (Word
k Word -> Word -> Word
forall a. Num a => a -> a -> a
+Word
1)a -> a -> a
forall a. Num a => a -> a -> a
-a
1)a -> a -> Maybe a
forall a. GcdDomain a => a -> a -> Maybe a
`divide`(a
pa a -> a -> a
forall a. Num a => a -> a -> a
-a
1)){-# INLINEsigmaHelper #-}-- | See 'totientA'.totient ::UniqueFactorisation n =>n ->n totient :: forall n. UniqueFactorisation n => n -> n
totient =ArithmeticFunction n n -> n -> n
forall n a.
UniqueFactorisation n =>
ArithmeticFunction n a -> n -> a
runFunction ArithmeticFunction n n
forall n. Num n => ArithmeticFunction n n
totientA {-# INLINABLEtotient #-}-- | 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)@.totientA ::Numn =>ArithmeticFunction n n totientA :: forall n. Num n => ArithmeticFunction n n
totientA =(Prime n -> Word -> n) -> ArithmeticFunction n n
forall a n.
Num a =>
(Prime n -> Word -> a) -> ArithmeticFunction n a
multiplicative ((Prime n -> Word -> n) -> ArithmeticFunction n n)
-> (Prime n -> Word -> n) -> ArithmeticFunction n n
forall a b. (a -> b) -> a -> b
$n -> Word -> n
forall n. Num n => n -> Word -> n
jordanHelper (n -> Word -> n) -> (Prime n -> n) -> Prime n -> Word -> n
forall b c a. (b -> c) -> (a -> b) -> a -> c
.Prime n -> n
forall a. Prime a -> a
unPrime {-# INLINABLEtotientA #-}-- | See 'jordanA'.jordan ::UniqueFactorisation n =>Word->n ->n jordan :: forall n. UniqueFactorisation n => Word -> n -> n
jordan =ArithmeticFunction n n -> n -> n
forall n a.
UniqueFactorisation n =>
ArithmeticFunction n a -> n -> a
runFunction (ArithmeticFunction n n -> n -> n)
-> (Word -> ArithmeticFunction n n) -> Word -> n -> n
forall b c a. (b -> c) -> (a -> b) -> a -> c
.Word -> ArithmeticFunction n n
forall n. Num n => Word -> ArithmeticFunction n n
jordanA -- | Calculates the k-th Jordan function of an argument.---- > jordanA 1 = totientAjordanA ::Numn =>Word->ArithmeticFunction n n jordanA :: forall n. Num n => Word -> ArithmeticFunction n n
jordanA Word
0=(Prime n -> Word -> n) -> ArithmeticFunction n n
forall a n.
Num a =>
(Prime n -> Word -> a) -> ArithmeticFunction n a
multiplicative ((Prime n -> Word -> n) -> ArithmeticFunction n n)
-> (Prime n -> Word -> n) -> ArithmeticFunction n n
forall a b. (a -> b) -> a -> b
$\Prime n
_Word
_->n
0jordanA Word
1=ArithmeticFunction n n
forall n. Num n => ArithmeticFunction n n
totientA jordanA Word
a =(Prime n -> Word -> n) -> ArithmeticFunction n n
forall a n.
Num a =>
(Prime n -> Word -> a) -> ArithmeticFunction n a
multiplicative ((Prime n -> Word -> n) -> ArithmeticFunction n n)
-> (Prime n -> Word -> n) -> ArithmeticFunction n n
forall a b. (a -> b) -> a -> b
$n -> Word -> n
forall n. Num n => n -> Word -> n
jordanHelper (n -> Word -> n) -> (Prime n -> n) -> Prime n -> Word -> n
forall b c a. (b -> c) -> (a -> b) -> a -> c
.(n -> Int -> n
forall a b. (Num a, Integral b) => a -> b -> a
^Word -> Int
wordToInt Word
a )(n -> n) -> (Prime n -> n) -> Prime n -> n
forall b c a. (b -> c) -> (a -> b) -> a -> c
.Prime n -> n
forall a. Prime a -> a
unPrime jordanHelper ::Numn =>n ->Word->n jordanHelper :: forall n. Num n => n -> Word -> n
jordanHelper n
pa Word
1=n
pa n -> n -> n
forall a. Num a => a -> a -> a
-n
1jordanHelper n
pa Word
2=(n
pa n -> n -> n
forall a. Num a => a -> a -> a
-n
1)n -> n -> n
forall a. Num a => a -> a -> a
*n
pa jordanHelper n
pa Word
k =(n
pa n -> n -> n
forall a. Num a => a -> a -> a
-n
1)n -> n -> n
forall a. Num a => a -> a -> a
*n
pa n -> Int -> n
forall a b. (Num a, Integral b) => a -> b -> a
^Word -> Int
wordToInt (Word
k Word -> Word -> Word
forall a. Num a => a -> a -> a
-Word
1){-# INLINEjordanHelper #-}-- | See 'ramanujanA'.ramanujan ::Integer->Integerramanujan :: Integer -> Integer
ramanujan =ArithmeticFunction Integer Integer -> Integer -> Integer
forall n a.
UniqueFactorisation n =>
ArithmeticFunction n a -> n -> a
runFunction ArithmeticFunction Integer Integer
ramanujanA -- | Calculates the <https://en.wikipedia.org/wiki/Ramanujan_tau_function Ramanujan tau function>-- of a positive number @n@, using formulas given <http://www.numbertheory.org/php/tau.html here>ramanujanA ::ArithmeticFunction IntegerIntegerramanujanA :: ArithmeticFunction Integer Integer
ramanujanA =(Prime Integer -> Word -> Integer)
-> ArithmeticFunction Integer Integer
forall a n.
Num a =>
(Prime n -> Word -> a) -> ArithmeticFunction n a
multiplicative ((Prime Integer -> Word -> Integer)
-> ArithmeticFunction Integer Integer)
-> (Prime Integer -> Word -> Integer)
-> ArithmeticFunction Integer Integer
forall a b. (a -> b) -> a -> b
$Integer -> Word -> Integer
ramanujanHelper (Integer -> Word -> Integer)
-> (Prime Integer -> Integer) -> Prime Integer -> Word -> Integer
forall b c a. (b -> c) -> (a -> b) -> a -> c
.Prime Integer -> Integer
forall a. Prime a -> a
unPrime ramanujanHelper ::Integer->Word->IntegerramanujanHelper :: Integer -> Word -> Integer
ramanujanHelper Integer
_Word
0=Integer
1ramanujanHelper Integer
2Word
1=-Integer
24ramanujanHelper Integer
p Word
1=(Integer
65Integer -> Integer -> Integer
forall a. Num a => a -> a -> a
*Integer -> Word -> Integer
forall a. (Num a, GcdDomain a) => a -> Word -> a
sigmaHelper (Integer
p Integer -> Int -> Integer
forall a b. (Num a, Integral b) => a -> b -> a
^(Int
11::Int))Word
1Integer -> Integer -> Integer
forall a. Num a => a -> a -> a
+Integer
691Integer -> Integer -> Integer
forall a. Num a => a -> a -> a
*Integer -> Word -> Integer
forall a. (Num a, GcdDomain a) => a -> Word -> a
sigmaHelper (Integer
p Integer -> Int -> Integer
forall a b. (Num a, Integral b) => a -> b -> a
^(Int
5::Int))Word
1Integer -> Integer -> Integer
forall a. Num a => a -> a -> a
-Integer
691Integer -> Integer -> Integer
forall a. Num a => a -> a -> a
*Integer
252Integer -> Integer -> Integer
forall a. Num a => a -> a -> a
*Integer
2Integer -> Integer -> Integer
forall a. Num a => a -> a -> a
*[Integer] -> Integer
forall a. Num a => [a] -> a
forall (t :: * -> *) a. (Foldable t, Num a) => t a -> a
sum[Word -> Integer -> Integer
forall n a.
(UniqueFactorisation n, Integral n, Num a, GcdDomain a) =>
Word -> n -> a
sigma Word
5Integer
k Integer -> Integer -> Integer
forall a. Num a => a -> a -> a
*Word -> Integer -> Integer
forall n a.
(UniqueFactorisation n, Integral n, Num a, GcdDomain a) =>
Word -> n -> a
sigma Word
5(Integer
p Integer -> Integer -> Integer
forall a. Num a => a -> a -> a
-Integer
k )|Integer
k <-[Integer
1..(Integer
p Integer -> Integer -> Integer
forall a. Integral a => a -> a -> a
`quot`Integer
2)]])Integer -> Integer -> Integer
forall a. Integral a => a -> a -> a
`quot`Integer
756ramanujanHelper Integer
p Word
k =[Integer] -> Integer
forall a. Num a => [a] -> a
forall (t :: * -> *) a. (Foldable t, Num a) => t a -> a
sum([Integer] -> Integer) -> [Integer] -> Integer
forall a b. (a -> b) -> a -> b
$(Integer -> Integer -> Integer -> Integer)
-> [Integer] -> [Integer] -> [Integer] -> [Integer]
forall a b c d. (a -> b -> c -> d) -> [a] -> [b] -> [c] -> [d]
zipWith3(\Integer
a Integer
b Integer
c ->Integer
a Integer -> Integer -> Integer
forall a. Num a => a -> a -> a
*Integer
b Integer -> Integer -> Integer
forall a. Num a => a -> a -> a
*Integer
c )[Integer]
paPowers [Integer]
tpPowers [Integer]
binomials wherepa :: Integer
pa =Integer
p Integer -> Int -> Integer
forall a b. (Num a, Integral b) => a -> b -> a
^(Int
11::Int)tp :: Integer
tp =Integer -> Word -> Integer
ramanujanHelper Integer
p Word
1paPowers :: [Integer]
paPowers =(Integer -> Integer) -> Integer -> [Integer]
forall a. (a -> a) -> a -> [a]
iterate(Integer -> Integer -> Integer
forall a. Num a => a -> a -> a
*(-Integer
pa ))Integer
1binomials :: [Integer]
binomials =(Integer -> Integer -> Integer)
-> Integer -> [Integer] -> [Integer]
forall b a. (b -> a -> b) -> b -> [a] -> [b]
scanl(\Integer
acc Integer
j ->Integer
acc Integer -> Integer -> Integer
forall a. Num a => a -> a -> a
*(Integer
k' Integer -> Integer -> Integer
forall a. Num a => a -> a -> a
-Integer
2Integer -> Integer -> Integer
forall a. Num a => a -> a -> a
*Integer
j )Integer -> Integer -> Integer
forall a. Num a => a -> a -> a
*(Integer
k' Integer -> Integer -> Integer
forall a. Num a => a -> a -> a
-Integer
2Integer -> Integer -> Integer
forall a. Num a => a -> a -> a
*Integer
j Integer -> Integer -> Integer
forall a. Num a => a -> a -> a
-Integer
1)Integer -> Integer -> Integer
forall a. Integral a => a -> a -> a
`quot`(Integer
k' Integer -> Integer -> Integer
forall a. Num a => a -> a -> a
-Integer
j )Integer -> Integer -> Integer
forall a. Integral a => a -> a -> a
`quot`(Integer
j Integer -> Integer -> Integer
forall a. Num a => a -> a -> a
+Integer
1))Integer
1[Integer
0..Integer
k' Integer -> Integer -> Integer
forall a. Integral a => a -> a -> a
`quot`Integer
2Integer -> Integer -> Integer
forall a. Num a => a -> a -> a
-Integer
1]k' :: Integer
k' =Word -> Integer
wordToInteger Word
k tpPowers :: [Integer]
tpPowers =[Integer] -> [Integer]
forall a. [a] -> [a]
reverse([Integer] -> [Integer]) -> [Integer] -> [Integer]
forall a b. (a -> b) -> a -> b
$Int -> [Integer] -> [Integer]
forall a. Int -> [a] -> [a]
take([Integer] -> Int
forall a. [a] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length[Integer]
binomials )([Integer] -> [Integer]) -> [Integer] -> [Integer]
forall a b. (a -> b) -> a -> b
$(Integer -> Integer) -> Integer -> [Integer]
forall a. (a -> a) -> a -> [a]
iterate(Integer -> Integer -> Integer
forall a. Num a => a -> a -> a
*Integer
tp Integer -> Int -> Integer
forall a b. (Num a, Integral b) => a -> b -> a
^(Int
2::Int))(ifWord -> Bool
forall a. Integral a => a -> Bool
evenWord
k thenInteger
1elseInteger
tp ){-# INLINEramanujanHelper #-}-- | See 'moebiusA'.moebius ::UniqueFactorisation n =>n ->Moebius moebius :: forall n. UniqueFactorisation n => n -> Moebius
moebius =ArithmeticFunction n Moebius -> n -> Moebius
forall n a.
UniqueFactorisation n =>
ArithmeticFunction n a -> n -> a
runFunction ArithmeticFunction n Moebius
forall n. ArithmeticFunction n Moebius
moebiusA -- | Calculates the Möbius function of an argument.moebiusA ::ArithmeticFunction n Moebius moebiusA :: forall n. ArithmeticFunction n Moebius
moebiusA =(Prime n -> Word -> Moebius)
-> (Moebius -> Moebius) -> ArithmeticFunction n Moebius
forall m n a.
Monoid m =>
(Prime n -> Word -> m) -> (m -> a) -> ArithmeticFunction n a
ArithmeticFunction ((Word -> Moebius) -> Prime n -> Word -> Moebius
forall a b. a -> b -> a
constWord -> Moebius
forall {a}. (Eq a, Num a) => a -> Moebius
f )Moebius -> Moebius
forall a. a -> a
idwheref :: a -> Moebius
f a
1=Moebius
MoebiusN f a
0=Moebius
MoebiusP f a
_=Moebius
MoebiusZ -- | See 'liouvilleA'.liouville ::(UniqueFactorisation n ,Numa )=>n ->a liouville :: forall n a. (UniqueFactorisation n, Num a) => n -> a
liouville =ArithmeticFunction n a -> n -> a
forall n a.
UniqueFactorisation n =>
ArithmeticFunction n a -> n -> a
runFunction ArithmeticFunction n a
forall a n. Num a => ArithmeticFunction n a
liouvilleA -- | Calculates the Liouville function of an argument.liouvilleA ::Numa =>ArithmeticFunction n a liouvilleA :: forall a n. Num a => ArithmeticFunction n a
liouvilleA =(Prime n -> Word -> Xor) -> (Xor -> a) -> ArithmeticFunction n a
forall m n a.
Monoid m =>
(Prime n -> Word -> m) -> (m -> a) -> ArithmeticFunction n a
ArithmeticFunction ((Word -> Xor) -> Prime n -> Word -> Xor
forall a b. a -> b -> a
const((Word -> Xor) -> Prime n -> Word -> Xor)
-> (Word -> Xor) -> Prime n -> Word -> Xor
forall a b. (a -> b) -> a -> b
$Bool -> Xor
Xor (Bool -> Xor) -> (Word -> Bool) -> Word -> Xor
forall b c a. (b -> c) -> (a -> b) -> a -> c
.Word -> Bool
forall a. Integral a => a -> Bool
odd)Xor -> a
forall a. Num a => Xor -> a
runXor -- | See 'carmichaelA'.carmichael ::(UniqueFactorisation n ,Integraln )=>n ->n carmichael :: forall n. (UniqueFactorisation n, Integral n) => n -> n
carmichael =ArithmeticFunction n n -> n -> n
forall n a.
UniqueFactorisation n =>
ArithmeticFunction n a -> n -> a
runFunction ArithmeticFunction n n
forall n. Integral n => ArithmeticFunction n n
carmichaelA {-# SPECIALIZEcarmichael ::Int->Int#-}{-# SPECIALIZEcarmichael ::Word->Word#-}{-# SPECIALIZEcarmichael ::Integer->Integer#-}{-# SPECIALIZEcarmichael ::Natural->Natural#-}-- | Calculates the Carmichael function for a positive integer, that is,-- the (smallest) exponent of the group of units in @ℤ/(n)@.carmichaelA ::Integraln =>ArithmeticFunction n n carmichaelA :: forall n. Integral n => ArithmeticFunction n n
carmichaelA =(Prime n -> Word -> LCM n)
-> (LCM n -> n) -> ArithmeticFunction n n
forall m n a.
Monoid m =>
(Prime n -> Word -> m) -> (m -> a) -> ArithmeticFunction n a
ArithmeticFunction (\Prime n
p ->n -> LCM n
forall a. a -> LCM a
LCM (n -> LCM n) -> (Word -> n) -> Word -> LCM n
forall b c a. (b -> c) -> (a -> b) -> a -> c
.n -> Word -> n
forall {a}. (Eq a, Num a) => a -> Word -> a
f (Prime n -> n
forall a. Prime a -> a
unPrime Prime n
p ))LCM n -> n
forall a. LCM a -> a
getLCM wheref :: a -> Word -> a
f a
2Word
1=a
1f a
2Word
2=a
2f a
2Word
k =a
2a -> Int -> a
forall a b. (Num a, Integral b) => a -> b -> a
^Word -> Int
wordToInt (Word
k Word -> Word -> Word
forall a. Num a => a -> a -> a
-Word
2)f a
p Word
1=a
p a -> a -> a
forall a. Num a => a -> a -> a
-a
1f a
p Word
2=(a
p a -> a -> a
forall a. Num a => a -> a -> a
-a
1)a -> a -> a
forall a. Num a => a -> a -> a
*a
p f a
p Word
k =(a
p a -> a -> a
forall a. Num a => a -> a -> a
-a
1)a -> a -> a
forall a. Num a => a -> a -> a
*a
p a -> Int -> a
forall a b. (Num a, Integral b) => a -> b -> a
^Word -> Int
wordToInt (Word
k Word -> Word -> Word
forall a. Num a => a -> a -> a
-Word
1)-- | Create an additive function from the function on prime's powers. See examples below.additive ::Numa =>(Prime n ->Word->a )->ArithmeticFunction n a additive :: forall a n.
Num a =>
(Prime n -> Word -> a) -> ArithmeticFunction n a
additive Prime n -> Word -> a
f =(Prime n -> Word -> Sum a)
-> (Sum a -> a) -> ArithmeticFunction n a
forall m n a.
Monoid m =>
(Prime n -> Word -> m) -> (m -> a) -> ArithmeticFunction n a
ArithmeticFunction ((a -> Sum a
forall a. a -> Sum a
Sum(a -> Sum a) -> (Word -> a) -> Word -> Sum a
forall b c a. (b -> c) -> (a -> b) -> a -> c
.)((Word -> a) -> Word -> Sum a)
-> (Prime n -> Word -> a) -> Prime n -> Word -> Sum a
forall b c a. (b -> c) -> (a -> b) -> a -> c
.Prime n -> Word -> a
f )Sum a -> a
forall a. Sum a -> a
getSum-- | See 'smallOmegaA'.smallOmega ::(UniqueFactorisation n ,Numa )=>n ->a smallOmega :: forall n a. (UniqueFactorisation n, Num a) => n -> a
smallOmega =ArithmeticFunction n a -> n -> a
forall n a.
UniqueFactorisation n =>
ArithmeticFunction n a -> n -> a
runFunction ArithmeticFunction n a
forall a n. Num a => ArithmeticFunction n a
smallOmegaA -- | Number of distinct prime factors.---- > smallOmegaA = additive (\_ _ -> 1)smallOmegaA ::Numa =>ArithmeticFunction n a smallOmegaA :: forall a n. Num a => ArithmeticFunction n a
smallOmegaA =(Prime n -> Word -> a) -> ArithmeticFunction n a
forall a n.
Num a =>
(Prime n -> Word -> a) -> ArithmeticFunction n a
additive ((Prime n -> Word -> a) -> ArithmeticFunction n a)
-> (Prime n -> Word -> a) -> ArithmeticFunction n a
forall a b. (a -> b) -> a -> b
$(Word -> a) -> Prime n -> Word -> a
forall a b. a -> b -> a
const((Word -> a) -> Prime n -> Word -> a)
-> (Word -> a) -> Prime n -> Word -> a
forall a b. (a -> b) -> a -> b
$a -> Word -> a
forall a b. a -> b -> a
consta
1-- | See 'bigOmegaA'.bigOmega ::UniqueFactorisation n =>n ->WordbigOmega :: forall n. UniqueFactorisation n => n -> Word
bigOmega =ArithmeticFunction n Word -> n -> Word
forall n a.
UniqueFactorisation n =>
ArithmeticFunction n a -> n -> a
runFunction ArithmeticFunction n Word
forall n. ArithmeticFunction n Word
bigOmegaA -- | Number of prime factors, counted with multiplicity.---- > bigOmegaA = additive (\_ k -> k)bigOmegaA ::ArithmeticFunction n WordbigOmegaA :: forall n. ArithmeticFunction n Word
bigOmegaA =(Prime n -> Word -> Word) -> ArithmeticFunction n Word
forall a n.
Num a =>
(Prime n -> Word -> a) -> ArithmeticFunction n a
additive ((Prime n -> Word -> Word) -> ArithmeticFunction n Word)
-> (Prime n -> Word -> Word) -> ArithmeticFunction n Word
forall a b. (a -> b) -> a -> b
$(Word -> Word) -> Prime n -> Word -> Word
forall a b. a -> b -> a
constWord -> Word
forall a. a -> a
id-- | See 'expMangoldtA'.expMangoldt ::UniqueFactorisation n =>n ->n expMangoldt :: forall n. UniqueFactorisation n => n -> n
expMangoldt =ArithmeticFunction n n -> n -> n
forall n a.
UniqueFactorisation n =>
ArithmeticFunction n a -> n -> a
runFunction ArithmeticFunction n n
forall n. Num n => ArithmeticFunction n n
expMangoldtA -- | The exponent of von Mangoldt function. Use @log expMangoldtA@ to recover von Mangoldt function itself.expMangoldtA ::Numn =>ArithmeticFunction n n expMangoldtA :: forall n. Num n => ArithmeticFunction n n
expMangoldtA =(Prime n -> Word -> Mangoldt n)
-> (Mangoldt n -> n) -> ArithmeticFunction n n
forall m n a.
Monoid m =>
(Prime n -> Word -> m) -> (m -> a) -> ArithmeticFunction n a
ArithmeticFunction (Mangoldt n -> Word -> Mangoldt n
forall a b. a -> b -> a
const(Mangoldt n -> Word -> Mangoldt n)
-> (Prime n -> Mangoldt n) -> Prime n -> Word -> Mangoldt n
forall b c a. (b -> c) -> (a -> b) -> a -> c
.n -> Mangoldt n
forall a. a -> Mangoldt a
MangoldtOne (n -> Mangoldt n) -> (Prime n -> n) -> Prime n -> Mangoldt n
forall b c a. (b -> c) -> (a -> b) -> a -> c
.Prime n -> n
forall a. Prime a -> a
unPrime )Mangoldt n -> n
forall a. Num a => Mangoldt a -> a
runMangoldt dataMangoldt a =MangoldtZero |MangoldtOne a |MangoldtMany runMangoldt ::Numa =>Mangoldt a ->a runMangoldt :: forall a. Num a => Mangoldt a -> a
runMangoldt Mangoldt a
m =caseMangoldt a
m ofMangoldt a
MangoldtZero ->a
1MangoldtOne a
a ->a
a Mangoldt a
MangoldtMany ->a
1instanceSemigroup(Mangoldt a )whereMangoldt a
MangoldtZero <> :: Mangoldt a -> Mangoldt a -> Mangoldt a
<>Mangoldt a
a =Mangoldt a
a Mangoldt a
a <>Mangoldt a
MangoldtZero =Mangoldt a
a Mangoldt a
_<>Mangoldt a
_=Mangoldt a
forall a. Mangoldt a
MangoldtMany instanceMonoid(Mangoldt a )wheremempty :: Mangoldt a
mempty=Mangoldt a
forall a. Mangoldt a
MangoldtZero -- | See 'isNFreeA'.isNFree ::UniqueFactorisation n =>Word->n ->BoolisNFree :: forall n. UniqueFactorisation n => Word -> n -> Bool
isNFree Word
n =ArithmeticFunction n Bool -> n -> Bool
forall n a.
UniqueFactorisation n =>
ArithmeticFunction n a -> n -> a
runFunction (Word -> ArithmeticFunction n Bool
forall n. Word -> ArithmeticFunction n Bool
isNFreeA Word
n )-- | 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@.isNFreeA ::Word->ArithmeticFunction n BoolisNFreeA :: forall n. Word -> ArithmeticFunction n Bool
isNFreeA Word
n =(Prime n -> Word -> All)
-> (All -> Bool) -> ArithmeticFunction n Bool
forall m n a.
Monoid m =>
(Prime n -> Word -> m) -> (m -> a) -> ArithmeticFunction n a
ArithmeticFunction (\Prime n
_Word
pow ->Bool -> All
All(Bool -> All) -> Bool -> All
forall a b. (a -> b) -> a -> b
$Word
pow Word -> Word -> Bool
forall a. Ord a => a -> a -> Bool
<Word
n )All -> Bool
getAllnewtypeLCM a =LCM {forall a. LCM a -> a
getLCM ::a }instanceIntegrala =>Semigroup(LCM a )where<> :: LCM a -> LCM a -> LCM a
(<>)=(a -> a -> a) -> LCM a -> LCM a -> LCM a
forall a b. Coercible a b => a -> b
coerce(a -> a -> a
forall a. Integral a => a -> a -> a
lcm::a ->a ->a )instanceIntegrala =>Monoid(LCM a )wheremempty :: LCM a
mempty=a -> LCM a
forall a. a -> LCM a
LCM a
1newtypeXor =Xor {Xor -> Bool
_getXor ::Bool}runXor ::Numa =>Xor ->a runXor :: forall a. Num a => Xor -> a
runXor Xor
m =caseXor
m ofXor Bool
False->a
1Xor Bool
True->-a
1instanceSemigroupXor where<> :: Xor -> Xor -> Xor
(<>)=(Bool -> Bool -> Bool) -> Xor -> Xor -> Xor
forall a b. Coercible a b => a -> b
coerce(Bool -> Bool -> Bool
forall a. Eq a => a -> a -> Bool
(/=)::Bool->Bool->Bool)instanceMonoidXor wheremempty :: Xor
mempty=Bool -> Xor
Xor Bool
FalsenewtypeSetProduct a =SetProduct {forall a. SetProduct a -> Set a
getSetProduct ::Seta }instance(Numa ,Orda )=>Semigroup(SetProduct a )whereSetProduct Set a
s1 <> :: SetProduct a -> SetProduct a -> SetProduct a
<>SetProduct Set a
s2 =Set a -> SetProduct a
forall a. Set a -> SetProduct a
SetProduct (Set a -> SetProduct a) -> Set a -> SetProduct a
forall a b. (a -> b) -> a -> b
$Set a
s1 Set a -> Set a -> Set a
forall a. Semigroup a => a -> a -> a
<>Set a
s2 Set a -> Set a -> Set a
forall a. Semigroup a => a -> a -> a
<>(a -> Set a) -> Set a -> Set a
forall m a. Monoid m => (a -> m) -> Set a -> m
forall (t :: * -> *) m a.
(Foldable t, Monoid m) =>
(a -> m) -> t a -> m
foldMap(\a
n ->(a -> a) -> Set a -> Set a
forall a b. (a -> b) -> Set a -> Set b
S.mapMonotonic(a -> a -> a
forall a. Num a => a -> a -> a
*a
n )Set a
s2 )Set a
s1 instance(Numa ,Orda )=>Monoid(SetProduct a )wheremempty :: SetProduct a
mempty=Set a -> SetProduct a
forall a. Set a -> SetProduct a
SetProduct Set a
forall a. Monoid a => a
memptynewtypeListProduct a =ListProduct {forall a. ListProduct a -> [a]
getListProduct ::[a ]}instanceNuma =>Semigroup(ListProduct a )whereListProduct [a]
s1 <> :: ListProduct a -> ListProduct a -> ListProduct a
<>ListProduct [a]
s2 =[a] -> ListProduct a
forall a. [a] -> ListProduct a
ListProduct ([a] -> ListProduct a) -> [a] -> ListProduct a
forall a b. (a -> b) -> a -> b
$[a]
s1 [a] -> [a] -> [a]
forall a. Semigroup a => a -> a -> a
<>[a]
s2 [a] -> [a] -> [a]
forall a. Semigroup a => a -> a -> a
<>(a -> [a]) -> [a] -> [a]
forall m a. Monoid m => (a -> m) -> [a] -> m
forall (t :: * -> *) m a.
(Foldable t, Monoid m) =>
(a -> m) -> t a -> m
foldMap(\a
n ->(a -> a) -> [a] -> [a]
forall a b. (a -> b) -> [a] -> [b]
map(a -> a -> a
forall a. Num a => a -> a -> a
*a
n )[a]
s2 )[a]
s1 instanceNuma =>Monoid(ListProduct a )wheremempty :: ListProduct a
mempty=[a] -> ListProduct a
forall a. [a] -> ListProduct a
ListProduct [a]
forall a. Monoid a => a
mempty-- Represent as a Reader monadnewtypeBoundedSetProduct a =BoundedSetProduct {forall a. BoundedSetProduct a -> a -> Set a
_getBoundedSetProduct ::a ->Seta }takeWhileLE ::Orda =>a ->Seta ->Seta takeWhileLE :: forall a. Ord a => a -> Set a -> Set a
takeWhileLE a
b Set a
xs =ifBool
m thena -> Set a -> Set a
forall a. Ord a => a -> Set a -> Set a
S.inserta
b Set a
ls elseSet a
ls where(Set a
ls ,Bool
m ,Set a
_)=a -> Set a -> (Set a, Bool, Set a)
forall a. Ord a => a -> Set a -> (Set a, Bool, Set a)
S.splitMembera
b Set a
xs instance(Orda ,Numa )=>Semigroup(BoundedSetProduct a )whereBoundedSetProduct a -> Set a
f1 <> :: BoundedSetProduct a -> BoundedSetProduct a -> BoundedSetProduct a
<>BoundedSetProduct a -> Set a
f2 =(a -> Set a) -> BoundedSetProduct a
forall a. (a -> Set a) -> BoundedSetProduct a
BoundedSetProduct a -> Set a
f wheref :: a -> Set a
f a
b =Set a
s1 Set a -> Set a -> Set a
forall a. Semigroup a => a -> a -> a
<>Set a
s2 Set a -> Set a -> Set a
forall a. Semigroup a => a -> a -> a
<>(a -> Set a) -> Set a -> Set a
forall m a. Monoid m => (a -> m) -> Set a -> m
forall (t :: * -> *) m a.
(Foldable t, Monoid m) =>
(a -> m) -> t a -> m
foldMap(\a
n ->a -> Set a -> Set a
forall a. Ord a => a -> Set a -> Set a
takeWhileLE a
b (Set a -> Set a) -> Set a -> Set a
forall a b. (a -> b) -> a -> b
$(a -> a) -> Set a -> Set a
forall a b. (a -> b) -> Set a -> Set b
S.mapMonotonic(a -> a -> a
forall a. Num a => a -> a -> a
*a
n )Set a
s2 )Set a
s1 wheres1 :: Set a
s1 =a -> Set a
f1 a
b s2 :: Set a
s2 =a -> Set a
f2 a
b instance(Orda ,Numa )=>Monoid(BoundedSetProduct a )wheremempty :: BoundedSetProduct a
mempty=(a -> Set a) -> BoundedSetProduct a
forall a. (a -> Set a) -> BoundedSetProduct a
BoundedSetProduct a -> Set a
forall a. Monoid a => a
memptynewtypeIntSetProduct =IntSetProduct {IntSetProduct -> IntSet
getIntSetProduct ::IntSet}instanceSemigroupIntSetProduct whereIntSetProduct IntSet
s1 <> :: IntSetProduct -> IntSetProduct -> IntSetProduct
<>IntSetProduct IntSet
s2 =IntSet -> IntSetProduct
IntSetProduct (IntSet -> IntSetProduct) -> IntSet -> IntSetProduct
forall a b. (a -> b) -> a -> b
$[IntSet] -> IntSet
forall (f :: * -> *). Foldable f => f IntSet -> IntSet
IS.unions([IntSet] -> IntSet) -> [IntSet] -> IntSet
forall a b. (a -> b) -> a -> b
$IntSet
s1 IntSet -> [IntSet] -> [IntSet]
forall a. a -> [a] -> [a]
:IntSet
s2 IntSet -> [IntSet] -> [IntSet]
forall a. a -> [a] -> [a]
:(Int -> IntSet) -> [Int] -> [IntSet]
forall a b. (a -> b) -> [a] -> [b]
map(\Int
n ->(Int -> Int) -> IntSet -> IntSet
IS.map(Int -> Int -> Int
forall a. Num a => a -> a -> a
*Int
n )IntSet
s2 )(IntSet -> [Int]
IS.toAscListIntSet
s1 )instanceMonoidIntSetProduct wheremempty :: IntSetProduct
mempty=IntSet -> IntSetProduct
IntSetProduct IntSet
forall a. Monoid a => a
mempty