Submission #1990858


Source Code Expand

import qualified Data.ByteString.Char8 as BC
import Data.Maybe (fromJust)
import Data.Array.IO
import Data.List
import Data.Bits
import Control.Monad

type Arr = IOUArray Int Int
type Arr2D = IOUArray (Int, Int) Int
type Mark = IOUArray Int Bool

maxLog = 31

main = do
  [n,m,d] <- map read . words <$> getLine :: IO [Int]
  a <- getIntListBC
  pos <- newListArray (1, n) [1..n] :: IO Arr
  foldM amida pos a
  a'' <- getElems pos
  let l = snd . unzip . sort $ zip a'' [1..n]
  lot <- newListArray (1, n) l :: IO Arr
  mark <- newArray (1, n) False :: IO Mark
  lp <- filter (>0) <$> loop lot mark n 0 1 0
  table <- newArray ((1, 0), (n, maxLog-1)) 0 :: IO Arr2D
  initTable table l 1
  foldM (makeTable table n) pos [0..maxLog-2]
  ans <- newListArray (1, n) [1..n] :: IO Arr
  foldM (solve table n d) ans [0..maxLog-1]
  ans' <- getElems ans
  let l' = snd . unzip . sort $ zip ans' [1..n]
  putStr $ unlines . map show $ l'

printList2D :: Int -> [Int] -> IO ()
printList2D _ []   = return ()
printList2D n list = do
  print $ take n list
  printList2D n $ drop n list

solve :: Arr2D -> Int -> Int -> Arr -> Int -> IO Arr
solve table n i ans k = do
  if shiftR i k .&. 1 == 1
    then do
      ls <- getElems ans
      l <- getLot table k n 1
      update ans l ls
      return ans
    else return ans

update :: Arr -> [Int] -> [Int] -> IO ()
update _   []     []     = return ()
update pos (l:ls) (a:as) = do
  writeArray pos l a
  update pos ls as

initTable :: Arr2D -> [Int] -> Int -> IO ()
initTable table []     _ = return ()
initTable table (i:is) n = do
  writeArray table (n, 0) i
  initTable table is $ n+1

makeTable :: Arr2D -> Int -> Arr -> Int -> IO Arr
makeTable table n pos k = do
  pos' <- getElems pos
  l <- getLot table k n 1
  move pos l pos'
  p <- getElems pos
  let p' = snd . unzip . sort $ zip p [1..n]
  add p' 1
  return pos
  where move :: Arr -> [Int] -> [Int] -> IO ()
        move p []     []     = return ()
        move p (l:ls) (i:is) = do
          writeArray p l i
          move p ls is
        add :: [Int] -> Int -> IO ()
        add []     _ = return ()
        add (p:ps) i = do
          writeArray table (i, k+1) p
          add ps $ i+1

getLot :: Arr2D -> Int -> Int -> Int -> IO [Int]
getLot table k n i
  | n < i = return []
  | otherwise = do
    x <- readArray table (i, k)
    xs <- getLot table k n $ i+1
    return $ x : xs

loop :: Arr -> Mark -> Int -> Int -> Int -> Int -> IO [Int]
loop arr mark n i now count
  | n == i = return []
  | otherwise = do
    isMark <- readArray mark now
    if isMark
      then do
        ls <- loop arr mark n (i + 1) (now + 1) 0
        return $ count : ls
      else do
        writeArray mark now True
        next <- readArray arr now
        loop arr mark n (i + 1) next $ count + 1

amida :: Arr -> Int -> IO Arr
amida arr i = do
  x <- readArray arr i
  y <- readArray arr $ i+1
  writeArray arr i y
  writeArray arr (i+1) x
  return arr

bsToInt :: BC.ByteString -> Int
bsToInt = fst . fromJust . BC.readInt

getIntListBC :: IO [Int]
getIntListBC = map bsToInt . BC.words <$> BC.getLine

Submission Info

Submission Time
Task D - 阿弥陀
User amanuko
Language Haskell (GHC 7.10.3)
Score 100
Code Size 3205 Byte
Status AC
Exec Time 3566 ms
Memory 87036 KB

Judge Result

