Return Styles: Pseud0ch, Terminal, Valhalla, NES, Geocities, Blue Moon. Entire thread

Tripcode decoder?

Name: Anonymous 2007-12-03 19:48

is there anyway to convert a tripcode into the password for that tripcode, im using tripsage and I see that you can put in a word you want to see in a trip code and it produces results of passwords that would produce a tripcode with those letters in it, so if we were to take a complete tripcode someone has and enter it into that field, in theory it should eventually produce the 1 password that produces that tripcode, however i have a core 2 duo e6600 which can run 170,000 crypts per second but with over 10^80 possible combinations(numbers + letters + capital letters + symbols, and 10 characters in a tripcode) it would take litteraly much more than trillions of years to run through every combination. Any other suggestions?

Name: Anonymous 2009-04-07 16:15

{-# INCLUDE <crypt.h> #-}
{-# LANGUAGE ForeignFunctionInterface #-}
module Main (main) where

import Char (chr, ord)
import Foreign.C
import System (getArgs, exitFailure)
import Random
import Text.Regex.Posix
import System.IO.Unsafe (unsafePerformIO)

-- We'll need crypt(3)
foreign import ccall "crypt" crypt :: CString -> CString -> CString

-- Generate the salt
salt :: String -> String
salt t  =
    map f . take 2 . tail $ t ++ "H.."
    where
      f c
        | c `notElem` ['.'..'z'] = '.'
        | c `elem` [':'..'@'] = chr $ ord c + 7
        | c `elem` ['['..'`'] = chr $ ord c + 6
        | otherwise = c

-- The actual tripcode
tripcode :: String -> String
tripcode tr = unsafePerformIO $ do
    trip <- newCString tr
    salt <- newCString $ salt tr
    trip <- peekCString $ crypt trip salt
    return . drop (length trip - 10) $ trip

makeString :: (Char,Char) -> IO String
makeString (a,b) = mapM randomRIO $ replicate 8 (a,b)

showTrip :: IO (Bool,(String,String)) -> IO ()
showTrip t = do
    (b,(s,t)) <- t
    if b then putStrLn $ s ++ " -> " ++ t else return ()

tripTuple :: IO String -> IO (String, String)
tripTuple s = do
    s <- s
    return (s,tripcode s)

matchTrip :: String -> IO (String,String) -> IO (Bool,(String,String))
matchTrip r t = do
    (s,t) <- t
    return (t =~ r,(s,t))

main :: IO ()
main = do
    args <- getArgs
    f args
    where
      f [] = do
          mapM_ (showTrip . matchTrip "." . tripTuple . makeString) $ repeat (' ','~')
      f args = do
          mapM_ (showTrip . (matchTrip $ head args) . tripTuple . makeString) $ repeat (' ','~')

Newer Posts