2022-05-17 00:23:30 +02:00
#!/ usr / bin / env runhaskell
{- # LANGUAGE DeriveDataTypeable # -}
module Main where
import System.Console.CmdArgs
import Control.Arrow
2022-05-22 01:15:09 +02:00
import Data.Text ( pack , unpack )
2022-05-22 22:48:44 +02:00
import Data.Text.Encoding ( encodeUtf8 )
2022-05-22 01:15:09 +02:00
import Data.Maybe ( fromJust )
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 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 qualified Data.ByteString.Char8 as C
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
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
2024-04-20 01:20:53 +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 =
2024-04-20 01:20:53 +02:00
-- 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
2024-04-28 23:47:31 +02:00
encodeToBase64 :: C . ByteString -> Either String C . ByteString
encodeToBase64 bs =
case B64 . encode bs of
encoded | C . null encoded -> Left " Failed to encode base64. "
| otherwise -> Right encoded
2024-04-18 00:18:39 +02:00
2024-04-20 01:20:53 +02:00
decodeFromBase64 :: C . ByteString -> Either String C . ByteString
2024-04-18 00:18:39 +02:00
decodeFromBase64 bs =
case B64L . decodeLenient bs of
2024-04-20 01:20:53 +02:00
decoded | C . null decoded -> Left " Failed to decode from base64. "
2024-04-18 00:18:39 +02:00
| otherwise -> Right decoded
-- | otherwise -> Right (BSU.toString decoded)
-- Left err -> Left $ "Failed to decode from base64: " ++ err
-- Right decoded -> Right decoded
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-28 23:47:31 +02:00
dec91 :: String -> String
2024-04-20 01:20:53 +02:00
dec91 = C . unpack . B91 . decode
2024-04-28 23:47:31 +02:00
enc91 :: String -> String
2022-05-17 00:23:30 +02:00
enc91 = B91 . encode . BSU . fromString
2024-04-28 23:47:31 +02:00
2024-04-29 23:06:06 +02:00
-- dec85 = C.unpack . U.fromRight . B85.decode . BSU.fromString
dec85 :: String -> String
dec85 input =
let decoded = B85 . decode ( BSU . fromString input )
in case decoded of
Right decodedStr -> C . unpack decodedStr
Left ( decodedStr , _ ) -> C . unpack decodedStr
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
-- dec64 = C.unpack . B64L.decodeLenient . BSU.fromString
2024-04-20 01:20:53 +02:00
dec64 :: String -> String
dec64 input =
case decodeFromBase64 ( BSU . fromString input ) of
Right byteString -> C . unpack byteString
Left errMsg -> " Error: " ++ errMsg
2024-04-18 00:18:39 +02:00
2024-04-28 23:47:31 +02:00
-- enc64 = C.unpack . B64.encode . BSU.fromString
enc64 :: String -> String
enc64 input =
case encodeToBase64 ( BSU . fromString input ) of
Right byteString -> C . unpack byteString
Left errMsg -> " Error: " ++ errMsg
2024-04-18 00:18:39 +02:00
2022-05-22 22:48:44 +02:00
dec64url = C . unpack . U . fromRight . B64U . decode . BSU . fromString
enc64url = C . unpack . B64U . encode . BSU . fromString
2022-09-19 23:11:13 +02:00
decurl = HB . urlDecode
encurl = HB . urlEncode
2022-05-22 01:15:09 +02:00
dec62 = show . fromJust . B62 . decode128 . ( Bytes . fromByteString . BSU . fromString )
enc62 = C . unpack . BSU . fromString . Bytes . toLatinString . ( Bytes . fromByteArray . ( B62 . encode64 . ( intToWord64 . decimalStringToInt ) ) )
dec58 = C . unpack . fromJust . B58 . decodeBase58 . pack
enc58 = unpack . B58 . encodeBase58 . BSU . fromString
2022-05-17 00:23:30 +02:00
dec32 = C . unpack . U . fromRight . B32 . decode . BSU . fromString
enc32 = C . unpack . B32 . encode . BSU . fromString
dec16 = C . unpack . U . fromRight . B16 . decode . BSU . fromString
enc16 = C . unpack . B16 . encode . BSU . fromString
2022-05-19 23:55:26 +02:00
dec10 = show . hexStringToInt
enc10 = C . unpack . BSU . fromString . intToHexString . decimalStringToInt -- Depending on what you want, do enc10 = show . map ord
2022-05-22 22:48:44 +02:00
dec8 = C . unpack . encodeUtf8 . toText . showbOct . hexStringToInt
enc8 = C . unpack . BSU . fromString . intToHexString . octToInt . ( reverse . ( map fromJust . ( map fromOctDigit ) ) )
dec2 = C . unpack . encodeUtf8 . toText . showbBin . hexStringToInt
enc2 = C . unpack . BSU . fromString . intToHexString . binToInt . ( reverse . ( map fromJust . ( map fromBinDigit ) ) )
2022-05-19 23:55:26 +02:00
decqp = C . unpack . U . fromRight . QP . decode . BSU . fromString
encqp = C . unpack . QP . encode . BSU . fromString
decuu = C . unpack . U . fromRight . UU . decode . BSU . fromString
encuu = C . unpack . UU . encode . BSU . fromString
decxx = C . unpack . U . fromRight . XX . decode . BSU . fromString
encxx = C . unpack . XX . encode . BSU . fromString
decy = C . unpack . U . fromRight . Y . decode . BSU . fromString
ency = C . unpack . Y . encode . BSU . fromString
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 } = decuu
optionHandler Decode { uu = True } = encuu
optionHandler Decode { xx = True } = decxx
optionHandler Encode { xx = True } = encxx
optionHandler Decode { yenc = True } = decy
optionHandler Encode { yenc = True } = ency
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 "
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. \ n To see every parameter of every mode use --help=all " &= program " based " &= summary " based v0.4 " ) >>= interact . optionHandler