Skip to content

Instantly share code, notes, and snippets.

@kwannoel
Last active May 9, 2020 13:44
Show Gist options
  • Save kwannoel/eec46780b4f62aebea3fa4742f29d17e to your computer and use it in GitHub Desktop.
Save kwannoel/eec46780b4f62aebea3fa4742f29d17e to your computer and use it in GitHub Desktop.
-- stack --system-ghc runghc
{- |
Result of pair programming with [bumbleblym](https://github.com/bumbleblym)
He implemented most of the code below and suggested using parsers from base
rather than @getLine@ & @read@ to parse the input.
This increases code modularity and ease of refactoring.
Interesting parts:
- The @countSepBy@ parser
- The @int@ parser
Didn't rely on @read@ to parse strings to integers
__Original problem__
https://open.kattis.com/problems/floodit
You'll have to look through this to get a rough idea of what we're parsing
__Script below doesn't actually solve the problem, just parses inputs__
It is interesting to see how one can bootstrap a parser using built-ins to __base__.
__test parsing with:__
> cat input | stack floodit.hs
__sample input__ (copy this to a file to pipe it in)
4
6
123423
334521
433123
543621
324343
234156
5
12121
21212
12121
21212
12121
5
12345
12345
12345
12345
12345
5
11131
12211
31311
21111
11111
__sample output__
(6,["123423","334521","433123","543621","324343","234156"])
(5,["12121","21212","12121","21212","12121"])
(5,["12345","12345","12345","12345","12345"])
(5,["11131","12211","31311","21111","11111"])
-}
module Main where
import Control.Applicative
import Control.Monad (replicateM, void)
import Data.Foldable (foldl')
import qualified Data.Char as Char
import Text.ParserCombinators.ReadP
type TestCase = ( Int -- ^ size
, Grid
)
type Solution = TestCase
type Color = Char -- ^ "123456"
type Grid = [[Color]]
-- | Parse the input to a list of test cases
parse :: String -> [TestCase]
parse s = fst $ head $ readP_to_S inputP s -- ^ Assume first test case is correct
where
inputP :: ReadP [TestCase] -- ^ Parse a list of test cases
inputP = do
numTestCases <- numTestCasesP <* newline -- ^ Parse number of test cases
-- | Parse list of testcases
countSepBy numTestCases newline $ do
size <- sizeP <* newline
grid <- gridP size
pure (size, grid)
numTestCasesP = int
sizeP = int
-- | Parses a grid
gridP
:: Int -- ^ size
-> ReadP Grid
gridP n = countSepBy n (satisfy (== '\n')) rowP
where
rowP = count n $ satisfy (`elem` "123456")
-- | The following 3 lines of 123 are separated by "\n.\n"
-- 123
-- .
-- 123
-- .
-- 123
--
-- Our end result should be [123, 123, 123]
-- This function helps us do the relevant parsing
--
countSepBy :: Int -- ^ Number of lines
-> ReadP sep -- ^ Parser for separator between lines
-> ReadP a -- ^ Parser for each line
-> ReadP [a] -- ^ Parser which collates the result of parsing each line
countSepBy n sep p = (:) <$> p <*> replicateM (n - 1) (sep *> p)
newline :: ReadP Char
newline = satisfy (== '\n')
int :: ReadP Int
int = f <$> munch1 Char.isDigit
where
f :: String -> Int
f = foldl' (\n x -> n * 10 + fromEnum x - fromEnum '0') 0
solve :: TestCase -> Solution
solve = id
printSolution :: Solution -> IO ()
printSolution = print
main :: IO ()
main = do
inp <- getContents
--let testCases = parse inp
-- Print the solutions
mapM_ (printSolution . solve) $ parse inp
Sign up for free to join this conversation on GitHub. Already have an account? Sign in to comment