Regression atm, Moved from Unicode/Utf8 to ByteString so binary data is encoded correctly. WIP

This commit is contained in:
Stefan Friese 2024-06-07 18:09:20 +02:00
parent faf12b64f1
commit fbb10d0edf
15 changed files with 443 additions and 291 deletions

View File

@ -1,21 +1,23 @@
#!/usr/bin/env runhaskell #!/usr/bin/env runhaskell
{-# LANGUAGE DeriveDataTypeable #-} {-# LANGUAGE DeriveDataTypeable #-}
module Main where module Main where
import System.Console.CmdArgs import System.Console.CmdArgs
import Control.Arrow --import Control.Arrow
import Data.ByteString.UTF8 as BSU -- from utf8-string --import Data.ByteString.UTF8 as BSU -- from utf8-string
import qualified Data.ByteString.Char8 as C --import qualified Data.ByteString.Char8 as C
import Text.Regex.TDFA import qualified Data.ByteString as B
import Encoding.Base2 (enc2, dec2) import qualified Data.ByteString.Char8 as BC
import Encoding.Base8 (enc8, dec8) --import Text.Regex.TDFA
--import Encoding.Base2 (enc2, dec2)
--import Encoding.Base8 (enc8, dec8)
import Encoding.Base10 (enc10, dec10) import Encoding.Base10 (enc10, dec10)
import Encoding.Base16 (enc16, dec16) import Encoding.Base16 (enc16, dec16)
import Encoding.Base32 (enc32, dec32) import Encoding.Base32 (enc32, dec32)
import Encoding.Base45 (enc45, dec45) --import Encoding.Base45 (enc45, dec45)
import Encoding.Base58 (enc58, dec58) import Encoding.Base58 (enc58, dec58)
import Encoding.Base62 (enc62, dec62) --import Encoding.Base62 (enc62, dec62)
import Encoding.Base64 (enc64, dec64, enc64url, dec64url) import Encoding.Base64 (enc64, dec64, enc64url, dec64url)
import Encoding.Base85 (enc85, dec85) import Encoding.Base85 (enc85, dec85)
import Encoding.Base91 (enc91, dec91) import Encoding.Base91 (enc91, dec91)
@ -24,131 +26,131 @@ import Encoding.Xx (encxx, decxx)
import Encoding.QuotedPrintable (encqp, decqp) import Encoding.QuotedPrintable (encqp, decqp)
import Encoding.UnixToUnix (encuu, decuu) import Encoding.UnixToUnix (encuu, decuu)
import Encoding.Yenc (ency, decy) import Encoding.Yenc (ency, decy)
import Encoding.Rotate (rotate) --import Encoding.Rotate (rotate)
data Based = Decode { data Based = Decode {
b91 :: Bool, b91 :: Bool,
b85 :: Bool, b85 :: Bool,
b64 :: Bool, b64 :: Bool,
b64url :: Bool, b64url :: Bool,
url :: Bool, url :: Bool,
b62 :: Bool, -- b62 :: Bool,
b58 :: Bool, b58 :: Bool,
b45 :: Bool, -- b45 :: Bool,
b32 :: Bool, b32 :: Bool,
b16 :: Bool, b16 :: Bool,
b10 :: Bool, b10 :: Bool,
b8 :: Bool, -- b8 :: Bool,
b2 :: Bool, -- b2 :: Bool,
qp :: Bool, qp :: Bool,
uu :: Bool, uu :: Bool,
xx :: Bool, xx :: Bool,
yenc :: Bool, yenc :: Bool
rot :: Maybe Int, -- rot :: Maybe Int,
solve :: Bool -- solve :: Bool
} }
| Encode { | Encode {
b91 :: Bool, b91 :: Bool,
b85 :: Bool, b85 :: Bool,
b64 :: Bool, b64 :: Bool,
b64url :: Bool, b64url :: Bool,
url :: Bool, url :: Bool,
b62 :: Bool, -- b62 :: Bool,
b58 :: Bool, b58 :: Bool,
b45 :: Bool, -- b45 :: Bool,
b32 :: Bool, b32 :: Bool,
b16 :: Bool, b16 :: Bool,
b10 :: Bool, b10 :: Bool,
b8 :: Bool, -- b8 :: Bool,
b2 :: Bool, -- b2 :: Bool,
qp :: Bool, qp :: Bool,
uu :: Bool, uu :: Bool,
xx :: Bool, xx :: Bool,
yenc :: Bool, yenc :: Bool
rot :: Maybe Int -- rot :: Maybe Int
} }
deriving(Show, Data, Typeable) deriving(Show, Data, Typeable)
-- helper functions ---- helper functions
-- convertToByteString :: String -> Either String C.ByteString ---- convertToByteString :: String -> Either String C.ByteString
-- convertToByteString str = ---- convertToByteString str =
-- case BSU.fromString str of ---- case BSU.fromString str of
-- Just bs -> Right bs ---- Just bs -> Right bs
-- Nothing -> Left "Failed to convert string to ByteString." -- -- Nothing -> Left "Failed to convert string to ByteString."
-- decodeFromBase91 :: String -> Either String C.ByteString ---- decodeFromBase91 :: String -> Either String C.ByteString
-- decodeFromBase91 decoded = ---- decodeFromBase91 decoded =
-- case B91.decode of ---- case B91.decode of
-- decoded | C.null decoded -> Left "Failed to decode from base91" ---- decoded | C.null decoded -> Left "Failed to decode from base91"
-- | otherwise -> Right decoded ---- | otherwise -> Right decoded
binToInt :: [Int] -> Int --binToInt :: [Int] -> Int
binToInt [] = 0 --binToInt [] = 0
binToInt (x : xs) = x + 2 * binToInt xs --binToInt (x : xs) = x + 2 * binToInt xs
octToInt :: [Int] -> Int --octToInt :: [Int] -> Int
octToInt [] = 0 --octToInt [] = 0
octToInt (x : xs) = x + 8 * octToInt xs --octToInt (x : xs) = x + 8 * octToInt xs
-- base functions ---- base functions
-- without the show func, sequences like \n will not be shown as characters but will be executed as newline ---- without the show func, sequences like \n will not be shown as characters but will be executed as newline
base91Regex = "^[!-~]*$" --base91Regex = "^[!-~]*$"
base85Regex = "^[0-9A-Za-z!#$%&()*+,-;<=>?@^_`{|}~]+$" --base85Regex = "^[0-9A-Za-z!#$%&()*+,-;<=>?@^_`{|}~]+$"
-- base85Regex = "^[A-Za-u0-9!\"#$%&((*+,-./;:<=@[]\\`]*$" ---- base85Regex = "^[A-Za-u0-9!\"#$%&((*+,-./;:<=@[]\\`]*$"
base64Regex = "^([A-Za-z0-9+/]{4})*([A-Za-z0-9+/]{3}=|[A-Za-z0-9+/]{2}==)?$" --base64Regex = "^([A-Za-z0-9+/]{4})*([A-Za-z0-9+/]{3}=|[A-Za-z0-9+/]{2}==)?$"
base58Regex = "^[1-9A-HJ-NP-Za-km-z]+$" -- incorrect --base58Regex = "^[1-9A-HJ-NP-Za-km-z]+$" -- incorrect
base32Regex = "^(?:[A-Z2-7]{8})*(?:[A-Z2-7]{2}={6}|[A-Z2-7]{4}={4}|[A-Z2-7]{5}={3}|[A-Z2-7]{7}=)?$" --base32Regex = "^(?:[A-Z2-7]{8})*(?:[A-Z2-7]{2}={6}|[A-Z2-7]{4}={4}|[A-Z2-7]{5}={3}|[A-Z2-7]{7}=)?$"
base16Regex = "^[0-9A-FXx]*$" --base16Regex = "^[0-9A-FXx]*$"
base10Regex = "^[0-9]*$" --base10Regex = "^[0-9]*$"
base8Regex = "^[0-7]*$" --base8Regex = "^[0-7]*$"
base2Regex = "^[01]*$" --base2Regex = "^[01]*$"
urlRegex = "^[a-zA-Z0-9%]*$" --urlRegex = "^[a-zA-Z0-9%]*$"
solveEnc :: String -> String --solveEnc :: String -> String
solveEnc input = --solveEnc input =
let isBase91 = BSU.fromString input =~ base91Regex :: Bool -- let isBase91 = BSU.fromString input =~ base91Regex :: Bool
isBase85 = BSU.fromString input =~ base85Regex :: Bool -- isBase85 = BSU.fromString input =~ base85Regex :: Bool
isBase64 = BSU.fromString input =~ base64Regex :: Bool -- isBase64 = BSU.fromString input =~ base64Regex :: Bool
isBase58 = BSU.fromString input =~ base58Regex :: Bool -- isBase58 = BSU.fromString input =~ base58Regex :: Bool
isBase32 = BSU.fromString input =~ base32Regex :: Bool -- isBase32 = BSU.fromString input =~ base32Regex :: Bool
isBase16 = BSU.fromString input =~ base16Regex :: Bool -- isBase16 = BSU.fromString input =~ base16Regex :: Bool
isBase10 = BSU.fromString input =~ base10Regex :: Bool -- isBase10 = BSU.fromString input =~ base10Regex :: Bool
isBase8 = BSU.fromString input =~ base8Regex :: Bool -- isBase8 = BSU.fromString input =~ base8Regex :: Bool
isBase2 = BSU.fromString input =~ base2Regex :: Bool -- isBase2 = BSU.fromString input =~ base2Regex :: Bool
isURL = BSU.fromString input =~ urlRegex :: Bool -- isURL = BSU.fromString input =~ urlRegex :: Bool
base91Result = if isBase91 then "\nTrying base91:\n" ++ dec91 input else "" -- base91Result = if isBase91 then "\nTrying base91:\n" ++ dec91 input else ""
base85Result = if isBase85 then "\nTrying base85:\n" ++ dec85 input else "" -- base85Result = if isBase85 then "\nTrying base85:\n" ++ dec85 input else ""
base64Result = if isBase64 then "\nTrying base64:\n" ++ dec64 input else "" -- base64Result = if isBase64 then "\nTrying base64:\n" ++ dec64 input else ""
base58Result = if isBase58 then "\nTrying base58:\n" ++ dec58 input else "" -- base58Result = if isBase58 then "\nTrying base58:\n" ++ dec58 input else ""
base32Result = if isBase64 then "\nTrying base32:\n" ++ dec32 input else "" -- base32Result = if isBase64 then "\nTrying base32:\n" ++ dec32 input else ""
base16Result = if isBase16 then "\nTrying base16:\n" ++ dec16 input else "" -- base16Result = if isBase16 then "\nTrying base16:\n" ++ dec16 input else ""
base10Result = if isBase10 then "\nTrying base10:\n" ++ dec10 input else "" -- base10Result = if isBase10 then "\nTrying base10:\n" ++ dec10 input else ""
base2Result = if isBase2 then "\nTrying base2:\n" ++ dec2 input else "" -- base2Result = if isBase2 then "\nTrying base2:\n" ++ dec2 input else ""
base8Result = if isBase8 then "\nTrying base8:\n" ++ dec8 input else "" -- base8Result = if isBase8 then "\nTrying base8:\n" ++ dec8 input else ""
urlResult = if isURL then "\nTrying URL decode:\n" ++ decurl input else "" -- urlResult = if isURL then "\nTrying URL decode:\n" ++ decurl input else ""
results = filter (not . null) [base91Result, base85Result, base64Result, base58Result, base32Result, base16Result, base10Result, base8Result, base2Result, urlResult] -- results = filter (not . null) [base91Result, base85Result, base64Result, base58Result, base32Result, base16Result, base10Result, base8Result, base2Result, urlResult]
in -- in
if null results -- if null results
then "Not able to solve the encoding.\n" -- then "Not able to solve the encoding.\n"
else unlines results -- else unlines results
-- -- --
-- | input =~ base64Regex = dec64 input -- -- | input =~ base64Regex = dec64 input
-- | input =~ base32Regex = dec32 input -- -- | input =~ base32Regex = dec32 input
-- | otherwise = "Cannot decode: " ++ input -- -- | otherwise = "Cannot decode: " ++ input
-- -- --
-- if BSU.fromString input =~ base64Regex :: Bool -- -- if BSU.fromString input =~ base64Regex :: Bool
-- then dec64 input -- -- then dec64 input
-- else "Not Base64.\n" -- -- else "Not Base64.\n"
-- ++ if BSU.fromString input =~ base32Regex :: Bool -- -- ++ if BSU.fromString input =~ base32Regex :: Bool
-- then dec32 input -- -- then dec32 input
-- else "Not able to solve the encoding.\n" -- -- else "Not able to solve the encoding.\n"
-- optionHandler :: EncodeOptions -> Text -> Text optionHandler :: Based -> B.ByteString -> B.ByteString
optionHandler Decode{b91=True} = dec91 optionHandler Decode{b91=True} = dec91
optionHandler Encode{b91=True} = enc91 optionHandler Encode{b91=True} = enc91
optionHandler Decode{b85=True} = dec85 optionHandler Decode{b85=True} = dec85
@ -159,22 +161,22 @@ optionHandler Decode{b64url=True} = dec64url
optionHandler Encode{b64url=True} = enc64url optionHandler Encode{b64url=True} = enc64url
optionHandler Decode{url=True} = decurl optionHandler Decode{url=True} = decurl
optionHandler Encode{url=True} = encurl optionHandler Encode{url=True} = encurl
optionHandler Decode{b62=True} = dec62 --optionHandler Decode{b62=True} = dec62
optionHandler Encode{b62=True} = enc62 --optionHandler Encode{b62=True} = enc62
optionHandler Decode{b58=True} = dec58 optionHandler Decode{b58=True} = dec58
optionHandler Encode{b58=True} = enc58 optionHandler Encode{b58=True} = enc58
optionHandler Decode{b45=True} = dec45 --optionHandler Decode{b45=True} = dec45
optionHandler Encode{b45=True} = enc45 --optionHandler Encode{b45=True} = enc45
optionHandler Decode{b32=True} = dec32 optionHandler Decode{b32=True} = dec32
optionHandler Encode{b32=True} = enc32 optionHandler Encode{b32=True} = enc32
optionHandler Decode{b16=True} = dec16 optionHandler Decode{b16=True} = dec16
optionHandler Encode{b16=True} = enc16 optionHandler Encode{b16=True} = enc16
optionHandler Decode{b10=True} = dec10 optionHandler Decode{b10=True} = dec10
optionHandler Encode{b10=True} = enc10 optionHandler Encode{b10=True} = enc10
optionHandler Decode{b8=True} = dec8 --optionHandler Decode{b8=True} = dec8
optionHandler Encode{b8=True} = enc8 --optionHandler Encode{b8=True} = enc8
optionHandler Decode{b2=True} = dec2 --optionHandler Decode{b2=True} = dec2
optionHandler Encode{b2=True} = enc2 --optionHandler Encode{b2=True} = enc2
optionHandler Decode{qp=True} = decqp optionHandler Decode{qp=True} = decqp
optionHandler Encode{qp=True} = encqp optionHandler Encode{qp=True} = encqp
optionHandler Encode{uu=True} = encuu optionHandler Encode{uu=True} = encuu
@ -183,54 +185,108 @@ optionHandler Decode{xx=True} = decxx
optionHandler Encode{xx=True} = encxx optionHandler Encode{xx=True} = encxx
optionHandler Decode{yenc=True} = decy optionHandler Decode{yenc=True} = decy
optionHandler Encode{yenc=True} = ency optionHandler Encode{yenc=True} = ency
optionHandler Encode{rot=Just n} = rotate n --optionHandler Encode{rot=Just n} = rotate n
optionHandler Decode{rot=Just n} = rotate n --optionHandler Decode{rot=Just n} = rotate n
optionHandler Decode{solve=True} = solveEnc --optionHandler Decode{solve=True} = solveEnc
decodeMode :: Based decodeMode :: Based
decodeMode = Decode { decodeMode = Decode {
b91 = def &= help "decode base91", b91 = def &= help "decode base91",
b85 = def &= help "decode base85", b85 = def &= help "decode base85",
b64 = def &= help "decode base64", b64 = def &= help "decode base64",
b64url = def &= help "decode base64Url", b64url = def &= help "decode base64Url",
url = def &= help "decode URI", url = def &= help "decode URI",
b62 = def &= help "decode base62", -- b62 = def &= help "decode base62",
b58 = def &= help "decode base58", b58 = def &= help "decode base58",
b45 = def &= help "decode base45", -- b45 = def &= help "decode base45",
b32 = def &= help "decode base32", b32 = def &= help "decode base32",
b16 = def &= help "decode base16", b16 = def &= help "decode base16",
b10 = def &= help "decode decimal from hex", b10 = def &= help "decode decimal from hex",
b8 = def &= help "decode octal from hex", -- b8 = def &= help "decode octal from hex",
b2 = def &= help "decode binary from hex", -- b2 = def &= help "decode binary from hex",
qp = def &= help "decode quoted-printable", qp = def &= help "decode quoted-printable",
uu = def &= help "decode uu", uu = def &= help "decode uu",
xx = def &= help "decode xx", xx = def &= help "decode xx",
yenc = def &= help "decode yEncode", yenc = def &= help "decode yEncode"
rot = def &= help "rotate characters by n positions", -- rot = def &= help "rotate characters by n positions",
solve = def &= help "solve encoding" -- solve = def &= help "solve encoding"
} &= help "Decode chosen base" &=auto } &= help "Decode chosen base" &=auto
encodeMode :: Based encodeMode :: Based
encodeMode = Encode { encodeMode = Encode {
b91 = def &= help "encode base91", b91 = def &= help "encode base91",
b85 = def &= help "encode base85", b85 = def &= help "encode base85",
b64 = def &= help "encode base64", b64 = def &= help "encode base64",
b64url = def &= help "encode base64Url", b64url = def &= help "encode base64Url",
url = def &= help "encode URI", url = def &= help "encode URI",
b62 = def &= help "encode base62", -- b62 = def &= help "encode base62",
b58 = def &= help "encode base58", b58 = def &= help "encode base58",
b45 = def &= help "encode base45", -- b45 = def &= help "encode base45",
b32 = def &= help "encode base32", b32 = def &= help "encode base32",
b16 = def &= help "encode base16", b16 = def &= help "encode base16",
b10 = def &= help "encode base10 to hex", b10 = def &= help "encode base10 to hex",
b8 = def &= help "encode octal to hex", -- b8 = def &= help "encode octal to hex",
b2 = def &= help "encode binary to hex", -- b2 = def &= help "encode binary to hex",
qp = def &= help "encode quoted-printable", qp = def &= help "encode quoted-printable",
uu = def &= help "encode uu", uu = def &= help "encode uu",
xx = def &= help "encode xx", xx = def &= help "encode xx",
yenc = def &= help "encode yEncode", yenc = def &= help "encode yEncode"
rot = def &= help "rotate characters by n positions" -- rot = def &= help "rotate characters by n positions"
} &= help "Encode chosen base" } &= help "Encode chosen base"
--main :: IO()
--main = cmdArgs (modes[decodeMode, encodeMode] &= help "Based, when Cyberchef doesn't cut it.\nTo see every parameter of every mode use --help=all" &= program "based" &= summary "based v0.4") >>= interact . optionHandler
--
main :: IO() main :: IO()
main = cmdArgs (modes[decodeMode, encodeMode] &= help "Based, when Cyberchef doesn't cut it.\nTo see every parameter of every mode use --help=all" &= program "based" &= summary "based v0.4") >>= interact . optionHandler main = do
args <- cmdArgs(modes[decodeMode, encodeMode] &= help "Based, Binary to text encoding.\nTo see arguments of encode and decode modes use --help=all" &= program "based" &= summary "based v0.4")
input <- B.getContents
B.putStr $ optionHandler args input
-- #!/usr/bin/env runhaskell
-- {-# LANGUAGE DeriveDataTypeable #-}
-- module Main where
-- import System.Console.CmdArgs
-- import qualified Data.ByteString as B
-- import qualified Data.ByteString.Base64 as B64
-- import qualified Data.ByteString.Char8 as BC
-- data Based = Decode { b64 :: Bool }
-- | Encode { b64 :: Bool }
-- deriving (Show, Data, Typeable)
-- -- Function to decode from Base64
-- dec64 :: B.ByteString -> B.ByteString
-- dec64 input = case B64.decode input of
-- Right byteString -> byteString
-- Left _ -> BC.pack "Error: Invalid Base64 input"
-- -- Function to encode to Base64
-- enc64 :: B.ByteString -> B.ByteString
-- enc64 = B64.encode
-- Handle the option to encode or decode
-- optionHandler :: Based -> B.ByteString -> B.ByteString
-- optionHandler Decode { b64 = True } = dec64
-- optionHandler Encode { b64 = True } = enc64
-- decodeMode :: Based
-- decodeMode = Decode { b64 = def &= help "decode base64" }
-- &= help "Decode chosen base" &= auto
-- encodeMode :: Based
-- encodeMode = Encode { b64 = def &= help "encode base64" }
-- &= help "Encode chosen base"
-- main :: IO ()
-- main = do
-- -- Read command line arguments
-- args <- cmdArgs (modes [decodeMode, encodeMode] &= help "Based.\nTo see every parameter of every mode use --help=all" &= program "based" &= summary "based v0.4")
-- -- Read input from stdin
-- input <- B.getContents
-- -- Process the input according to the command line arguments
-- B.putStr $ optionHandler args input

View File

@ -55,6 +55,7 @@ executable based
cmdargs, cmdargs,
utf8-string, utf8-string,
bytestring, bytestring,
-- base64-bytestring,
regex-tdfa regex-tdfa
-- sandi, -- sandi,
-- base62, -- base62,

View File

@ -3,12 +3,16 @@ module Encoding.Base10
, dec10 , dec10
) where ) where
import qualified Data.ByteString.Char8 as C import Data.ByteString as B
import qualified Data.ByteString.Char8 as BC
import Data.Char (ord, chr, digitToInt, intToDigit) import Data.Char (ord, chr, digitToInt, intToDigit)
dec10 :: String -> String -- dec10 :: String -> String
dec10 = map (chr . read) . words -- dec10 = map (chr . read) . words
dec10 :: B.ByteString -> B.ByteString
dec10 = BC.pack . Prelude.map (chr . read) . words . BC.unpack
enc10 :: String -> String -- enc10 :: String -> String
enc10 = unwords . map (show . ord) enc10 :: B.ByteString -> B.ByteString
enc10 = BC.pack . unwords . Prelude.map (show . ord) . BC.unpack
-- enc10 str = C.unpack $ C.pack $ Prelude.foldl (\acc char -> acc ++ show (ord char)) "" str -- enc10 str = C.unpack $ C.pack $ Prelude.foldl (\acc char -> acc ++ show (ord char)) "" str

