{- Testbench for data in Fermatfactors. This code is public domain. -} {-# LANGUAGE ScopedTypeVariables, LambdaCase, PackageImports #-} module Main(main) where { import System.Environment(getArgs); import Data.Function((&)); import Control.Category((>>>)); import Prelude hiding((.),(>>)); import qualified Fermatfactors; import GHC.Integer.GMP.Internals(powModInteger); import qualified Numeric.Modular as Modular; type Ii = Integer; main :: IO(); main = getArgs >>= \case{ -- compute remainders after division by known factors, so should print out all zeroes [] -> Fermatfactors.initfactors & map (\x -> 0 == fastverify x) & and & print; ["fastverify"] -> mapM_ (fastverify >>> print) Fermatfactors.initfactors; ["slowverify",n] -> mapM_ (slowverify >>> print) $ take (read n) Fermatfactors.initfactors; ["slowverify"] -> mapM_ (slowverify >>> print) $ take 31 Fermatfactors.initfactors; ["parigp"] -> mapM_ (verifyparigp >>> putStrLn) Fermatfactors.initfactors; -- verify no gaps ["ordered"] -> mapM_ print didverifyordered; -- test with cofactor is prime. composite for n >= 12, untestable for n> about 26 ["cofactorprime"] -> cofactorprime; ["cofactorprime1",n] -> (Fermatfactors.initfactors !! (read n)) & cofactorprime1 & printprp; _ -> undefined; }; printprp :: (Ii,Bool) -> IO (); printprp (i,result) = putStrLn $ show i ++ " " ++ if result then "probably-prime" else "definitely-composite"; -- Num works for Modular.Mod type in fastverify nthfermatnumber :: Num a => Ii -> a; nthfermatnumber n = 2^(2::Ii)^n+1; -- 31 is about the max this can do slowverify :: (Ii, [Fermatfactors.Fermatrecord]) -> (Ii,Ii); slowverify (n,fs) = (n,mod (nthfermatnumber n) (map Fermatfactors.getprimefactor fs & product)); verifyordered :: Ii -> (Ii,a) -> (Ii,a); verifyordered x y = if x== fst y then y else error $ "did not match " ++ show x ++ " " ++ show (fst y); didverifyordered :: [(Ii,[Fermatfactors.Fermatrecord])]; didverifyordered = zipWith verifyordered (enumFrom 0) Fermatfactors.initfactors; allsmallfactors :: [Fermatfactors.Fermatrecord] -> Ii; allsmallfactors = map Fermatfactors.getprimefactor >>> product; cofactor :: (Ii, [Fermatfactors.Fermatrecord]) -> Ii; cofactor (n,fs) = case divMod (nthfermatnumber n) (allsmallfactors fs) of {(q,0) -> q; _ -> error "cofactor did not divide evenly" }; -- fermat test with base 3 fermatprimality :: Ii -> Ii; fermatprimality p = powModInteger 3 (p-1) p; cofactorprime1 :: (Ii, [Fermatfactors.Fermatrecord]) -> (Ii, Bool); cofactorprime1 (0,_) = (0,True); -- fermat test base 3 does not work when the number tested is 3, so hardcode the correct answer cofactorprime1 x = (fst x, 1==fermatprimality(cofactor x)); cofactorprime :: IO (); cofactorprime = Fermatfactors.initfactors & mapM_ (cofactorprime1 >>> printprp); verifyparigp :: (Ii, [Fermatfactors.Fermatrecord]) -> String; verifyparigp (n,fs) = "print("++show n++",\" \",1+Mod(2," ++ (fs & allsmallfactors & show) ++")^(2^"++ show n++"))"; fastverify :: (Ii, [Fermatfactors.Fermatrecord]) -> Ii; fastverify (n,fs) = Modular.withMod (allsmallfactors fs) $ nthfermatnumber n; -- magic mkMod type is an instance of Num } --end