based/app/Main.hs

366 lines
14 KiB
Haskell
Raw Normal View History

2022-05-17 00:23:30 +02:00
#!/usr/bin/env runhaskell
{-# LANGUAGE DeriveDataTypeable #-}
module Main where
import System.Console.CmdArgs
import Control.Arrow
import Data.Text (pack, unpack, Text)
import Data.Bits
-- import Data.Char
import Text.Read (readMaybe)
import qualified Data.Text as T
import qualified Data.Text.Encoding as T
import qualified Data.Text.IO as T
-- import Data.Text (Text)
import qualified Data.Text.Lazy as TL
import Data.Text.Lazy.Builder (toLazyText)
import Data.Text.Encoding (decodeUtf8With, decodeUtf8, encodeUtf8)
import Data.Maybe (fromJust, fromMaybe)
import Data.Text.Encoding.Error (lenientDecode)
2022-05-19 23:55:26 +02:00
import TextShow (toText)
2022-05-22 22:48:44 +02:00
import Text.XML.HXT.DOM.Util (hexStringToInt, intToHexString, decimalStringToInt)
import TextShow.Data.Integral (showbBin, showbOct)
import Text.Ascii (fromBinDigit, fromOctDigit)
2022-05-22 01:15:09 +02:00
import Codec.CBOR.Magic (intToWord64)
2022-05-17 00:23:30 +02:00
import qualified Data.Either.Unwrap as U
import Data.Bytes.Text.Latin1 as Latin1
2022-05-17 00:23:30 +02:00
import qualified Codec.Binary.Base91 as B91
import qualified Codec.Binary.Base85 as B85
import qualified Codec.Binary.Base64 as B64
2023-07-25 23:17:25 +02:00
import qualified Data.ByteString.Base64 as B64L
2022-05-22 22:48:44 +02:00
import qualified Codec.Binary.Base64Url as B64U
2022-09-19 23:11:13 +02:00
import qualified Network.HTTP.Base as HB
2022-05-17 00:23:30 +02:00
import qualified Data.Word.Base62 as B62
2022-05-22 01:15:09 +02:00
import qualified Haskoin.Address.Base58 as B58
2022-05-17 00:23:30 +02:00
import qualified Codec.Binary.Base32 as B32
import qualified Codec.Binary.Base16 as B16
2022-05-19 23:55:26 +02:00
import qualified Codec.Binary.QuotedPrintable as QP
import qualified Codec.Binary.Uu as UU
import qualified Codec.Binary.Xx as XX
import qualified Codec.Binary.Yenc as Y
2022-05-17 00:23:30 +02:00
import qualified Data.Bytes as Bytes
import qualified Data.Bytes.Text.Ascii as ASCII
2022-05-22 01:15:09 +02:00
import Data.Bytes.Get (getWord64host)
2022-05-17 00:23:30 +02:00
import Data.ByteString.UTF8 as BSU -- from utf8-string
-- import Data.ByteString (singleton)
import GHC.Word (Word8)
2022-05-17 00:23:30 +02:00
import qualified Data.ByteString.Char8 as C
-- Regex imports
import Text.Regex.TDFA
2024-05-03 23:36:35 +02:00
import Data.Word (Word8)
import Data.Char (ord, chr, intToDigit, digitToInt)
import Encoding.Base2 (enc2, dec2)
import Encoding.Base8 (enc8, dec8)
import Encoding.Base10 (enc10, dec10)
import Encoding.Base16 (enc16, dec16)
import Encoding.Base64 (enc64, dec64, enc64url, dec64url)
import Encoding.Base91 (enc91, dec91)
2022-05-17 00:23:30 +02:00
data Based = Decode {
b91 :: Bool,
b85 :: Bool,
b64 :: Bool,
2022-05-22 22:48:44 +02:00
b64url :: Bool,
2022-09-19 23:11:13 +02:00
url :: Bool,
2022-05-17 00:23:30 +02:00
b62 :: Bool,
2022-05-19 23:55:26 +02:00
b58 :: Bool,
2022-05-17 00:23:30 +02:00
b32 :: Bool,
2022-05-19 23:55:26 +02:00
b16 :: Bool,
b10 :: Bool,
2022-05-22 22:48:44 +02:00
b8 :: Bool,
b2 :: Bool,
2022-05-19 23:55:26 +02:00
qp :: Bool,
uu :: Bool,
xx :: Bool,
yenc :: Bool,
solve :: Bool
2022-05-17 00:23:30 +02:00
}
| Encode {
b91 :: Bool,
b85 :: Bool,
b64 :: Bool,
2022-05-22 22:48:44 +02:00
b64url :: Bool,
2022-09-19 23:11:13 +02:00
url :: Bool,
2022-05-17 00:23:30 +02:00
b62 :: Bool,
2022-05-19 23:55:26 +02:00
b58 :: Bool,
2022-05-17 00:23:30 +02:00
b32 :: Bool,
2022-05-19 23:55:26 +02:00
b16 :: Bool,
b10 :: Bool,
2022-05-22 22:48:44 +02:00
b8 :: Bool,
b2 :: Bool,
2022-05-19 23:55:26 +02:00
qp :: Bool,
uu :: Bool,
xx :: Bool,
yenc :: Bool
2022-05-17 00:23:30 +02:00
}
deriving(Show, Data, Typeable)
2022-05-22 22:48:44 +02:00
-- helper functions
2024-04-18 00:18:39 +02:00
-- convertToByteString :: String -> Either String C.ByteString
-- convertToByteString str =
-- case BSU.fromString str of
-- Just bs -> Right bs
-- Nothing -> Left "Failed to convert string to ByteString."
2024-04-18 00:18:39 +02:00
2024-04-28 23:47:31 +02:00
-- decodeFromBase91 :: String -> Either String C.ByteString
-- decodeFromBase91 decoded =
-- case B91.decode of
2024-04-28 23:47:31 +02:00
-- decoded | C.null decoded -> Left "Failed to decode from base91"
-- | otherwise -> Right decoded
2024-04-18 00:18:39 +02:00
2022-05-22 22:48:44 +02:00
binToInt :: [Int] -> Int
binToInt [] = 0
binToInt (x : xs) = x + 2 * binToInt xs
octToInt :: [Int] -> Int
octToInt [] = 0
octToInt (x : xs) = x + 8 * octToInt xs
-- base functions
2022-05-17 00:23:30 +02:00
-- without the show func, sequences like \n will not be shown as characters but will be executed as newline
2024-04-18 00:18:39 +02:00
2024-04-29 23:06:06 +02:00
-- dec85 = C.unpack . U.fromRight . B85.decode . BSU.fromString
dec85 :: String -> String
dec85 input =
case B85.decode (BSU.fromString input) of
2024-04-29 23:06:06 +02:00
Right decodedStr -> C.unpack decodedStr
Left _ -> "Error decoding Base85.\n"
2024-04-28 23:47:31 +02:00
2024-04-29 23:06:06 +02:00
enc85 :: String -> String
2022-05-17 00:23:30 +02:00
enc85 = C.unpack . B85.encode . BSU.fromString
2024-04-18 00:18:39 +02:00
2024-05-01 14:28:50 +02:00
decurl :: String -> String
2022-09-19 23:11:13 +02:00
decurl = HB.urlDecode
2024-05-01 14:28:50 +02:00
encurl :: String -> String
2022-09-19 23:11:13 +02:00
encurl = HB.urlEncode
2024-05-01 14:28:50 +02:00
dec62 :: String -> String
-- dec62 = T.unpack . B62.text128 . fromJust . B62.decode128 . Bytes.fromAsciiString
-- dec62 input =
-- case B62.decode128 (Bytes.fromAsciiString input) of
-- Just decoded -> (T.unpack (B62.text128 decoded))
-- -- Just decoded -> C.unpack decoded
-- Nothing -> "Error decoding Base62.\n"
-- dec62 = show . fromJust . B62.decode128 . (Bytes.fromByteString . BSU.fromString)
dec62 input =
let decoded = B62.decode128 (Bytes.fromByteString (BSU.fromString input))
in fromMaybe "Error decoding Base62.\n" (show <$> decoded)
-- dec62 input =
-- maybe "Error decoding Base62.\n" show (B62.decode128 (Bytes.fromByteString (BSU.fromString input)))
stringToInt :: String -> Maybe Integer
stringToInt = readMaybe
-- enc62 :: String -> String
-- enc62 = C.unpack . BSU.fromString. Latin1.toString . (Bytes.fromByteArray . ( B62.encode64 . (intToWord64 . decimalStringToInt)))
-- enc62 = T.unpack . T.decodeUtf8 . BSU.fromString . Latin1.toString . (Bytes.fromByteArray . ( B62.encode64 . (intToWord64 . decimalStringToInt)))
-- enc62 = T.unpack . T.decodeUtf8 . BSU.fromString . Latin1.toString . (Bytes.fromByteArray . (B62.encode128 . (fromIntegral . ( BSU.fromString . fromJust StringToInt))))
2024-05-01 14:28:50 +02:00
-- working correct:
-- enc62 :: String -> String
-- enc62 = T.unpack . T.decodeUtf8 . BSU.fromString . Latin1.toString . Bytes.fromByteArray . B62.encode64 . fromIntegral . fromJust . stringToInt
enc62 :: String -> String
enc62 input =
let intValue = fromMaybe (error "Error: Unable to convert input string to integer") (stringToInt input)
encoded = B62.encode64 (fromIntegral intValue)
encodedText = T.decodeUtf8 (BSU.fromString (Latin1.toString (Bytes.fromByteArray encoded)))
in T.unpack encodedText
-- enc62 :: Text -> Text
-- enc62 text = B62.text128 (fromIntegral (T.length text))
2024-05-01 14:28:50 +02:00
dec58 :: String -> String
-- dec58 = C.unpack . fromJust . B58.decodeBase58 . pack
dec58 input =
maybe "Error decoding Base58.\n" C.unpack (B58.decodeBase58 (T.pack input))
2024-05-01 14:28:50 +02:00
enc58 :: String -> String
enc58 = T.unpack . B58.encodeBase58 . BSU.fromString
2024-05-01 14:28:50 +02:00
dec32 :: String -> String
-- dec32 = C.unpack . U.fromRight . B32.decode . BSU.fromString
dec32 input =
case B32.decode (BSU.fromString input) of
Right decoded -> C.unpack decoded
Left _ -> "Error decoding Base32.\n"
2024-05-01 14:28:50 +02:00
enc32 :: String -> String
2022-05-17 00:23:30 +02:00
enc32 = C.unpack . B32.encode . BSU.fromString
2024-05-01 14:28:50 +02:00
decqp :: String -> String
-- decqp = C.unpack . U.fromRight . QP.decode . BSU.fromString
decqp input =
case QP.decode (BSU.fromString input) of
Right decoded -> C.unpack decoded
Left _ -> "Error decoding QP.\n"
2024-05-01 14:28:50 +02:00
encqp :: String -> String
2022-05-19 23:55:26 +02:00
encqp = C.unpack . QP.encode . BSU.fromString
2024-05-01 14:28:50 +02:00
decuu :: String -> String
-- decuu = C.unpack . U.fromRight . UU.decode . BSU.fromString
decuu input =
case UU.decode (BSU.fromString input) of
Right decoded -> C.unpack decoded
Left _ -> "Error decoding UU.\n"
2024-05-01 14:28:50 +02:00
encuu :: String -> String
2022-05-19 23:55:26 +02:00
encuu = C.unpack . UU.encode . BSU.fromString
2024-05-01 14:28:50 +02:00
decxx :: String -> String
-- decxx = C.unpack . U.fromRight . XX.decode . BSU.fromString
decxx input =
case XX.decode (BSU.fromString input) of
Right decoded -> C.unpack decoded
Left _ -> "Error decoding XX.\n"
2024-05-01 14:28:50 +02:00
encxx :: String -> String
2022-05-19 23:55:26 +02:00
encxx = C.unpack . XX.encode . BSU.fromString
2024-05-01 14:28:50 +02:00
decy :: String -> String
-- decy = C.unpack . U.fromRight . Y.decode . BSU.fromString
decy input =
case Y.decode (BSU.fromString input) of
Right decoded -> C.unpack decoded
Left _ -> "Error decoding Y.\n"
ency :: String -> String
2022-05-19 23:55:26 +02:00
ency = C.unpack . Y.encode . BSU.fromString
base91Regex = "^[!-~]*$"
base85Regex = "^[0-9A-Za-z!#$%&()*+,-;<=>?@^_`{|}~]+$"
-- base85Regex = "^[A-Za-u0-9!\"#$%&((*+,-./;:<=@[]\\`]*$"
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
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]*$"
base10Regex = "^[0-9]*$"
base8Regex = "^[0-7]*$"
base2Regex = "^[01]*$"
urlRegex = "^[a-zA-Z0-9%]*$"
solveEnc :: String -> String
solveEnc input =
2024-05-03 23:36:35 +02:00
let isBase91 = BSU.fromString input =~ base91Regex :: Bool
isBase85 = BSU.fromString input =~ base85Regex :: Bool
2024-05-03 23:36:35 +02:00
isBase64 = BSU.fromString input =~ base64Regex :: Bool
isBase58 = BSU.fromString input =~ base58Regex :: Bool
isBase32 = BSU.fromString input =~ base32Regex :: Bool
isBase16 = BSU.fromString input =~ base16Regex :: Bool
isBase10 = BSU.fromString input =~ base10Regex :: Bool
isBase8 = BSU.fromString input =~ base8Regex :: Bool
isBase2 = BSU.fromString input =~ base2Regex :: Bool
isURL = BSU.fromString input =~ urlRegex :: Bool
2024-05-03 23:36:35 +02:00
base91Result = if isBase91 then "\nTrying base91:\n" ++ dec91 input else ""
base85Result = if isBase85 then "\nTrying base85:\n" ++ dec85 input else ""
base64Result = if isBase64 then "\nTrying base64:\n" ++ dec64 input else ""
base58Result = if isBase58 then "\nTrying base58:\n" ++ dec58 input else ""
base32Result = if isBase64 then "\nTrying base32:\n" ++ dec32 input else ""
base16Result = if isBase16 then "\nTrying base16:\n" ++ dec16 input else ""
base10Result = if isBase10 then "\nTrying base10:\n" ++ dec10 input else ""
base2Result = if isBase2 then "\nTrying base2:\n" ++ dec2 input else ""
base8Result = if isBase8 then "\nTrying base8:\n" ++ dec8 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]
in
if null results
then "Not able to solve the encoding.\n"
else unlines results
--
-- | input =~ base64Regex = dec64 input
-- | input =~ base32Regex = dec32 input
-- | otherwise = "Cannot decode: " ++ input
--
-- if BSU.fromString input =~ base64Regex :: Bool
-- then dec64 input
-- else "Not Base64.\n"
-- ++ if BSU.fromString input =~ base32Regex :: Bool
-- then dec32 input
-- else "Not able to solve the encoding.\n"
2022-05-19 23:55:26 +02:00
-- optionHandler :: EncodeOptions -> Text -> Text
2022-05-17 00:23:30 +02:00
optionHandler Decode{b91=True} = dec91
optionHandler Encode{b91=True} = enc91
optionHandler Decode{b85=True} = dec85
optionHandler Encode{b85=True} = enc85
optionHandler Decode{b64=True} = dec64
optionHandler Encode{b64=True} = enc64
2022-05-22 22:48:44 +02:00
optionHandler Decode{b64url=True} = dec64url
optionHandler Encode{b64url=True} = enc64url
2022-09-19 23:11:13 +02:00
optionHandler Decode{url=True} = decurl
optionHandler Encode{url=True} = encurl
2022-05-17 00:23:30 +02:00
optionHandler Decode{b62=True} = dec62
optionHandler Encode{b62=True} = enc62
2022-05-19 23:55:26 +02:00
optionHandler Decode{b58=True} = dec58
optionHandler Encode{b58=True} = enc58
2022-05-17 00:23:30 +02:00
optionHandler Decode{b32=True} = dec32
optionHandler Encode{b32=True} = enc32
optionHandler Decode{b16=True} = dec16
optionHandler Encode{b16=True} = enc16
2022-05-19 23:55:26 +02:00
optionHandler Decode{b10=True} = dec10
optionHandler Encode{b10=True} = enc10
2022-05-22 22:48:44 +02:00
optionHandler Decode{b8=True} = dec8
optionHandler Encode{b8=True} = enc8
optionHandler Decode{b2=True} = dec2
optionHandler Encode{b2=True} = enc2
2022-05-19 23:55:26 +02:00
optionHandler Decode{qp=True} = decqp
optionHandler Encode{qp=True} = encqp
optionHandler Encode{uu=True} = encuu
optionHandler Decode{uu=True} = decuu
2022-05-19 23:55:26 +02:00
optionHandler Decode{xx=True} = decxx
optionHandler Encode{xx=True} = encxx
optionHandler Decode{yenc=True} = decy
optionHandler Encode{yenc=True} = ency
optionHandler Decode{solve=True} = solveEnc
2022-05-17 00:23:30 +02:00
2023-07-25 23:17:25 +02:00
decodeMode :: Based
decodeMode = Decode {
2022-05-17 00:23:30 +02:00
b91 = def &= help "decode base91",
b85 = def &= help "decode base85",
b64 = def &= help "decode base64",
2022-05-22 22:48:44 +02:00
b64url = def &= help "decode base64Url",
2022-09-19 23:11:13 +02:00
url = def &= help "decode URI",
2022-05-17 00:23:30 +02:00
b62 = def &= help "decode base62",
2022-05-19 23:55:26 +02:00
b58 = def &= help "decode base58",
2022-05-17 00:23:30 +02:00
b32 = def &= help "decode base32",
2022-05-19 23:55:26 +02:00
b16 = def &= help "decode base16",
2022-05-22 22:48:44 +02:00
b10 = def &= help "decode decimal from hex",
b8 = def &= help "decode octal from hex",
b2 = def &= help "decode binary from hex",
2022-05-19 23:55:26 +02:00
qp = def &= help "decode quoted-printable",
uu = def &= help "decode uu",
xx = def &= help "decode xx",
yenc = def &= help "decode yEncode",
solve = def &= help "solve encoding"
2022-05-17 00:23:30 +02:00
} &= help "Decode chosen base" &=auto
2023-07-25 23:17:25 +02:00
encodeMode :: Based
encodeMode = Encode {
2022-05-17 00:23:30 +02:00
b91 = def &= help "encode base91",
b85 = def &= help "encode base85",
b64 = def &= help "encode base64",
2022-05-22 22:48:44 +02:00
b64url = def &= help "encode base64Url",
2022-09-19 23:11:13 +02:00
url = def &= help "encode URI",
2022-05-17 00:23:30 +02:00
b62 = def &= help "encode base62",
2022-05-19 23:55:26 +02:00
b58 = def &= help "encode base58",
2022-05-17 00:23:30 +02:00
b32 = def &= help "encode base32",
2022-05-19 23:55:26 +02:00
b16 = def &= help "encode base16",
b10 = def &= help "encode base10 to hex",
2022-05-22 22:48:44 +02:00
b8 = def &= help "encode octal to hex",
b2 = def &= help "encode binary to hex",
2022-05-19 23:55:26 +02:00
qp = def &= help "encode quoted-printable",
uu = def &= help "encode uu",
xx = def &= help "encode xx",
yenc = def &= help "encode yEncode"
2022-05-17 00:23:30 +02:00
} &= help "Encode chosen base"
2023-07-25 23:17:25 +02:00
main :: IO()
main = cmdArgs (modes[decodeMode, encodeMode] &= help "Anybased, when Cyberchef simply doesn't cut it.\nTo see every parameter of every mode use --help=all" &= program "based" &= summary "based v0.4") >>= interact . optionHandler