9462
|
1 |
module Test where
|
|
2 |
|
|
3 |
import Control.Monad
|
|
4 |
import Data.Word
|
|
5 |
import qualified Data.IntSet as IS
|
|
6 |
|
|
7 |
data OP = Sum
|
|
8 |
| Mul
|
|
9 |
| Sub
|
|
10 |
deriving Show
|
|
11 |
|
|
12 |
|
|
13 |
genOps :: Int -> [[OP]]
|
|
14 |
genOps 1 = [[Sum], [Mul], [Sub]]
|
|
15 |
genOps n = [a : as | a <- [Sum, Mul, Sub], as <- genOps (n - 1)]
|
|
16 |
|
|
17 |
|
|
18 |
genPos :: Int -> Int -> [[Int]]
|
|
19 |
genPos m 1 = map (:[]) [-m..m - 1]
|
|
20 |
genPos m n = [a : as | a <- [-m..m - 1], as <- genPos m (n - 1)]
|
|
21 |
|
|
22 |
|
|
23 |
hash :: [Int] -> [OP] -> [Int] -> Int
|
|
24 |
hash poss op s = foldl applyOp s' (zip ss op)
|
|
25 |
where
|
|
26 |
applyOp v (n, Sum) = (v + n) `mod` 256
|
|
27 |
applyOp v (n, Mul) = (v * n) `mod` 256
|
|
28 |
applyOp v (n, Sub) = (v - n) `mod` 256
|
|
29 |
(s' : ss) = map (\p -> if p >= 0 then s !! p else s !! (l + p)) poss
|
|
30 |
l = length s
|
|
31 |
|
|
32 |
|
|
33 |
test = do
|
|
34 |
a <- liftM lines getContents
|
|
35 |
let w = minimum $ map length a
|
|
36 |
let opsNum = 4
|
|
37 |
let opsList = genOps (opsNum - 1)
|
|
38 |
let posList = genPos w opsNum
|
|
39 |
let target = length a
|
|
40 |
let wordsList = map (map fromEnum) a
|
|
41 |
let hashedSize = IS.size . IS.fromList
|
|
42 |
print $ length a
|
|
43 |
putStrLn . unlines . map show $ filter (\l -> fst l == length a) $ [(hs, (p, o)) | p <- posList, o <- opsList, let hs = hashedSize . map (hash p o) $ wordsList]
|
|
44 |
|
|
45 |
didIunderstand' = do
|
|
46 |
a <- liftM lines getContents
|
|
47 |
print . IS.size . IS.fromList . map (testHash . map fromEnum) $ a
|
|
48 |
where
|
|
49 |
testHash s = let l = length s in
|
|
50 |
(s !! (l - 2) * s !! 1) + s !! (l - 1) - s !! 0
|