Skip to content

Instantly share code, notes, and snippets.

@SilverTab
Created April 29, 2010 17:58
Show Gist options
  • Save SilverTab/383965 to your computer and use it in GitHub Desktop.
Save SilverTab/383965 to your computer and use it in GitHub Desktop.
-- Simple module for decoding yEnc files...
-- For now it only supports single-part files...enventually... WHO KNOWS! :P
-- By: Jean-Nicolas Jolivet <jeannicolascocoa@gmail.com>
module HYDecoder where
import Data.Char
import System.Environment (getArgs)
import qualified Data.ByteString.Lazy.Char8 as L
import Text.Regex.Posix
import System.IO
import Maybe
import Data.Digest.CRC32
import Numeric
data YEncFile = YEncFile {fileName :: String, fileSize :: Int, fileChecksum :: String, fileData :: L.ByteString}
deriving (Show)
-- Reverse the modulo 256
decodechar :: Int -> Char
decodechar i
| i < 0 = chr (i + 256)
| otherwise = chr i
-- Remove whitespace at the end...
trim :: String -> String
trim [] = []
trim str = takeWhile (\c -> not (isSpace c)) str
-- Decode a pair of character, checking if a char if preceeded by an escape char
decodepair :: (Char, Char) -> Maybe Char
decodepair cs
| snd(cs) == '=' = Nothing
| fst(cs) == '=' = Just (decodechar(ord(snd cs) - 106))
| otherwise = Just (decodechar(ord(snd cs) - 42))
-- Determine if the file is indeed a yEnc file
isYenc :: L.ByteString -> L.ByteString -> Maybe YEncFile
isYenc str fullstr
| isNothing (ofileName str) || isNothing (ofileSize str) || isNothing (ofileChecksum str) = Nothing
| otherwise = Just (YEncFile (fromJust (ofileName str)) (fromJust (ofileSize str)) (fromJust (ofileChecksum str)) (ofileData fullstr))
-- Decode a yEncoded ByteString
decodeByteString :: L.ByteString -> L.ByteString
decodeByteString str = do
let str1 = mapMaybe decodepair (L.zip str(L.tail str))
firstChar = decodechar (ord(L.head str) - 42)
L.pack (firstChar:str1) -- Don't forget that we have to add the first char!
-- Extracts the filename...
ofileName :: L.ByteString -> Maybe String
ofileName str
| null match = Nothing
| otherwise = Just (trim( L.unpack(head(match))))
where match = mrSubList ( str =~ "name=([^\r\n]+)" :: (MatchResult L.ByteString) )
-- Extracts the crc32: crc32=XXXXXX
ofileChecksum :: L.ByteString -> Maybe String
ofileChecksum str
| null match = Nothing
| otherwise = Just (L.unpack(head match) )
where match = mrSubList (str =~ "crc32=([a-zA-Z0-9]+)" :: (MatchResult L.ByteString) )
-- Extracts the filesize...
ofileSize :: L.ByteString -> Maybe Int
ofileSize str =
case L.readInt (head (mrSubList (str =~ "size=([0-9]+)" :: (MatchResult L.ByteString)))) of
Nothing -> Nothing
Just (size, rest) -> Just size
-- Extracts the encoded data
ofileData :: L.ByteString -> L.ByteString
ofileData str = do
let prefix = L.pack "=ybegin"
suffix = L.pack "=yend"
dataStart = dropWhile (\s -> not (L.isPrefixOf prefix s)) (L.lines str)
dirtyData = foldr L.append (L.pack "") ( tail (takeWhile (\s -> not (L.isPrefixOf suffix s)) dataStart) )
L.filter (\c -> c /= '\r' && c /= '\n') dirtyData
-- Take a Yenc file,output a checksum in the console
decodeFile :: YEncFile -> IO()
decodeFile yenc = do
outh <- openFile (fileName yenc) WriteMode
let decodedData = decodeByteString (fileData yenc)
checksum = (showIntAtBase 16 intToDigit (crc32 decodedData) "")
if checksum == (fileChecksum yenc)
then do
L.hPut outh decodedData
hClose outh
putStrLn ("\t" ++ (fileName yenc) ++ " decoded successfully!\n\tChecksum: " ++ checksum)
else putStrLn "\tBad Checksum"
putStrLn "\tDecoding Finished"
-- combine the =ybegin and =yend lines...
combineHeaders :: L.ByteString -> L.ByteString
combineHeaders str = do
L.unlines[(str =~ "=ybegin[^\n\r]+" :: L.ByteString),(str =~ "=yend[^\n\r]+" :: L.ByteString)]
-- Main Function...
main = do
(fileName:_) <- getArgs
contents <- L.readFile fileName
putStrLn "Starting Decoding Process"
let combinedHead = (combineHeaders contents)
print combinedHead
let maybeYenc = isYenc combinedHead contents
if not (isNothing maybeYenc)
then decodeFile (fromJust maybeYenc)
else putStrLn "This doesn't appear to be a yEnc file!"
putStrLn "Bye Bye!"
Sign up for free to join this conversation on GitHub. Already have an account? Sign in to comment