View File

@ -3,18 +3,27 @@ module Encoding.Base16
, dec16 , dec16
) where ) where
import qualified Data.ByteString.Char8 as C
import Data.ByteString.UTF8 as BSU import Data.ByteString.UTF8 as BSU
import Data.ByteString as B
import qualified Data.ByteString.Char8 as BC
import qualified Codec.Binary.Base16 as B16 import qualified Codec.Binary.Base16 as B16
import qualified Data.Text as T import qualified Data.Text as T
import qualified Data.Text.Encoding as T import qualified Data.Text.Encoding as T
import qualified Data.Text.IO as T import qualified Data.Text.IO as T
dec16 :: String -> String -- dec16 :: String -> String
dec16 input = -- dec16 input =
case B16.decode (BSU.fromString input) of -- case B16.decode (BSU.fromString input) of
Right decoded -> T.unpack (T.decodeUtf8 decoded) -- Right decoded -> T.unpack (T.decodeUtf8 decoded)
Left _ -> "Error decoding Base16.\n" -- Left _ -> "Error decoding Base16.\n"
enc16 :: String -> String dec16 :: B.ByteString -> B.ByteString
enc16 = C.unpack . B16.encode . BSU.fromString dec16 input = case B16.decode input of
Right byteString -> byteString
Left _ -> BC.pack "Error: Invalid Hexadecimal input"
-- enc16 :: String -> String
-- enc16 = C.unpack . B16.encode . BSU.fromString
enc16 :: B.ByteString -> B.ByteString
enc16 = B16.encode

