{- Convert raw data (little-endian base-256 bytes) to big-endian decimal with zero-padding so that the decimal may be losslessly converted back to data. -} {- Copyright 2015 Ken Takusagawa This program is free software: you can redistribute it and/or modify it under the terms of the GNU General Public License as published by the Free Software Foundation, either version 3 of the License, or (at your option) any later version. This program is distributed in the hope that it will be useful, but WITHOUT ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU General Public License for more details. You should have received a copy of the GNU General Public License along with this program. If not, see . -} {-# LANGUAGE ScopedTypeVariables, LambdaCase, MagicHash #-} module Main(main) where { import Data.List; import qualified Data.ByteString.Lazy as B; import Data.Int(Int64); import GHC.Integer(mkInteger); import GHC.Integer.Logarithms(integerLogBase#); import Data.Bits(testBit); import Data.Word(Word8); import GHC.Exts(Int(I#)); import System.Environment(getArgs); main :: IO(); main = getArgs >>= \case { ["unopt"] -> B.getContents >>= putStrLn . to_dec_padded; _ -> B.getContents >>= putStrLn . to_dec_padded_opt; }; -- not optimized at all -- little endian makes more sense for data, in contrast to hex and decimal bytestring_to_integer :: B.ByteString -> Integer; bytestring_to_integer = B.foldr (\digit accum -> accum * 256 + (fromIntegral digit)) 0; equivalent_decimal_length :: Int64 -> Integer; equivalent_decimal_length data_length = genericLength $ show $ bytestring_to_integer $ B.replicate data_length 255; to_dec_padded :: B.ByteString -> String; to_dec_padded s = reverse $ genericTake (equivalent_decimal_length $ B.length s) $ (reverse $ show $ bytestring_to_integer s) ++ repeat '0'; ---------------- optimized version to_bits :: Word8 -> [Bool]; to_bits x = map (testBit x) [0..7]; from_bits :: [Bool] -> Int; from_bits = foldr (\b accum -> accum * 2 + if b then 1 else 0) 0; nchunk :: Integer -> [a] -> [[a]]; nchunk n = unfoldr $ \l -> if null l then Nothing else Just $ genericSplitAt n l; bool_to_integer :: [Bool] -> Integer; bool_to_integer = mkInteger True . map from_bits . nchunk 31; bytestring_to_integer_opt :: B.ByteString -> Integer; bytestring_to_integer_opt = bool_to_integer . concatMap to_bits . B.unpack; rep255 :: Int64 -> Integer; rep255 data_length = bool_to_integer $ genericReplicate (8*data_length) True; base10_length :: Integer -> Int; base10_length x = 1 + I# (integerLogBase# 10 x); equivalent_decimal_length_opt :: Int64 -> Integer; equivalent_decimal_length_opt = fromIntegral . base10_length . rep255; to_dec_padded_opt :: B.ByteString -> String; to_dec_padded_opt s = reverse $ genericTake (equivalent_decimal_length_opt $ B.length s) $ (reverse $ show $ bytestring_to_integer_opt s) ++ repeat '0'; } --end