Skip to content

Instantly share code, notes, and snippets.

@zouppen
Created December 1, 2011 23:03
Show Gist options
  • Save zouppen/1420551 to your computer and use it in GitHub Desktop.
Save zouppen/1420551 to your computer and use it in GitHub Desktop.
A proof of concept for a low overhead datamatrix. Probable use is visualizing Instanssi demos.
-- |Pseudorandom generation for ensuring entropy and distribution of
-- the bit map.
module SlowResponse where
import System.Random -- Requires 1.0.1.0
import Data.Word
import Data.Bits
-- import Data.Tuple (swap) -- Requires base 4.3
import Data.ByteString.Lazy (ByteString)
import qualified Data.ByteString.Lazy as B
import Data.Digest.CRC32
import Control.Arrow (second)
import Data.Binary.Put
import Control.Monad (when)
-- |Mutilates data using a random generator state. Mutilation function
-- is xor, so this is bi-directional.
mutilate :: (RandomGen g) => g -> ByteString -> ByteString
mutilate initG bytes = snd $ B.mapAccumL randXor initG bytes
where randXor g a = second (xor a) $ swap $ random g
swap (a,b) = (b,a)
-- |Builds a bit map of data. Note that the seed function is just 8
-- bits because the only reason is to keep the data looking a nice
-- square. No cryptography involved.
build :: Word8 -> ByteString -> ByteString
build seed bytes = runPut $ do
putWord8 seed -- 8 bits of seed is enough for everybody.
putWord32be $ crc32 message
putLazyByteString $ mutilate g message
where
g = mkStdGen $ fromIntegral seed
message = runPut $ do
-- Size of 64 kibibytes will be encoded as zeros.
let size = B.length bytes
when (size < 1) $
fail "Your product is zero-length"
when (size > 2^16) $
fail "Your product is too lame. Maximum size is 64 kibibytes."
putWord16be $ fromIntegral $ size
putLazyByteString bytes
-- Not very efficient way to turn a byte array into bits.
toBits :: ByteString -> [Bool]
toBits bytes = concatMap bits $ B.unpack bytes
where bits a = map (testBit a) [7,6..0]
Sign up for free to join this conversation on GitHub. Already have an account? Sign in to comment