View File

@ -4,18 +4,27 @@ module Encoding.Base32
) where ) where
import Data.ByteString as B
import qualified Data.ByteString.Char8 as BC
import Data.ByteString.UTF8 as BSU -- from utf8-string import Data.ByteString.UTF8 as BSU -- from utf8-string
import qualified Data.ByteString.Char8 as C
import qualified Codec.Binary.Base32 as B32 import qualified Codec.Binary.Base32 as B32
import qualified Data.Text as T import qualified Data.Text as T
import qualified Data.Text.Encoding as T import qualified Data.Text.Encoding as T
import qualified Data.Text.IO as T import qualified Data.Text.IO as T
dec32 :: String -> String -- dec32 :: String -> String
dec32 input = -- dec32 input =
case B32.decode (BSU.fromString input) of -- case B32.decode (BSU.fromString input) of
Right decoded -> T.unpack (T.decodeUtf8 decoded) -- Right decoded -> T.unpack (T.decodeUtf8 decoded)
Left _ -> "Error decoding Base32.\n" -- Left _ -> "Error decoding Base32.\n"
enc32 :: String -> String dec32 :: B.ByteString -> B.ByteString
enc32 = C.unpack . B32.encode . BSU.fromString dec32 input = case B32.decode input of
Right byteString -> byteString
Left _ -> BC.pack "Error: Invalid Base32 input"
-- enc32 :: String -> String
-- enc32 = C.unpack . B32.encode . BSU.fromString
enc32 :: B.ByteString -> B.ByteString
enc32 = B32.encode