Set Name Subtask1 Subtask2 Subtask3 Subtask4
Score / Max Score 10 / 10 20 / 20 20 / 20 50 / 50
Status
AC × 9
AC × 18
AC × 18
AC × 29
Set Name Test Cases
Subtask1 sample_1.txt, 01_i.txt, 01_random01.txt, 01_random02.txt, 01_random03.txt, 01_random04.txt, 01_random05.txt, 01_random06.txt, 01_random07.txt
Subtask2 sample_1.txt, sample_2.txt, sample_3.txt, 02_i.txt, 02_p.txt, 02_random01.txt, 02_random02.txt, 02_random03.txt, 02_random04.txt, 02_random05.txt, 02_random06.txt, 02_random07.txt, 02_random08.txt, 02_rp01.txt, 02_rp02.txt, 02_rp03.txt, 02_rp04.txt, 02_rp05.txt
Subtask3 sample_1.txt, sample_2.txt, 03_i.txt, 03_random01.txt, 03_random02.txt, 03_random03.txt, 03_random04.txt, 03_random05.txt, 03_random06.txt, 03_random07.txt, 03_random08.txt, 03_random09.txt, 03_random10.txt, 03_random11.txt, 03_random12.txt, 03_random13.txt, 03_random14.txt, 03_random15.txt
Subtask4 sample_1.txt, sample_2.txt, sample_3.txt, 04_i.txt, 04_p1.txt, 04_p2.txt, 04_random01.txt, 04_random02.txt, 04_random03.txt, 04_random04.txt, 04_random05.txt, 04_random06.txt, 04_random07.txt, 04_random08.txt, 04_random09.txt, 04_random10.txt, 04_random11.txt, 04_random12.txt, 04_random13.txt, 04_rp01.txt, 04_rp02.txt, 04_rp03.txt, 04_rp04.txt, 04_rp05.txt, 04_rp06.txt, 04_rp07.txt, 04_rp08.txt, 04_rp09.txt, 04_rp10.txt
Case Name Status Exec Time Memory
01_i.txt AC 1699 ms 86652 KB
01_random01.txt AC 2 ms 508 KB
01_random02.txt AC 2 ms 508 KB
01_random03.txt AC 2 ms 636 KB
01_random04.txt AC 56 ms 3452 KB
01_random05.txt AC 2752 ms 85372 KB
01_random06.txt AC 3272 ms 84988 KB
01_random07.txt AC 3300 ms 85372 KB
02_i.txt AC 7 ms 1404 KB
02_p.txt AC 9 ms 1404 KB
02_random01.txt AC 2 ms 508 KB
02_random02.txt AC 2 ms 508 KB
02_random03.txt AC 12 ms 1276 KB
02_random04.txt AC 7 ms 1404 KB
02_random05.txt AC 17 ms 1660 KB
02_random06.txt AC 23 ms 2044 KB
02_random07.txt AC 31 ms 2684 KB
02_random08.txt AC 31 ms 2684 KB
02_rp01.txt AC 9 ms 1404 KB
02_rp02.txt AC 9 ms 1404 KB
02_rp03.txt AC 8 ms 1404 KB
02_rp04.txt AC 9 ms 1404 KB
02_rp05.txt AC 9 ms 1404 KB
03_i.txt AC 2 ms 636 KB
03_random01.txt AC 3 ms 1020 KB
03_random02.txt AC 11 ms 1788 KB
03_random03.txt AC 10 ms 1660 KB
03_random04.txt AC 10 ms 1660 KB
03_random05.txt AC 3 ms 1020 KB
03_random06.txt AC 3 ms 1020 KB
03_random07.txt AC 4 ms 1148 KB
03_random08.txt AC 2 ms 1020 KB
03_random09.txt AC 5 ms 1148 KB
03_random10.txt AC 7 ms 1404 KB
03_random11.txt AC 11 ms 1660 KB
03_random12.txt AC 11 ms 1788 KB
03_random13.txt AC 9 ms 1532 KB
03_random14.txt AC 8 ms 1404 KB
03_random15.txt AC 4 ms 1148 KB
04_i.txt AC 1954 ms 86012 KB
04_p1.txt AC 2583 ms 81276 KB
04_p2.txt AC 2067 ms 65276 KB
04_random01.txt AC 1797 ms 50684 KB
04_random02.txt AC 1430 ms 39804 KB
04_random03.txt AC 294 ms 10620 KB
04_random04.txt AC 250 ms 7548 KB
04_random05.txt AC 405 ms 14716 KB
04_random06.txt AC 1987 ms 55676 KB
04_random07.txt AC 1153 ms 33276 KB
04_random08.txt AC 991 ms 29180 KB
04_random09.txt AC 506 ms 14716 KB
04_random10.txt AC 1933 ms 54652 KB
04_random11.txt AC 3524 ms 87036 KB
04_random12.txt AC 3566 ms 84988 KB
04_random13.txt AC 3473 ms 85244 KB
04_rp01.txt AC 2437 ms 85500 KB
04_rp02.txt AC 2438 ms 84348 KB
04_rp03.txt AC 2359 ms 83836 KB
04_rp04.txt AC 2502 ms 87036 KB
04_rp05.txt AC 2387 ms 85884 KB
04_rp06.txt AC 2460 ms 80892 KB
04_rp07.txt AC 2417 ms 81916 KB
04_rp08.txt AC 2569 ms 84348 KB
04_rp09.txt AC 2522 ms 85628 KB
04_rp10.txt AC 2449 ms 83836 KB
sample_1.txt AC 2 ms 508 KB
sample_2.txt AC 2 ms 508 KB
sample_3.txt AC 2 ms 764 KB