Copyright | © 2020 Herbert Valerio Riedel |
---|---|
License | GPL-2.0-or-later |
Safe Haskell | Trustworthy |
Language | Haskell2010 |
Apply XOR-masks to ByteString
s and memory regions.
Synopsis
- xor32StrictByteString :: Word32 -> ByteString -> ByteString
- xor32StrictByteString' :: Word32 -> ByteString -> (Word32, ByteString)
- xor32LazyByteString :: Word32 -> ByteString -> ByteString
- xor32ShortByteString :: Word32 -> ShortByteString -> ShortByteString
- xor32CStringLen :: Word32 -> CStringLen -> IO Word32
- xor8StrictByteString :: Word8 -> ByteString -> ByteString
- xor8LazyByteString :: Word8 -> ByteString -> ByteString
- xor8ShortByteString :: Word8 -> ShortByteString -> ShortByteString
- xor8CStringLen :: Word8 -> CStringLen -> IO ()
Apply 32-bit XOR mask
xor32StrictByteString :: Word32 -> ByteString -> ByteString Source #
Apply 32-bit XOR mask (considered as four octets in big-endian order) to ByteString
.
>>>
xor32StrictByteString 0x37fa213d "\x7f\x9f\x4d\x51\x58"
"Hello"
In other words, the 32-bit word 0x37fa213d
is taken as the infinite series of octets (
and cycle
[0x37,0xfa,0x21,0x3d])xor
ed with the respective octets from the input ByteString
.
The xor
laws give rise to the following laws:
xor32StrictByteString m (xor32StrictByteString m x) == x
xor32StrictByteString 0 x == x
xor32StrictByteString m (xor32StrictByteString n x) == xor32StrictByteString (m `xor` n) x
This function is semantically equivalent to the (less efficient) implementation shown below
xor32StrictByteString'ref :: Word32 -> BS.ByteString -> BS.ByteString xor32StrictByteString'ref 0 = id xor32StrictByteString'ref msk0 = snd . BS.mapAccumL go msk0 where go :: Word32 -> Word8 -> (Word32,Word8) go msk b = let b' = fromIntegral (msk' .&. 0xff) `xor` b msk' = rotateL msk 8 in (msk',b')
The xor32StrictByteString
implementation is about 6-7 times faster than the naive implementation above.
xor32StrictByteString' :: Word32 -> ByteString -> (Word32, ByteString) Source #
Convenience version of xor32StrictByteString
which also returns the rotated XOR-mask useful for chained masking.
>>>
xor32StrictByteString' 0x37fa213d "\x7f\x9f\x4d\x51\x58"
(0xfa213d37,"Hello")
xor32LazyByteString :: Word32 -> ByteString -> ByteString Source #
Variant of xor32StrictByteString
for masking lazy ByteString
s.
>>>
xor32LazyByteString 0x37fa213d "\x7f\x9f\x4d\x51\x58"
"Hello"
xor32ShortByteString :: Word32 -> ShortByteString -> ShortByteString Source #
Apply 32-bit XOR mask (considered as four octets in big-endian order) to ShortByteString
. See also xor32StrictByteString
.
>>>
xor32ShortByteString 0x37fa213d "\x7f\x9f\x4d\x51\x58"
"Hello"
xor32CStringLen :: Word32 -> CStringLen -> IO Word32 Source #
Apply 32-bit XOR mask (considered as four octets in big-endian order) to memory region expressed as base-pointer and size. The returned value is the input mask rotated by the word-size remained of the memory region size (useful for chained xor-masking of multiple memory-fragments).
Apply 8-bit XOR mask
xor8StrictByteString :: Word8 -> ByteString -> ByteString Source #
Apply 8-bit XOR mask to each octet of a ByteString
.
>>>
xor8StrictByteString 0x20 "Hello"
"hELLO"
This function is a faster implementation of the semantically equivalent function shown below:
xor8StrictByteString'ref :: Word8 -> BS.ByteString -> BS.ByteString xor8StrictByteString'ref 0 = id xor8StrictByteString'ref msk0 = BS.map (xor msk0)
xor8LazyByteString :: Word8 -> ByteString -> ByteString Source #
Apply 8-bit XOR mask to each octet of a lazy ByteString
.
See also xor8StrictByteString
xor8ShortByteString :: Word8 -> ShortByteString -> ShortByteString Source #
Apply 8-bit XOR mask to each octet of a ShortByteString
.
See also xor8StrictByteString
xor8CStringLen :: Word8 -> CStringLen -> IO () Source #
Apply 8-bit XOR mask to each octet of a memory region expressed as start address and length in bytes.
See also xor8StrictByteString