View File

@ -3,19 +3,27 @@ module Encoding.Base58
, dec58 , dec58
) where ) where
import qualified Data.ByteString.Char8 as C import Data.ByteString as B
import qualified Data.ByteString.Char8 as BC
import Data.ByteString.UTF8 as BSU -- from utf8-string import Data.ByteString.UTF8 as BSU -- from utf8-string
import qualified Haskoin.Address.Base58 as B58 import qualified Haskoin.Address.Base58 as B58
import qualified Data.Text as T import qualified Data.Text as T
import qualified Data.Text.Encoding as T import qualified Data.Text.Encoding as T
-- import qualified Data.Text.IO as T import qualified Data.Text.IO as T
dec58 :: String -> String -- dec58 :: String -> String
dec58 input = -- dec58 input =
case B58.decodeBase58 (T.pack input) of -- case B58.decodeBase58 (T.pack input) of
Just decodedStr -> T.unpack (T.decodeUtf8 decodedStr) -- Just decodedStr -> T.unpack (T.decodeUtf8 decodedStr)
Nothing -> "Error decoding Base58.\n" -- Nothing -> "Error decoding Base58.\n"
enc58 :: String -> String dec58 :: B.ByteString -> B.ByteString
enc58 = T.unpack . B58.encodeBase58 . BSU.fromString dec58 input = case B58.decodeBase58 (T.decodeUtf8 input) of
Just byteString -> byteString
Nothing -> BC.pack "Error: Invalid Base58 input"
-- enc58 :: String -> String
-- enc58 = T.unpack . B58.encodeBase58 . BSU.fromString
enc58 :: B.ByteString -> B.ByteString
enc58 = BC.pack . T.unpack . B58.encodeBase58

