{- Convert raw data (little-endian base-256 bytes) to little-endian octal with zero-padding so that the octal may be losslessly converted back to data. Note: little-endian octal is a very unusual way of expressing octal, not the standard way which is big-endian. -} {- 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 GHC.Integer(mkInteger); import Data.Bits(testBit); import Data.Word(Word8); import Data.Char(intToDigit); main :: IO(); main = B.getContents >>= putStrLn . to_oct; oct_show_unpadded :: B.ByteString -> String; oct_show_unpadded = map (intToDigit . fromIntegral . bool_to_integer) . nchunk 3 . concatMap to_bits . B.unpack; {- expected_octal_digits :: Integer -> Integer; expected_octal_digits byte_length = case divMod (8*byte_length) 3 of { (q,0) -> q; (q,_) -> q+1; }; -} to_oct :: B.ByteString -> String; -- to_oct s = genericTake (expected_octal_digits $ fromIntegral $ B.length s) $ (reverse $ oct_show_unpadded s) ++ repeat '0'; to_oct = oct_show_unpadded; -- no need to estimate width because leading zeros don't get converted to nothing as does going through Integer 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; } --end