結果

問題 No.3030 ミラー・ラビン素数判定法のテスト
ユーザー かりあげクンかりあげクン
提出日時 2020-09-17 01:28:05
言語 Haskell
(9.8.2)
結果
AC  
実行時間 242 ms / 9,973 ms
コード長 2,265 bytes
コンパイル時間 1,421 ms
コンパイル使用メモリ 189,768 KB
実行使用メモリ 13,028 KB
最終ジャッジ日時 2023-08-10 16:22:51
合計ジャッジ時間 3,181 ms
ジャッジサーバーID
(参考情報)
judge12 / judge14
このコードへのチャレンジ
(要ログイン)

テストケース

テストケース表示
入力 結果 実行時間
実行使用メモリ
testcase_00 AC 2 ms
7,804 KB
testcase_01 AC 2 ms
7,668 KB
testcase_02 AC 3 ms
7,940 KB
testcase_03 AC 3 ms
8,100 KB
testcase_04 AC 162 ms
12,888 KB
testcase_05 AC 162 ms
12,988 KB
testcase_06 AC 102 ms
12,892 KB
testcase_07 AC 102 ms
12,776 KB
testcase_08 AC 102 ms
13,028 KB
testcase_09 AC 242 ms
12,796 KB
権限があれば一括ダウンロードができます
コンパイルメッセージ
Loaded package environment from /home/judge/.ghc/x86_64-linux-9.6.1/environments/default
[1 of 2] Compiling Main             ( Main.hs, Main.o )

Main.hs:42:34: warning: [GHC-68441] [-Wdeprecations]
    In the use of ‘powModInteger’
    (imported from GHC.Integer.GMP.Internals):
    Deprecated: "Use integerPowMod# instead"
   |
42 | powModInt a n mo = fromInteger $ GMP.powModInteger (fromIntegral a) (fromIntegral n) (fromIntegral mo)
   |                                  ^^^^^^^^^^^^^^^^^
[2 of 2] Linking a.out

ソースコード

diff #

{-# LANGUAGE BangPatterns #-}
import qualified Control.Arrow             as Arrow
import           Data.Bits                 (Bits (unsafeShiftL, unsafeShiftR),
                                            FiniteBits (countTrailingZeros))
import           Data.Bool                 (bool)
import qualified Data.ByteString.Char8     as BSC8

import qualified Data.Vector.Unboxed       as VU
import qualified GHC.Integer.GMP.Internals as GMP

isPrime :: Int -> Bool
isPrime k
  | k <= 3 = k == 2 || k == 3
  | even k = False
  | otherwise = millerRabin k
  where
    millerRabin :: Int -> Bool
    millerRabin n
      | n < 2047                = loop [2]
      | n < 1373653             = loop [2,3]
      | n < 9080191             = loop [31,73]
      | n < 25326001            = loop [2,3,5]
      | n < 4759123141          = loop [2,7,61]
      | n < 1122004669633       = loop [2,13,23,1662803]
      | n < 2152302898747       = loop [2,3,5,7,11]
      | n < 3474749660383       = loop [2,3,5,7,11,13]
      | n < 341550071728321     = loop [2,3,5,7,11,13,17]
      | otherwise               = loop [2,325,9375,28178,450775,9780504,1795265022]
      where
        m = n - 1
        s = countTrailingZeros m
        d = m `unsafeShiftR` s

        loop [] = True
        loop (a:as)
          | powModInt (a `mod` n) d n /= 1 = (not allok) && loop as
          | otherwise = loop as
          where
            !allok = all (\r -> (powModInt a ((1 `unsafeShiftL` r) * d) n) /= m) [0..(s - 1)]

powModInt :: Int -> Int -> Int -> Int
powModInt a n mo = fromInteger $ GMP.powModInteger (fromIntegral a) (fromIntegral n) (fromIntegral mo)
{-# INLINE powModInt #-}

type Parser a = BSC8.ByteString -> Maybe (a, BSC8.ByteString)
parseInt :: Parser Int
parseInt = fmap (Arrow.second BSC8.tail) . BSC8.readInt
parse1 :: IO Int
parse1 = readLn
parseN :: Int -> IO (VU.Vector Int)
parseN n = VU.replicateM n parse1
-------------------------------------------------------------------------------
main :: IO ()
main = do
  n  <- parse1
  xs <- parseN n
  VU.mapM_ (BSC8.putStrLn . solve) xs

solve :: Int -> BSC8.ByteString
solve n = BSC8.pack $ bool (show n ++ " 0") (show n ++ " 1") (isPrime n)
-------------------------------------------------------------------------------
0