Skip to content

Instantly share code, notes, and snippets.

@jjant
Created August 21, 2020 21:16
Show Gist options
  • Save jjant/14506ca564d0ca2563a9bba6a39d3ba6 to your computer and use it in GitHub Desktop.
Save jjant/14506ca564d0ca2563a9bba6a39d3ba6 to your computer and use it in GitHub Desktop.
module Main where
import qualified Data.List as List
import System.Environment
import System.IO
-- | Remove duplicates in sorted (descending order) list
dedupe :: [Int] -> [Int]
dedupe [] = []
dedupe (x : xs) = reverse $ dedupeX [] x xs
where
dedupeX res b [] = b : res
dedupeX res b (c : cs) =
if b == c
then dedupeX res c cs
else dedupeX (b : res) c cs
type Count = Int
-- | Remove duplicates in sorted (descending order) list,
-- | keeping count of how many times each number appeared in the original list
dedupeWithCount :: [Int] -> [(Int, Count)]
dedupeWithCount [] = []
dedupeWithCount (x : xs) = reverse $ dedupeX [] 1 x xs
where
dedupeX :: [(Int, Count)] -> Count -> Int -> [Int] -> [(Int, Count)]
dedupeX res count b [] = (b, count) : res
dedupeX res count b (c : cs) =
if b == c
then dedupeX res (count + 1) c cs
else dedupeX ((b, count) : res) 1 c cs
-- | Returns the ranks alice would have with a given scores
-- | Assumes both lists are in descending order.
aliceRanks :: [Int] -> [(Int, Count)] -> [Int]
aliceranks [] [] = []
aliceranks scores [] = []
aliceRanks scores ((aliceScore, count) : restAliceScores) = go 1 [] (aliceScore, count) restAliceScores scores
where
go :: Int -> [Int] -> (Int, Count) -> [(Int, Count)] -> [Int] -> [Int]
go currentRank aliceRanks (aliceScore, count) [] [] = List.replicate count currentRank ++ aliceRanks
go currentRank aliceRanks (aliceScore, count) aliceScores [] =
List.replicate (List.sum (List.map snd ((aliceScore, count) : aliceScores))) currentRank ++ aliceRanks
go currentRank aliceRanks (aliceScore, count) [] (topScore : restScores) =
if aliceScore >= topScore
then List.replicate count currentRank ++ aliceRanks
else go (currentRank + 1) aliceRanks (aliceScore, count) [] restScores
go currentRank aliceRanks (aliceScore, count) (newAliceScore : restAliceScores) (topScore : restScores) =
if aliceScore >= topScore
then go currentRank (List.replicate count currentRank ++ aliceRanks) newAliceScore restAliceScores (topScore : restScores)
else go (currentRank + 1) aliceRanks (aliceScore, count) (newAliceScore : restAliceScores) restScores
climbingLeaderboard :: [Int] -> [Int] -> [Int]
climbingLeaderboard allScores aliceScores =
aliceRanks (dedupe allScores) (reverse $ dedupeWithCount aliceScores)
---- Misc: Hackerrank boilerplate ----
readMultipleLinesAsStringArray :: Int -> IO [String]
readMultipleLinesAsStringArray 0 = return []
readMultipleLinesAsStringArray n = do
line <- getLine
rest <- readMultipleLinesAsStringArray (n - 1)
return (line : rest)
main :: IO ()
main = do
stdout <- getEnv "OUTPUT_PATH"
fptr <- openFile stdout WriteMode
_ <- readLn :: IO Int
scoresTemp <- getLine
let allScores :: [Int]
allScores = List.map (read :: String -> Int) . words $ scoresTemp
_ <- readLn :: IO Int
aliceTemp <- getLine
let aliceScores :: [Int]
aliceScores = List.map (read :: String -> Int) . words $ aliceTemp
let result = climbingLeaderboard allScores aliceScores
hPutStrLn fptr $ List.intercalate "\n" $ List.map (\x -> show x) $ result
hFlush fptr
hClose fptr
Sign up for free to join this conversation on GitHub. Already have an account? Sign in to comment