~shreyasminocha/haskell-crypto

67019a8c1a5bf5b613e11db48cb7d545a7cc286c — Shreyas Minocha 1 year, 1 month ago 8362589
Add sieving functions
5 files changed, 55 insertions(+), 1 deletions(-)

M Factorize.hs
M FastPowering.hs
A QuadraticSieve.hs
M README.md
A SmoothNumbers.hs
M Factorize.hs => Factorize.hs +6 -1
@@ 1,4 1,9 @@
module Factorize (factors, canonicalFactorization) where
module Factorize (isPrime, factors, canonicalFactorization) where

isPrime :: Int -> Bool
isPrime n
    | n == 1    = False
    | otherwise = length (factors n) == 1

factors :: Int -> [Int]
factors 0 = [0]

M FastPowering.hs => FastPowering.hs +3 -0
@@ 1,9 1,12 @@
module FastPowering where

import LinearCongruences (inverse)

powMod :: Int -> Int -> Int -> Int
powMod _ _ 0 = 1
powMod m x 1 = x `mod` m
powMod m x y
    | y < 0          = powMod m (inverse m x) (-y)
    | y `mod` 2 == 0 = t
    | otherwise      = ((x `mod` m) * t) `mod` m
    where r = powMod m x (y `div` 2)

A QuadraticSieve.hs => QuadraticSieve.hs +24 -0
@@ 0,0 1,24 @@
import Factorize (isPrime)

quadraticSieve :: Int -> Int -> [Int] -> [(Int, Int)]
quadraticSieve n b ts = map (\i -> (i, f n i)) thatReduce
    where thatReduce = filter ((== 1) . (sieve (primePowersUpto b)) . (f n)) ts

sieve :: [Int] -> Int -> Int
sieve fs x = foldl reduce x fs

reduce :: Int -> Int -> Int
reduce n fac
    | n `mod` fac == 0 = reduce (n `div` fac) fac
    | otherwise = n

f :: Int -> Int -> Int
f n t = t^2 - n

primePowersUpto :: Int -> [Int]
primePowersUpto b = foldl (++) [] $
    map ((takeWhile (<= b)) . powers) primes
    where primes = filter isPrime [1..b]

powers :: Int -> [Int]
powers i = iterate (*i) i

M README.md => README.md +13 -0
@@ 145,6 145,19 @@ factorizeWithK 1226987 3 36 -- (653,1879)
factorize 220459 2 -- 449
```

#### Smooth Numbers

```hs
isSmooth 10 84 -- True
isPowerSmooth 10 84 -- True
```

#### Quadratic Sieve

```hs
quadraticSieve 493 11 [23..38] -- [(23,36),(25,132)]
```

## Miscellaneous

### Fast Powering

A SmoothNumbers.hs => SmoothNumbers.hs +9 -0
@@ 0,0 1,9 @@
import Data.List (all)
import Factorize (factors, canonicalFactorization)
import FastPowering (powMod)

isSmooth :: Int -> Int -> Bool
isSmooth b m = all (<= b) $ factors m

isPowerSmooth :: Int -> Int -> Bool
isPowerSmooth b m = all (<= b) $ map (uncurry (^)) $ canonicalFactorization m