{- Copyright 2011 Ken Takusagawa This program is free software: you can redistribute it and/or modify it under the terms of the GNU General Public License as published by the Free Software Foundation, either version 3 of the License, or (at your option) any later version. This program is distributed in the hope that it will be useful, but WITHOUT ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU General Public License for more details. You should have received a copy of the GNU General Public License along with this program. If not, see . -} -- mnnfmzxq module Main where { import qualified Primality; import Data.Maybe; main::IO(); -- main = print (mypollard (sqr (10^15+37))); main= mapM_ print $ filter (\(_,y)->isNothing y) $ zip_map mypollard $ comps; mypollard :: Integer -> Maybe [Integer]; mypollard n = domany1 (Modulus n) (-1) (map initial [1..3]); -- (26756459,Nothing) after 423 minutes zip_map f l = zip l (map f l); pbig :: [Integer]; pbig = filter isprime (enumFrom (10)); comps :: [Integer]; -- comps = do { a <- pbig ; return (a*a)}; comps = filter (not.isprime)(enumFrom 10); isprime :: Integer -> Bool; isprime = Primality.miller_rabin_isPrime; sqr :: Integer -> Integer; sqr x = x*x; f :: Integer -> Integer -> Integer; f c x = x*x+c; pollard :: Integer -> Maybe Integer; pollard n = pollard1 n 2 2; pollard1 :: Integer -> Integer -> Integer -> Maybe Integer; pollard1 n slow fast = let { mf :: Integer -> Integer; mf x = mod (f 1 x) n; ns :: Integer; ns = mf slow; nf :: Integer; nf = mf (mf fast); } in case (gcd (nf-ns) n) of { x | x == 1 -> pollard1 n ns nf | x == n -> error ("failed " ++ (show x)) | True -> Just x; }; newtype Modulus = Modulus Integer; pollard2 :: Modulus -> Integer -> (Integer, Integer) -> (Integer, Integer); pollard2 (Modulus n) c (slow, fast) = let { mf :: Integer -> Integer; mf x = mod (f c x) n; ns :: Integer; ns = mf slow; nf :: Integer; nf = mf (mf fast); } in (ns, nf); type II = (Integer, Integer); termination :: Modulus -> II -> Bool; termination m xy = (1 /= gcdn m xy); success :: Modulus -> II -> Bool; success m@(Modulus n) xy = (n /= gcdn m xy); gcdn :: Modulus -> II -> Integer; gcdn (Modulus n) (x, y) = gcd (x-y) n; next :: Modulus -> Integer -> (Integer,Integer) -> Output; next m c xy = case (termination m xy) of { False -> Keep_going c xy; True -> case (success m xy) of { True -> Success (gcdn m xy); _ -> Failure; }; }; donext :: Modulus -> Output -> Output; donext m (Keep_going c xy) = next m c (pollard2 m c xy); donext _ x = x; isSuccess :: Output -> Bool; isSuccess (Success _) = True; isSuccess _ = False; isFail :: Output -> Bool; isFail Failure = True; isFail _ = False; domany1 :: Modulus -> Int -> [Output] -> Maybe [Integer]; domany1 _ 0 _ = Nothing; domany1 m count xs = let { new = map (donext m) xs; } in case (any isSuccess new) of { True -> Just $ do { (Success i) <- new; return i; }; False -> case (all isFail new) of { True -> Nothing; False -> domany1 m (count-1) new }; }; domany :: Modulus -> [Output] -> [Output]; domany m xs = let { new = map (donext m) xs; } in case (any isSuccess new) of { True -> filter isSuccess new; False -> new; }; evaluate :: [Output] -> [Integer]; evaluate xs = do { (Success i) <- xs; return i; }; countmany :: Modulus -> Int -> [Output] -> [Integer]; countmany m i xs = evaluate ((iterate (domany m) xs) !! i); data Output = Success Integer | Failure | Keep_going Integer II; initial :: Integer -> Output; initial c = Keep_going c (2,2); }