View File

@ -6,7 +6,8 @@ module Encoding.Base64
) where ) where
import Data.ByteString.UTF8 as BSU -- from utf8-string import Data.ByteString.UTF8 as BSU -- from utf8-string
import qualified Data.ByteString.Char8 as C import Data.ByteString as B
import qualified Data.ByteString.Char8 as BC
import qualified Codec.Binary.Base64 as B64 import qualified Codec.Binary.Base64 as B64
import qualified Data.ByteString.Base64 as B64L import qualified Data.ByteString.Base64 as B64L
import qualified Codec.Binary.Base64Url as B64U import qualified Codec.Binary.Base64Url as B64U
@ -15,38 +16,55 @@ import qualified Data.Text as T
import qualified Data.Text.Encoding as T import qualified Data.Text.Encoding as T
import qualified Data.Text.IO as T import qualified Data.Text.IO as T
encodeToBase64 :: C.ByteString -> Either String C.ByteString -- encodeToBase64 :: C.ByteString -> Either String C.ByteString
encodeToBase64 bs = -- encodeToBase64 bs =
case B64.encode bs of -- case B64.encode bs of
encoded | C.null encoded -> Left "Failed to encode Base64.\n" -- encoded | C.null encoded -> Left "Failed to encode Base64.\n"
| otherwise -> Right encoded -- | otherwise -> Right encoded
decodeFromBase64 :: C.ByteString -> Either String C.ByteString -- decodeFromBase64 :: C.ByteString -> Either String C.ByteString
decodeFromBase64 bs = -- decodeFromBase64 bs =
case B64L.decodeLenient bs of -- case B64L.decodeLenient bs of
decoded | C.null decoded -> Left "Failed to decode from Base64.\n" -- decoded | C.null decoded -> Left "Failed to decode from Base64.\n"
| otherwise -> Right decoded -- | otherwise -> Right decoded
-- | otherwise -> Right (BSU.toString decoded) -- | otherwise -> Right (BSU.toString decoded)
-- Left err -> Left $ "Failed to decode from base64: " ++ err -- Left err -> Left $ "Failed to decode from base64: " ++ err
-- Right decoded -> Right decoded -- Right decoded -> Right decoded
dec64 :: String -> String -- dec64 :: String -> String
dec64 input = -- dec64 input =
case decodeFromBase64 (BSU.fromString input) of -- case decodeFromBase64 (BSU.fromString input) of
Right byteString -> T.unpack (T.decodeUtf8 byteString) -- Right byteString -> T.unpack (T.decodeUtf8 byteString)
Left errMsg -> "Error: " ++ errMsg -- Left errMsg -> "Error: " ++ errMsg
enc64 :: String -> String
enc64 input =
case encodeToBase64 (BSU.fromString input) of
Right byteString -> C.unpack byteString
Left errMsg -> "Error: " ++ errMsg
dec64url :: String -> String -- enc64 :: String -> String
dec64url input = -- enc64 input =
case B64.decode (BSU.fromString input) of -- case encodeToBase64 (BSU.fromString input) of
Right decoded -> T.unpack (T.decodeUtf8 decoded) -- Right byteString -> C.unpack byteString
Left _ -> "Error decoding Base64 for URLs.\n" -- Left errMsg -> "Error: " ++ errMsg
enc64url :: String -> String dec64 :: B.ByteString -> B.ByteString
enc64url = C.unpack . B64U.encode . BSU.fromString dec64 input = case B64.decode input of
Right byteString -> byteString
Left _ -> BC.pack "Error: Invalid Base64 input"
enc64 :: B.ByteString -> B.ByteString
enc64 = B64.encode
-- dec64url :: String -> String
-- dec64url input =
-- case B64.decode (BSU.fromString input) of
-- Right decoded -> T.unpack (T.decodeUtf8 decoded)
-- Left _ -> "Error decoding Base64 for URLs.\n"
-- enc64url :: String -> String
-- enc64url = C.unpack . B64U.encode . BSU.fromString
dec64url :: B.ByteString -> B.ByteString
dec64url input = case B64U.decode input of
Right byteString -> byteString
Left _ -> BC.pack "Error: Invalid Base64URL input"
enc64url :: B.ByteString -> B.ByteString
enc64url = B64U.encode

