結果

問題 No.1232 2^x = x
ユーザー かりあげクンかりあげクン
提出日時 2020-09-23 15:29:05
言語 Haskell
(9.8.2)
結果
TLE  
実行時間 -
コード長 2,987 bytes
コンパイル時間 3,096 ms
コンパイル使用メモリ 189,792 KB
実行使用メモリ 13,876 KB
最終ジャッジ日時 2023-09-10 07:14:30
合計ジャッジ時間 8,025 ms
ジャッジサーバーID
(参考情報)
judge14 / judge13
このコードへのチャレンジ
(要ログイン)

テストケース

テストケース表示
入力 結果 実行時間
実行使用メモリ
testcase_00 TLE -
testcase_01 -- -
testcase_02 -- -
testcase_03 -- -
権限があれば一括ダウンロードができます
コンパイルメッセージ
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:27:33: warning: [GHC-68441] [-Wdeprecations]
    In the use of ‘powModInteger’
    (imported from GHC.Integer.GMP.Internals):
    Deprecated: "Use integerPowMod# instead"
   |
27 | powModInt a b c = fromInteger $ GMP.powModInteger (fromIntegral a) (fromIntegral b) (fromIntegral c)
   |                                 ^^^^^^^^^^^^^^^^^
[2 of 2] Linking a.out

ソースコード

diff #

{-# LANGUAGE BangPatterns #-}
{- base -}
import           Control.Arrow
import           Control.Monad
import           Control.Monad.ST
import           Data.Bool
import           Data.Char
{- integer-gmp -}
import qualified GHC.Integer.GMP.Internals         as GMP
{- bytestring -}
import qualified Data.ByteString.Char8             as BSC8
{- vector -}
import qualified Data.Vector                       as V
import qualified Data.Vector.Fusion.Stream.Monadic as VFSM
import qualified Data.Vector.Unboxed               as VU
import qualified Data.Vector.Unboxed.Mutable       as VUM


main :: IO ()
main = do
  n  <- parse1
  rep n $ \_ -> do
    p <-parse1
    print $ tetrationMod 2 32 (p * (p - 1))

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

tetrationMod :: Int -> Int -> Int -> Int
tetrationMod a b m
  | m == 1 = 0
  | a == 0 = bool 0 1 (even b)
  | b == 0 = 1
  | b == 1 = a `mod` m
  | b == 2 = powModInt a b m
  | otherwise = let phi = (m - 1) * eulerPhi (m - 1)
                in powModInt (a `mod` m) ((tetrationMod a (b - 1) phi) + phi) m

eulerPhi :: Int -> Int
eulerPhi n = runST $ do
  xs <- VU.unsafeThaw $ VU.fromList [n, n, 2]
  ys <- loopFor xs
  p  <- VUM.unsafeRead ys 0
  q  <- VUM.unsafeRead ys 1
  if q > 1 then return (p - p `div` q) else return p
    where
      loopFor :: VUM.STVector s Int -> ST s (VUM.STVector s Int)
      loopFor xx = do
        idx <- VUM.unsafeRead xx 2
        if idx * idx > n then return xx else do
          xret <- VUM.unsafeRead xx 0
          xn   <- VUM.unsafeRead xx 1
          if xn `mod` idx /= 0
            then do
              VUM.unsafeWrite xx 2 (idx + 1)
              loopFor xx
            else do
              VUM.unsafeWrite xx 0 (xret - xret `div` idx)
              whileXS <- loopWhile xx
              VUM.unsafeWrite whileXS 2 (idx + 1)
              loopFor whileXS
                where
                  loopWhile :: VUM.STVector s Int -> ST s (VUM.STVector s Int)
                  loopWhile ks = do
                    whileN <- VUM.unsafeRead ks 1
                    whileI <- VUM.unsafeRead ks 2
                    if whileN `mod` whileI /= 0 then return ks else do
                      VUM.unsafeWrite ks 1 (whileN `div` whileI)
                      loopWhile ks

-- input
type Parser a = BSC8.ByteString -> Maybe (a, BSC8.ByteString)
parseInt :: Parser Int
parseInt = fmap (second BSC8.tail) . BSC8.readInt
parse1 :: IO Int
parse1 = readLn
parseN :: Int -> IO (VU.Vector Int)
parseN n = VU.replicateM n parse1

-- rep
stream :: Monad m => Int -> Int -> VFSM.Stream m Int
stream !l !r = VFSM.Stream step l
  where
    step x
      | x < r     = return $ VFSM.Yield x (x + 1)
      | otherwise = return VFSM.Done
    {-# INLINE [0] step #-}
{-# INLINE [1] stream #-}

rep :: Monad m => Int -> (Int -> m ()) -> m ()
rep n = flip VFSM.mapM_ (stream 0 n)
{-# INLINE rep #-}
0