Skip to content

Commit c340b3e

Browse files
committed
ABC177-E
1 parent ad088f9 commit c340b3e

File tree

2 files changed

+80
-0
lines changed

2 files changed

+80
-0
lines changed

abc/README.md

Lines changed: 11 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -416,3 +416,14 @@
416416
* [x] D - Not Divisible
417417
* [ ] E - Smart Infants
418418
* [ ] F - Pond Skater
419+
420+
## AtCoder Beginner Contest 177
421+
422+
<https://atcoder.jp/contests/abc177>
423+
424+
* [ ] A - Don't be late
425+
* [ ] B - Substring
426+
* [ ] C - Sum of product of pairs
427+
* [ ] D - Friends
428+
* [x] E - Coprime
429+
* [ ] F - I hate Shortest Path Problem

abc/abc177-e/Main.hs

Lines changed: 69 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,69 @@
1+
-- https://github.com/minoki/my-atcoder-solutions
2+
{-# LANGUAGE TypeApplications #-}
3+
{-# LANGUAGE BangPatterns #-}
4+
{-# LANGUAGE NumericUnderscores #-}
5+
import Data.Char (isSpace)
6+
import Data.List
7+
import Control.Monad
8+
import Control.Monad.Trans.Maybe
9+
import Control.Monad.ST
10+
import qualified Data.Vector.Unboxed as U
11+
import qualified Data.Vector.Unboxed.Mutable as UM
12+
import qualified Data.ByteString.Char8 as BS
13+
import qualified Test.QuickCheck as QC
14+
import Data.Coerce
15+
16+
isPairwiseCoprime_naive :: Int -> U.Vector Int -> Bool
17+
isPairwiseCoprime_naive _mbound xs = and [ gcd x y == 1 | x:ys <- tails (U.toList xs), y <- ys ]
18+
19+
toHistogram :: Int -> U.Vector Int -> U.Vector Int
20+
toHistogram mbound xs = U.create $ do
21+
m <- UM.replicate (mbound + 1) (0 :: Int)
22+
U.forM_ xs $ \x -> do
23+
UM.modify m (+ 1) x
24+
return m
25+
26+
isPairwiseCoprime :: Int -> U.Vector Int -> Bool
27+
isPairwiseCoprime !mbound !xs = maybe False (const True) $ runST $ runMaybeT $ do
28+
let !m = toHistogram mbound xs
29+
sieve <- UM.replicate (mbound + 1) True
30+
UM.write sieve 0 False
31+
UM.write sieve 1 False
32+
forM_ [2..mbound] $ \i -> do
33+
t <- UM.read sieve i
34+
when t $ do
35+
let loop !j !u | j > mbound = if u >= 2 then
36+
mzero
37+
else
38+
return ()
39+
| otherwise = do
40+
UM.write sieve j False
41+
let !v = u + m U.! j
42+
if v >= 2 then
43+
mzero -- break
44+
else
45+
loop (j + i) v
46+
loop (2 * i) (m U.! i)
47+
return () -- The answer is "Yes" -- pairwise coprime
48+
49+
isSetwiseCoprime :: U.Vector Int -> Bool
50+
isSetwiseCoprime xs = U.foldl' gcd 0 xs == 1 -- not best
51+
52+
main = do
53+
n <- readLn @Int
54+
xs <- U.unfoldrN n (BS.readInt . BS.dropWhile isSpace) <$> BS.getLine
55+
let mbound = U.maximum xs
56+
if isPairwiseCoprime mbound xs then
57+
putStrLn "pairwise coprime"
58+
else if isSetwiseCoprime xs then
59+
putStrLn "setwise coprime"
60+
else
61+
putStrLn "not coprime"
62+
63+
prop :: QC.NonEmptyList (QC.Positive Int) -> QC.Property
64+
prop xs' = let xs = U.fromList (coerce xs') :: U.Vector Int
65+
mbound = U.maximum xs
66+
in isPairwiseCoprime mbound xs QC.=== isPairwiseCoprime_naive mbound xs
67+
68+
runTest :: IO ()
69+
runTest = QC.quickCheck $ QC.withMaxSuccess 1000 $ QC.mapSize (* 1000) prop

0 commit comments

Comments
 (0)