Skip to content

Instantly share code, notes, and snippets.

@meithecatte
Last active December 20, 2020 18:23
Show Gist options
  • Save meithecatte/1482d3780a7ff1b36b0589a5dda6738d to your computer and use it in GitHub Desktop.
Save meithecatte/1482d3780a7ff1b36b0589a5dda6738d to your computer and use it in GitHub Desktop.
·< - a Haskell reverse-engineering challenge on the 2020 hxpCTF
#!/usr/bin/env runhaskell
{-# LANGUAGE OverloadedStrings #-}
import Prelude hiding (replicate, putStrLn)
import Data.List hiding (replicate)
import Data.Tuple
import Data.Ord
import Data.Function
import Data.ByteString (replicate, ByteString)
import Data.ByteString.Char8 (putStrLn, pack)
import Control.Monad
import Control.Arrow
import Control.Applicative
import Crypto.Cipher.AES
import Crypto.Hash.SHA256
import Unsafe.Coerce
c = "\xd7\xc8\x35\x14\xc4\x27\xcd\x6f\x78\x3a\x80\x57\x76\xb0\xfd\x42\x25\xe4\x87\x5f\x99\x28\x87\x0a\x06\xef\x63\x81\x44"
-- infixr 0 $
-- infixr 1 >>> --- flip (.)
-- infixr 1 <<< --- (.)
-- infixr 1 ^>> --- flip (.)
-- infixl 1 &
-- infixr 1 >>=
-- infixl 4 <$>
-- infixl 4 <*>
-- infixl 4 <**>
-- infixr 9 .
main = do
input <- getContents
putStrLn (calculateOutput (read input))
calculateOutput :: [Int] -> ByteString
calculateOutput input = maybe "wrong" (doAES input) (unsafeCoerce (checkInput input))
checkInput :: [Int] -> Bool
checkInput input = and [or (map (\x2 -> x2 input y x) checks)
| x <- [0..39], y <- [0..39]]
indexOf :: Eq a => [a] -> a -> Int
indexOf xs x = unsingle $ elemIndices x xs
where
unsingle [n] = n
mystery4 p x0 x1 a = (indexOf p x1) >= (indexOf p (x0 a))
checks :: [[Int] -> Int -> Int -> Bool]
checks = [
(\ input x y -> mystery4 (nthPerm x) (input !!) y x),
(\ input x y -> (input !! x) == y),
(\ input x y -> mystery4 (nthPerm (40 + y)) (indexOf input) x y)]
lcg :: [Int]
lcg = tail (iterate next 44)
where
next x = (1337 * x + 42) `mod` 400013
lcgChunks :: [[Int]]
lcgChunks = tail $ fst <$> iterate (\(_, x) -> (take 40 x, drop 40 x)) ([], lcg)
randomPermutations :: [[Int]]
randomPermutations = (\x -> sortBy (comparing (x !!)) [0 .. 39]) <$> lcgChunks
nthPerm :: Int -> [Int]
nthPerm n = randomPermutations !! n
doAES :: [Int] -> a -> ByteString
doAES x _ = decryptCTR (initAES (hash (pack (show x)))) (replicate 16 0) c
Sign up for free to join this conversation on GitHub. Already have an account? Sign in to comment