View File

@ -5,17 +5,25 @@ module Encoding.Base85
import qualified Codec.Binary.Base85 as B85 import qualified Codec.Binary.Base85 as B85
import Data.ByteString.UTF8 as BSU -- from utf8-string import Data.ByteString.UTF8 as BSU -- from utf8-string
import qualified Data.ByteString.Char8 as C import Data.ByteString as B
import qualified Data.ByteString.Char8 as BC
import qualified Data.Text as T import qualified Data.Text as T
import qualified Data.Text.Encoding as T import qualified Data.Text.Encoding as T
dec85 :: String -> String -- dec85 :: String -> String
dec85 input = -- dec85 input =
case B85.decode (BSU.fromString input) of -- case B85.decode (BSU.fromString input) of
Right decodedStr -> T.unpack (T.decodeUtf8 decodedStr) -- Right decodedStr -> T.unpack (T.decodeUtf8 decodedStr)
Left _ -> "Error decoding Base85.\n" -- Left _ -> "Error decoding Base85.\n"
enc85 :: String -> String dec85 :: B.ByteString -> B.ByteString
enc85 = C.unpack . B85.encode . BSU.fromString dec85 input = case B85.decode input of
Right byteString -> byteString
Left _ -> BC.pack "Error: Invalid Base85 input"
-- enc85 :: String -> String
-- enc85 = C.unpack . B85.encode . BSU.fromString
enc85 :: B.ByteString -> B.ByteString
enc85 = B85.encode

View File

@ -3,6 +3,8 @@ module Encoding.Base91
, dec91 , dec91
) where ) where
import Data.ByteString as B
import qualified Data.ByteString.Char8 as BC
import qualified Data.ByteString.Char8 as C import qualified Data.ByteString.Char8 as C
import Data.ByteString.UTF8 as BSU import Data.ByteString.UTF8 as BSU
import qualified Codec.Binary.Base91 as B91 import qualified Codec.Binary.Base91 as B91
@ -10,8 +12,12 @@ import qualified Data.Text as T
-- import qualified Data.Text.IO as T -- import qualified Data.Text.IO as T
import qualified Data.Text.Encoding as T import qualified Data.Text.Encoding as T
dec91 :: String -> String -- dec91 :: String -> String
dec91 = T.unpack . T.decodeUtf8 . B91.decode -- dec91 = T.unpack . T.decodeUtf8 . B91.decode
dec91 :: B.ByteString -> B.ByteString
dec91 = B91.decode . BC.unpack
enc91 :: String -> String -- enc91 :: String -> String
enc91 = B91.encode . BSU.fromString -- enc91 = B91.encode . BSU.fromString
enc91 :: B.ByteString -> B.ByteString
enc91 = BC.pack . B91.encode

