Skip to content

Commit da2da3b

Browse files
committed
ABC162
1 parent 43e56be commit da2da3b

File tree

10 files changed

+206
-0
lines changed

10 files changed

+206
-0
lines changed

abc/README.md

Lines changed: 11 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -382,3 +382,14 @@
382382
* [ ] D - Prediction and Restriction
383383
* [ ] E - Handshake
384384
* [ ] F - Surrounded Notes
385+
386+
## AtCoder Beginner Contest 162
387+
388+
<https://atcoder.jp/contests/abc162>
389+
390+
* [x] A - Lucky 7
391+
* [x] B - FizzBuzz Sum
392+
* [x] C - Sum of gcd of Tuples (Easy)
393+
* [x] D - RGB Triplets
394+
* [x] E - Sum of gcd of Tuples (Hard)
395+
* [x] F - Select Half

abc/abc162-a/Main.hs

Lines changed: 5 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,5 @@
1+
-- https://github.com/minoki/my-atcoder-solutions
2+
3+
main = do
4+
s <- getLine
5+
putStrLn $ if '7' `elem` s then "Yes" else "No"

abc/abc162-b/Main.hs

Lines changed: 7 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,7 @@
1+
-- https://github.com/minoki/my-atcoder-solutions
2+
{-# LANGUAGE TypeApplications #-}
3+
import Data.Int (Int64)
4+
5+
main = do
6+
n <- readLn @Int64
7+
print $ sum [ x | x <- [1..n], x `rem` 3 /= 0, x `rem` 5 /= 0 ]

abc/abc162-c/Main.hs

Lines changed: 10 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,10 @@
1+
-- https://github.com/minoki/my-atcoder-solutions
2+
{-# LANGUAGE TypeApplications #-}
3+
4+
main = do
5+
k <- readLn @Int
6+
print $ sum [ if ab == 1 then k else sum [ gcd ab c | c <- [1..k] ]
7+
| a <- [1..k]
8+
, b <- [1..k]
9+
, let ab = gcd a b
10+
]

abc/abc162-d/Main.hs

Lines changed: 23 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,23 @@
1+
-- https://github.com/minoki/my-atcoder-solutions
2+
{-# LANGUAGE TypeApplications #-}
3+
import Data.Int (Int64)
4+
import qualified Data.ByteString.Char8 as BS
5+
6+
main = do
7+
n <- readLn @Int
8+
s <- BS.getLine
9+
let n_r, n_g, n_b :: Int64
10+
n_r = fromIntegral (BS.count 'R' s)
11+
n_g = fromIntegral (BS.count 'G' s)
12+
n_b = fromIntegral (BS.count 'B' s)
13+
print $
14+
n_r * n_g * n_b
15+
- sum [ 1 :: Int64
16+
| d <- [1..n `div` 2]
17+
, i <- [0..n - 1 - 2 * d]
18+
, let j = i + d
19+
k = j + d -- k <= n - 1
20+
, s `BS.index` i /= s `BS.index` j
21+
, s `BS.index` i /= s `BS.index` k
22+
, s `BS.index` j /= s `BS.index` k
23+
]

abc/abc162-d/Small.hs

Lines changed: 18 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,18 @@
1+
-- https://github.com/minoki/my-atcoder-solutions
2+
{-# LANGUAGE TypeApplications #-}
3+
{-# LANGUAGE BangPatterns #-}
4+
import Data.Int (Int64)
5+
import qualified Data.ByteString.Char8 as BS
6+
7+
main = do
8+
n <- readLn @Int
9+
s <- BS.getLine
10+
print $ sum [ 1 :: Int64
11+
| i <- [0..n-3]
12+
, j <- [i+1..n-2]
13+
, k <- [j+1..n-1]
14+
, s `BS.index` i /= s `BS.index` j
15+
, s `BS.index` i /= s `BS.index` k
16+
, s `BS.index` j /= s `BS.index` k
17+
, j - i /= k - j
18+
]

abc/abc162-e/Main.hs

Lines changed: 54 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,54 @@
1+
-- https://github.com/minoki/my-atcoder-solutions
2+
{-# LANGUAGE TypeApplications #-}
3+
{-# LANGUAGE BangPatterns #-}
4+
{-# LANGUAGE TypeFamilies #-}
5+
import Data.Char (isSpace)
6+
import Data.Int (Int64)
7+
import Data.List (unfoldr)
8+
import Control.Monad
9+
import qualified Data.Vector.Unboxing as U
10+
import qualified Data.Vector.Unboxing.Mutable as UM
11+
import qualified Data.ByteString.Char8 as BS
12+
13+
main = do
14+
[n,k] <- unfoldr (BS.readInt . BS.dropWhile isSpace) <$> BS.getLine
15+
let v :: U.Vector IntMod
16+
v = U.create $ do
17+
v <- UM.replicate (k+1) 0
18+
forM_ [1..k] $ \i -> do
19+
UM.write v i $! fromIntegral (k `quot` i) ^ n
20+
return v
21+
w :: U.Vector IntMod
22+
w = U.create $ do
23+
w <- U.thaw v
24+
forM_ [k,k-1..1] $ \i -> do
25+
s <- sum <$> sequence [ UM.read w j | j <- [2*i,3*i..k] ]
26+
UM.modify w (subtract s) i
27+
return w
28+
print $ sum [ fromIntegral i * w U.! i | i <- [1..k] ]
29+
30+
modulus :: Int64
31+
modulus = 10^9 + 7
32+
33+
newtype IntMod = IntMod { getIntMod :: Int64 } deriving Eq
34+
35+
instance Show IntMod where
36+
show (IntMod x) = show x
37+
38+
instance Num IntMod where
39+
IntMod x + IntMod y = IntMod ((x + y) `rem` modulus)
40+
IntMod x - IntMod y = IntMod ((x - y) `mod` modulus)
41+
IntMod x * IntMod y = IntMod ((x * y) `rem` modulus)
42+
negate (IntMod x) = IntMod (negate x `mod` modulus)
43+
fromInteger x = IntMod (fromInteger (x `mod` fromIntegral modulus))
44+
abs = undefined; signum = undefined
45+
46+
{-# RULES
47+
"fromIntegral/Int64->IntMod" forall (x :: Int64).
48+
fromIntegral x = IntMod (x `mod` modulus)
49+
"fromIntegral/Int->IntMod" forall (x :: Int).
50+
fromIntegral x = IntMod (fromIntegral x `mod` modulus)
51+
#-}
52+
53+
instance U.Unboxable IntMod where
54+
type Rep IntMod = Int64

abc/abc162-e/Naive.hs

Lines changed: 15 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,15 @@
1+
-- https://github.com/minoki/my-atcoder-solutions
2+
{-# LANGUAGE TypeApplications #-}
3+
{-# LANGUAGE BangPatterns #-}
4+
import Data.Char (isSpace)
5+
import Data.Int (Int64)
6+
import Data.List (unfoldr, foldl')
7+
import Control.Monad
8+
import qualified Data.Vector.Unboxed as U
9+
import qualified Data.Vector.Unboxed.Mutable as UM
10+
import qualified Data.ByteString.Char8 as BS
11+
12+
main = do
13+
[n,k] <- unfoldr (BS.readInt . BS.dropWhile isSpace) <$> BS.getLine
14+
print $ sum @[] @Int $ do xs <- replicateM n [1..k]
15+
pure $ foldl' gcd 0 xs

abc/abc162-e/Naive2.hs

Lines changed: 40 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,40 @@
1+
-- https://github.com/minoki/my-atcoder-solutions
2+
{-# LANGUAGE TypeApplications #-}
3+
{-# LANGUAGE BangPatterns #-}
4+
{-# LANGUAGE NumericUnderscores #-}
5+
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
6+
{-# LANGUAGE DerivingStrategies #-}
7+
import Data.Char (isSpace)
8+
import Data.Int (Int64)
9+
import Data.List (unfoldr, foldl')
10+
import Control.Monad
11+
import qualified Data.Vector.Unboxed as U
12+
import qualified Data.Vector.Unboxed.Mutable as UM
13+
import qualified Data.ByteString.Char8 as BS
14+
15+
main = do
16+
[n,k] <- unfoldr (BS.readInt . BS.dropWhile isSpace) <$> BS.getLine
17+
print $ sum $ do xs <- replicateM n [1..k]
18+
pure $ fromIntegral $ foldl' gcd 0 xs
19+
20+
modulus :: Int64
21+
modulus = 1_000_000_007
22+
23+
newtype IntMod = IntMod { getIntMod :: Int64 }
24+
deriving Eq
25+
deriving newtype Show
26+
27+
instance Num IntMod where
28+
IntMod x + IntMod y = IntMod ((x + y) `rem` modulus)
29+
IntMod x - IntMod y = IntMod ((x - y) `mod` modulus)
30+
IntMod x * IntMod y = IntMod ((x * y) `rem` modulus)
31+
negate (IntMod x) = IntMod (negate x `mod` modulus)
32+
fromInteger x = IntMod (fromInteger (x `mod` fromIntegral modulus))
33+
abs = undefined; signum = undefined
34+
35+
{-# RULES
36+
"fromIntegral/Int64->IntMod" forall (x :: Int64).
37+
fromIntegral x = IntMod (x `mod` modulus)
38+
"fromIntegral/Int->IntMod" forall (x :: Int).
39+
fromIntegral x = IntMod (fromIntegral x `mod` modulus)
40+
#-}

abc/abc162-f/Main.hs

Lines changed: 23 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,23 @@
1+
-- https://github.com/minoki/my-atcoder-solutions
2+
{-# LANGUAGE TypeApplications #-}
3+
{-# LANGUAGE BangPatterns #-}
4+
import Data.Char (isSpace)
5+
import Data.Int (Int64)
6+
import qualified Data.Vector.Unboxed as U
7+
import qualified Data.ByteString.Char8 as BS
8+
9+
main = do
10+
n <- readLn @Int
11+
-- 2 <= n <= 2*10^5
12+
xs <- U.map fromIntegral . U.unfoldrN n (BS.readInt . BS.dropWhile isSpace) <$> BS.getLine
13+
let loop :: Int -> Int64 -> Int64 -> Int64 -> (Int64, Int64, Int64)
14+
loop !k !a !b !c
15+
| k > n `quot` 2 = (a, b, c)
16+
| otherwise =
17+
-- k <= n `quot` 2
18+
let a' = a + xs U.! (2*k-2)
19+
b' = max a' (b + xs U.! (2*k-1))
20+
c' = if 2*k < n then max b' (c + xs U.! (2*k)) else b'
21+
in loop (k+1) a' b' c'
22+
(_,y,z) = loop 1 0 0 0
23+
print $ if even n then y else z

0 commit comments

Comments
 (0)