Day 10 - condensed a lot of functions and used normal lists instead of Seq
This commit is contained in:
parent
a96ab19024
commit
a44830ae8d
52
10.hs
52
10.hs
|
@ -1,54 +1,30 @@
|
||||||
import Data.List.Split (splitOn)
|
import Data.List.Split (splitOn, chunksOf)
|
||||||
import Data.Sequence (Seq, update, fromList)
|
|
||||||
import qualified Data.Sequence as S (lookup)
|
|
||||||
import Data.Char (ord)
|
import Data.Char (ord)
|
||||||
import Data.Bits (xor)
|
import Data.Bits (xor)
|
||||||
import Data.Foldable (toList)
|
import Text.Printf (printf)
|
||||||
import Numeric (showHex)
|
|
||||||
|
|
||||||
type Ring = Seq Int
|
|
||||||
type Position = Int
|
|
||||||
type Skip = Int
|
|
||||||
type Length = Int
|
type Length = Int
|
||||||
type State = (Ring, Position, Skip)
|
type State = ([Int], Int, Int)
|
||||||
|
|
||||||
(%) = mod
|
(%) = mod
|
||||||
|
|
||||||
unsafeLookup :: Int -> Seq Int -> Int
|
|
||||||
unsafeLookup index seq =
|
|
||||||
case S.lookup index seq of
|
|
||||||
Just i -> i
|
|
||||||
|
|
||||||
twist :: State -> Length -> State
|
twist :: State -> Length -> State
|
||||||
twist (ring, position, skip) len =
|
twist (ring, position, skip) len =
|
||||||
let end = position + len - 1
|
let rotated = slice position 256 $ cycle ring
|
||||||
positions = map (% 256) [position..end]
|
twisted = (reverse $ take len rotated) ++ drop len rotated
|
||||||
posRev = zip positions $ reverse positions
|
newRing = slice (256 - position) 256 $ cycle twisted
|
||||||
newRing = foldl (\currRing (pos, rev) -> update pos (unsafeLookup rev ring) currRing) ring posRev
|
in (newRing, (position + len + skip) % 256, skip + 1)
|
||||||
in (newRing, (end + skip + 1) % 256, skip + 1)
|
where slice start amount = take amount . drop start
|
||||||
|
|
||||||
hash :: [Length] -> State -> State
|
hash :: [Length] -> State -> State
|
||||||
hash lengths state = foldl twist state lengths
|
hash lengths state = foldl twist state lengths
|
||||||
|
|
||||||
condense :: [Int] -> [Int]
|
|
||||||
condense [] = []
|
|
||||||
condense ns =
|
|
||||||
let block = foldr xor 0 $ take 16 ns
|
|
||||||
in block : (condense $ drop 16 ns)
|
|
||||||
|
|
||||||
showHexPrepended :: Int -> (String -> String)
|
|
||||||
showHexPrepended n
|
|
||||||
| n < 15 = showHex 0 . showHex n
|
|
||||||
| otherwise = showHex n
|
|
||||||
|
|
||||||
main :: IO ()
|
main :: IO ()
|
||||||
main = do
|
main = do
|
||||||
input <- readFile "10.txt"
|
input <- readFile "10.txt"
|
||||||
let lengths = map read $ splitOn "," input
|
let lengths = map read $ splitOn "," input
|
||||||
newLengths = map ord input ++ [17, 31, 73, 47, 23]
|
newLengths = map ord input ++ [17, 31, 73, 47, 23]
|
||||||
(hashed, _, _) = hash lengths (fromList [0..255], 0, 0)
|
(hashed, _, _) = hash lengths ([0..255], 0, 0)
|
||||||
(sparseHash, _, _) = iterate (hash newLengths) (fromList [0..255], 0, 0) !! 64
|
(sparseHash, _, _) = iterate (hash newLengths) ([0..255], 0, 0) !! 64
|
||||||
condensedHash = condense $ toList sparseHash
|
hexString = concat . map (printf "%02x" . foldr xor 0) . chunksOf 16 $ sparseHash :: String
|
||||||
hexString = foldr (\digit str -> showHexPrepended digit $ str) "" condensedHash
|
print $ hashed !! 0 * hashed !! 1
|
||||||
print $ (unsafeLookup 0 hashed) * (unsafeLookup 1 hashed)
|
print $ hexString
|
||||||
print $ hexString
|
|
Loading…
Reference in New Issue