View File

@ -3,20 +3,27 @@ module Encoding.QuotedPrintable
, decqp , decqp
) where ) where
import Data.ByteString as B
import qualified Data.ByteString.Char8 as BC
import qualified Codec.Binary.QuotedPrintable as QP import qualified Codec.Binary.QuotedPrintable as QP
import Data.ByteString.UTF8 as BSU -- from utf8-string import Data.ByteString.UTF8 as BSU -- from utf8-string
import qualified Data.ByteString.Char8 as C -- import qualified Data.ByteString.Char8 as C
import qualified Data.Text as T import qualified Data.Text as T
import qualified Data.Text.Encoding as T import qualified Data.Text.Encoding as T
-- import qualified Data.Text.IO as T -- import qualified Data.Text.IO as T
decqp :: String -> String -- decqp :: String -> String
decqp input = -- decqp input =
case QP.decode (BSU.fromString input) of -- case QP.decode (BSU.fromString input) of
Right decoded -> T.unpack (T.decodeUtf8 decoded) -- Right decoded -> T.unpack (T.decodeUtf8 decoded)
Left _ -> "Error decoding QP.\n" -- Left _ -> "Error decoding QP.\n"
decqp :: B.ByteString -> B.ByteString
encqp :: String -> String decqp input = case QP.decode input of
encqp = C.unpack . QP.encode . BSU.fromString Right byteString -> byteString
Left _ -> BC.pack "Error: Invalid Quoted Printable input"
-- encqp :: String -> String
-- encqp = C.unpack . QP.encode . BSU.fromString
encqp :: B.ByteString -> B.ByteString
encqp = QP.encode

View File

@ -3,21 +3,28 @@ module Encoding.UnixToUnix
, decuu , decuu
) where ) where
import Data.ByteString as B
import qualified Data.ByteString.Char8 as BC
import qualified Codec.Binary.Uu as UU import qualified Codec.Binary.Uu as UU
import Data.ByteString.UTF8 as BSU -- from utf8-string import Data.ByteString.UTF8 as BSU -- from utf8-string
import qualified Data.ByteString.Char8 as C
import qualified Data.Text as T import qualified Data.Text as T
import qualified Data.Text.Encoding as T import qualified Data.Text.Encoding as T
import qualified Data.Text.IO as T import qualified Data.Text.IO as T
decuu :: String -> String -- decuu :: String -> String
-- decuu = C.unpack . U.fromRight . UU.decode . BSU.fromString -- -- decuu = C.unpack . U.fromRight . UU.decode . BSU.fromString
decuu input = -- decuu input =
case UU.decode (T.encodeUtf8 (T.pack input)) of -- case UU.decode (T.encodeUtf8 (T.pack input)) of
Right decoded -> T.unpack (T.decodeUtf8 decoded) -- Right decoded -> T.unpack (T.decodeUtf8 decoded)
Left _ -> "Error decoding UU.\n" -- Left _ -> "Error decoding UU.\n"
decuu :: B.ByteString -> B.ByteString
decuu input = case UU.decode input of
Right byteString -> byteString
Left _ -> BC.pack "Error: Invalid Unix to Unix encoding input"
encuu :: String -> String -- encuu :: String -> String
-- encuu = C.unpack . UU.encode . BSU.fromString -- -- encuu = C.unpack . UU.encode . BSU.fromString
encuu = T.unpack . T.decodeUtf8 . UU.encode . T.encodeUtf8 . T.pack -- encuu = T.unpack . T.decodeUtf8 . UU.encode . T.encodeUtf8 . T.pack
encuu :: B.ByteString -> B.ByteString
encuu = UU.encode

View File

@ -4,10 +4,14 @@ module Encoding.Url
) where ) where
import qualified Network.HTTP.Base as HB import qualified Network.HTTP.Base as HB
import Data.ByteString as B
import qualified Data.ByteString.Char8 as BC
decurl :: String -> String -- decurl :: String -> String
decurl = HB.urlDecode decurl :: B.ByteString -> B.ByteString
decurl = BC.pack . HB.urlDecode . BC.unpack
encurl :: String -> String -- encurl :: String -> String
encurl = HB.urlEncode encurl :: B.ByteString -> B.ByteString
encurl = BC.pack . HB.urlEncode . BC.unpack

View File

@ -3,18 +3,25 @@ module Encoding.Xx
, decxx , decxx
) where ) where
import Data.ByteString as B
import qualified Data.ByteString.Char8 as BC
import qualified Codec.Binary.Xx as XX import qualified Codec.Binary.Xx as XX
import Data.ByteString.UTF8 as BSU -- from utf8-string import Data.ByteString.UTF8 as BSU -- from utf8-string
import qualified Data.ByteString.Char8 as C
import qualified Data.Text as T import qualified Data.Text as T
import qualified Data.Text.Encoding as T import qualified Data.Text.Encoding as T
import qualified Data.Text.IO as T import qualified Data.Text.IO as T
decxx :: String -> String -- decxx :: String -> String
decxx input = -- decxx input =
case XX.decode (BSU.fromString input) of -- case XX.decode (BSU.fromString input) of
Right decoded -> T.unpack (T.decodeUtf8 decoded) -- Right decoded -> T.unpack (T.decodeUtf8 decoded)
Left _ -> "Error decoding XX.\n" -- Left _ -> "Error decoding XX.\n"
decxx :: B.ByteString -> B.ByteString
decxx input = case XX.decode input of
Right byteString -> byteString
Left _ -> BC.pack "Error: Invalid XX encoding input"
encxx :: String -> String -- encxx :: String -> String
encxx = C.unpack . XX.encode . BSU.fromString -- encxx = C.unpack . XX.encode . BSU.fromString
encxx :: B.ByteString -> B.ByteString
encxx = XX.encode

