Skip to content

Instantly share code, notes, and snippets.

@pedrofurla
Created February 21, 2015 20:01
Show Gist options
  • Select an option

  • Save pedrofurla/1954cd14e6abc97eb53a to your computer and use it in GitHub Desktop.

Select an option

Save pedrofurla/1954cd14e6abc97eb53a to your computer and use it in GitHub Desktop.
{-
From: https://gist.github.com/pedrofurla/12516a6998ca39520b14
Re-interpretation of the problem:
- An imaginary room of size N x M,
- Contains a robot that can move one unit (of the above scale) at a time.
- Attempting to cross the boundaries of the room has no effect.
- Certain positions contains patchs of dirty. If the robot gets to that position it is cleansed.
Program organization:
- Data types and aliases
- Movement primitives
- Parsing primities
- program setup and running
- less relevant helper functions
Implementation observations:
- All non-total functions were "left" non-total making the program fail fast for invalid inputs. No requirement for error messages where given, and adding them borders triviallity.
- Storing the dirty patches and the cleansed patches uses a Data.Set.Set, which gives O(log n) lookups and prevents repetition.
-}
import Control.Applicative
import qualified Data.Set as S
import Data.Char(isNumber, isAlpha)
import System.Environment
data Bounds = Bounds Int Int -- Right top coordinates, max x and y
deriving Show
data Coord = Coord Int Int -- coordinates as in (x, y)
deriving (Show, Eq, Ord)
type DirtySpots = S.Set Coord -- Represent existing and visited dirty spots. Todo: consider `newtype`s
type CleansedSpots = S.Set Coord
-- Translates the given Coord by given Ints bounded by given Bounds, see comments below
boundedTranslation ::
Int -> -- Translation amount in the horizontal coordinates
Int -> -- Translation amount in the vertical coordinates
Bounds -> -- Maximum horizontal and vertical coordinates
Coord -> -- Initial coordinates
Coord -- Final coordinates bounds by (0,0) and Bounds coordinates
boundedTranslation dx dy (Bounds maxx maxy) (Coord x0 y0) =
let
bound d b = if (d >= 0) then min b else max 0
in
Coord (bound dx maxx $ x0 + dx) (bound dy maxy $ y0 + dy)
-- Movements --
north,south,east,west :: Bounds -> Coord -> Coord
north = boundedTranslation 0 1
south = boundedTranslation 0 (-1)
east = boundedTranslation 1 0
west = boundedTranslation (-1) 0
readMove :: Char -> Bounds -> Coord -> Coord -- TODO an ADT for NSEW would be better than Char...
readMove s
| s == 'N' = north
| s == 'S' = south
| s == 'E' = east
| s == 'W' = west
readMoves :: String -> Bounds -> [Coord -> Coord]
readMoves = sequence . map readMove
-- Todo, the next two functions are basically the same, abstract then out
readBounds :: String -> Bounds
readBounds s =
let (x, y) = break2 (==' ') s
in Bounds ((read x :: Int) - 1) ((read y :: Int) - 1)
readCoord :: String -> Coord
readCoord s =
let (x, y) = break2 (==' ') s
in Coord (read x) (read y)
-- Given the Set of dirty spots, returns a function that processes one movement
-- and stores the visit to a dirty spot
processMove ::
DirtySpots -> -- dirty spots
(Coord -> Coord) -> -- the movement function
(Coord, CleansedSpots) -> -- a initial coordinate and initial state of the visited spots
(Coord, CleansedSpots) -- a new location and a new state of visited
processMove dirtySpots move (c0, cleansedSpots) =
let c1 = move c0 in
(c1, cleanDirty c1 dirtySpots cleansedSpots)
cleanDirty :: Coord -> DirtySpots -> CleansedSpots -> CleansedSpots
cleanDirty c dirtySpots cleansedSpots =
if S.member c dirtySpots then S.insert c cleansedSpots else cleansedSpots
-- Given the lines of the files, sets the program up
setup ::
[String] -> -- Lines of the file
(
Coord, -- Initial position
DirtySpots, -- Dirty spots
[Coord -> Coord] -- Movements
)
setup lines =
let
(boundStr : startPosStr : ls) = lines
(dirtySpotsStrs, movesStrs) = break (isAlpha . head) ls
bounds = readBounds boundStr
startPos = readCoord startPosStr
dirtySpots = foldr (S.insert . readCoord) S.empty dirtySpotsStrs
moves = readMoves (head movesStrs) bounds
in (startPos, dirtySpots, moves)
innerRun s = do
contents <- readFile s
let
(startPos, dirtySpots, moves) = setup $ lines contents
initialCleansedSpots = cleanDirty startPos dirtySpots S.empty
(finalPos, cleansedSpots) = foldl (flip $ processMove dirtySpots) (startPos, initialCleansedSpots) $ moves
return (finalPos, cleansedSpots)
runWith s = do
(Coord xf yf, cleansedSpots) <- innerRun s
let cleansed = S.size cleansedSpots
putStrLn $ (show xf) ++ " " ++ (show yf) -- could use printf here, but... bah
putStrLn $ (show cleansed)
run = runWith "input.txt"
main :: IO ()
main = do
(file : _) <- getArgs
runWith file
-- Like Data.List.break but excludes the separation predicate
break2 :: (a -> Bool) -> [a] -> ([a],[a])
break2 p as =
let (as0, as1) = break p as
in (as0, dropWhile p as1)
Sign up for free to join this conversation on GitHub. Already have an account? Sign in to comment