Copyright | (c) 2018 Frederick Schneider |
---|---|
License | MIT |
Maintainer | Frederick Schneider <frederick.schneider2011@gmail.com> |
Safe Haskell | None |
Language | Haskell2010 |
A smooth number is an integer, which can be represented as a product of powers of elements from a given set (smooth basis). E. g., 48 = 3 * 4 * 4 is smooth over a set {3, 4}, and 24 is not.
Synopsis
- data SmoothBasis a
- fromSet :: Euclidean a => Set a -> Maybe (SmoothBasis a)
- fromList :: Euclidean a => [a] -> Maybe (SmoothBasis a)
- fromSmoothUpperBound :: Integral a => a -> Maybe (SmoothBasis a)
- smoothOver :: Integral a => SmoothBasis a -> [a]
- smoothOver' :: forall a b. (Eq a, Num a, Ord b) => (a -> b) -> SmoothBasis a -> [a]
- smoothOverInRange :: forall a. Integral a => SmoothBasis a -> a -> a -> [a]
- smoothOverInRangeBF :: forall a. (Enum a, Euclidean a) => SmoothBasis a -> a -> a -> [a]
- isSmooth :: forall a. Euclidean a => SmoothBasis a -> a -> Bool
Create a smooth basis
data SmoothBasis a Source #
An abstract representation of a smooth basis. It consists of a set of numbers ≥2.
Instances
Eq a => Eq (SmoothBasis a) Source # | |
Defined in Math.NumberTheory.SmoothNumbers (==) :: SmoothBasis a -> SmoothBasis a -> Bool # (/=) :: SmoothBasis a -> SmoothBasis a -> Bool # | |
Show a => Show (SmoothBasis a) Source # | |
Defined in Math.NumberTheory.SmoothNumbers showsPrec :: Int -> SmoothBasis a -> ShowS # show :: SmoothBasis a -> String # showList :: [SmoothBasis a] -> ShowS # |
fromSet :: Euclidean a => Set a -> Maybe (SmoothBasis a) Source #
Build a SmoothBasis
from a set of numbers ≥2.
>>>
import qualified Data.Set as Set
>>>
fromSet (Set.fromList [2, 3])
Just (SmoothBasis {unSmoothBasis = [2,3]})>>>
fromSet (Set.fromList [2, 4])
Just (SmoothBasis {unSmoothBasis = [2,4]})>>>
fromSet (Set.fromList [1, 3]) -- should be >= 2
Nothing
fromList :: Euclidean a => [a] -> Maybe (SmoothBasis a) Source #
Build a SmoothBasis
from a list of numbers ≥2.
>>>
fromList [2, 3]
Just (SmoothBasis {unSmoothBasis = [2,3]})>>>
fromList [2, 2]
Just (SmoothBasis {unSmoothBasis = [2]})>>>
fromList [2, 4]
Just (SmoothBasis {unSmoothBasis = [2,4]})>>>
fromList [1, 3] -- should be >= 2
Nothing
fromSmoothUpperBound :: Integral a => a -> Maybe (SmoothBasis a) Source #
Build a SmoothBasis
from a list of primes below given bound.
>>>
fromSmoothUpperBound 10
Just (SmoothBasis {unSmoothBasis = [2,3,5,7]})>>>
fromSmoothUpperBound 1
Nothing
Generate smooth numbers
smoothOver :: Integral a => SmoothBasis a -> [a] Source #
Generate an infinite ascending list of smooth numbers over a given smooth basis.
>>>
import Data.Maybe
>>>
take 10 (smoothOver (fromJust (fromList [2, 5])))
[1,2,4,5,8,10,16,20,25,32]
smoothOver' :: forall a b. (Eq a, Num a, Ord b) => (a -> b) -> SmoothBasis a -> [a] Source #
Helper used by smoothOver
(Integral
constraint) and smoothOver'
(Euclidean
constraint) Since the typeclass constraint is just
Num
, it receives a norm
comparison function for the generated smooth
numbers.
This function relies on the fact that for any element of a smooth basis p
and any a
it is true that norm (a * p) > norm a
.
This condition is not checked.
smoothOverInRange :: forall a. Integral a => SmoothBasis a -> a -> a -> [a] Source #
Generate an ascending list of smooth numbers over a given smooth basis in a given range.
It may appear inefficient
for short, but distant ranges;
consider using smoothOverInRangeBF
in such cases.
>>>
import Data.Maybe
>>>
smoothOverInRange (fromJust (fromList [2, 5])) 100 200
[100,125,128,160,200]
smoothOverInRangeBF :: forall a. (Enum a, Euclidean a) => SmoothBasis a -> a -> a -> [a] Source #
Generate an ascending list of smooth numbers over a given smooth basis in a given range.
It is inefficient
for large or starting near 0 ranges;
consider using smoothOverInRange
in such cases.
Suffix BF stands for the brute force algorithm, involving a lot of divisions.
>>>
import Data.Maybe
>>>
smoothOverInRangeBF (fromJust (fromList [2, 5])) 100 200
[100,125,128,160,200]