View File

@ -4,20 +4,28 @@ module Encoding.Yenc
) where ) where
import Data.ByteString as B
import qualified Data.ByteString.Char8 as BC
import Data.ByteString.UTF8 as BSU -- from utf8-string import Data.ByteString.UTF8 as BSU -- from utf8-string
import qualified Data.ByteString.Char8 as C
import qualified Codec.Binary.Yenc as Y import qualified Codec.Binary.Yenc as Y
import qualified Data.Text as T import qualified Data.Text as T
import qualified Data.Text.Encoding as T import qualified Data.Text.Encoding as T
import qualified Data.Text.IO as T import qualified Data.Text.IO as T
decy :: String -> String -- decy :: String -> String
-- decy = C.unpack . U.fromRight . Y.decode . BSU.fromString -- -- decy = C.unpack . U.fromRight . Y.decode . BSU.fromString
decy input = -- decy input =
case Y.decode (BSU.fromString input) of -- case Y.decode (BSU.fromString input) of
Right decoded -> T.unpack (T.decodeUtf8 decoded) -- Right decoded -> T.unpack (T.decodeUtf8 decoded)
Left _ -> "Error decoding Y.\n" -- Left _ -> "Error decoding Y.\n"
ency :: String -> String decy :: B.ByteString -> B.ByteString
ency = C.unpack . Y.encode . BSU.fromString decy input = case Y.decode input of
Right byteString -> byteString
Left _ -> BC.pack "Error: Invalid YEncoding input"
-- ency :: String -> String
-- ency = C.unpack . Y.encode . BSU.fromString
ency :: B.ByteString -> B.ByteString
ency = Y.encode

View File

@ -124,17 +124,17 @@ testDecQp = TestCase $ do
assertEqual "for (decqp \"QP=20works=20by=20using=20the=20equals=20sign=20=3D=20as=20an=20escape=20=\r\ncharacter.=20It=20also=20limits=20line=20length=20to=2076,=20as=20some=20=\r\nsoftware=20has=20limits=20on=20line=20length.\")," "QP works by using the equals sign = as an escape character. It also limits line length to 76, as some software has limits on line length." (decqp "QP=20works=20by=20using=20the=20equals=20sign=20=3D=20as=20an=20escape=20=\ncharacter.=20It=20also=20limits=20line=20length=20to=2076,=20as=20some=20=\nsoftware=20has=20limits=20on=20line=20length.") assertEqual "for (decqp \"QP=20works=20by=20using=20the=20equals=20sign=20=3D=20as=20an=20escape=20=\r\ncharacter.=20It=20also=20limits=20line=20length=20to=2076,=20as=20some=20=\r\nsoftware=20has=20limits=20on=20line=20length.\")," "QP works by using the equals sign = as an escape character. It also limits line length to 76, as some software has limits on line length." (decqp "QP=20works=20by=20using=20the=20equals=20sign=20=3D=20as=20an=20escape=20=\ncharacter.=20It=20also=20limits=20line=20length=20to=2076,=20as=20some=20=\nsoftware=20has=20limits=20on=20line=20length.")
assertEqual "for (decqp \"=F0=9F=98=82\")," "😂" (decqp "=F0=9F=98=82") assertEqual "for (decqp \"=F0=9F=98=82\")," "😂" (decqp "=F0=9F=98=82")
testEnUu :: Test -- testEnUu :: Test
testEnUu = TestCase $ do -- testEnUu = TestCase $ do
assertEqual "for (encuu \"Hello, World!\")," "110 145 154 154 157 54 40 127 157 162 154 144 41" (encuu "Hello, World!") -- assertEqual "for (encuu \"Hello, World!\")," "110 145 154 154 157 54 40 127 157 162 154 144 41" (encuu "Hello, World!")
assertEqual "for (encuu \"Haskell\")," "110 141 163 153 145 154 154" (encuu "Haskell") -- assertEqual "for (encuu \"Haskell\")," "110 141 163 153 145 154 154" (encuu "Haskell")
assertEqual "for (encuu \"😂\")," "360 237 230 202" (encuu "😂") -- assertEqual "for (encuu \"😂\")," "360 237 230 202" (encuu "😂")
testDecUu :: Test -- testDecUu :: Test
testDecUu = TestCase $ do -- testDecUu = TestCase $ do
assertEqual "for (decuu \"110 145 154 154 157 54 40 127 157 162 154 144 41\")," "Hello, World!" (decuu "110 145 154 154 157 54 40 127 157 162 154 144 41") -- assertEqual "for (decuu \"110 145 154 154 157 54 40 127 157 162 154 144 41\")," "Hello, World!" (decuu "110 145 154 154 157 54 40 127 157 162 154 144 41")
assertEqual "for (decuu \"110 141 163 153 145 154 154\")," "Haskell" (decuu "110 141 163 153 145 154 154") -- assertEqual "for (decuu \"110 141 163 153 145 154 154\")," "Haskell" (decuu "110 141 163 153 145 154 154")
assertEqual "for (decuu \"360 237 230 202\")," "😂" (decuu "360 237 230 202") -- assertEqual "for (decuu \"360 237 230 202\")," "😂" (decuu "360 237 230 202")
tests :: Test tests :: Test