{-# language ScopedTypeVariables #-}
{-# language DataKinds           #-}

module System.Nix.Internal.Truncation
  ( truncateInNixWay
  )
where

import qualified Data.ByteString        as Bytes

-- | Bytewise truncation of a 'Digest'.
--
-- When truncation length is greater than the length of the bytestring
-- but less than twice the bytestring length, truncation splits the
-- bytestring into a head part (truncation length) and tail part
-- (leftover part), right-pads the leftovers with 0 to the truncation
-- length, and combines the two strings bytewise with 'xor'.
truncateInNixWay
  :: Int -> Bytes.ByteString -> Bytes.ByteString
--  2021-06-07: NOTE: Renamed function, since truncation can be done in a lot of ways, there is no practice of truncting hashes this way, moreover:
-- 1. <https://crypto.stackexchange.com/questions/56337/strength-of-hash-obtained-by-xor-of-parts-of-sha3>
-- 2. <https://www.reddit.com/r/crypto/comments/6olqfm/ways_to_truncated_hash/>
truncateInNixWay :: Int -> ByteString -> ByteString
truncateInNixWay Int
n ByteString
c =
    [Word8] -> ByteString
Bytes.pack forall a b. (a -> b) -> a -> b
$ forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Int -> Word8
truncOutputByte [Int
0 .. Int
nforall a. Num a => a -> a -> a
-Int
1]
  where

    truncOutputByte :: Int -> Word8
    truncOutputByte :: Int -> Word8
truncOutputByte Int
i = forall (t :: * -> *) b a.
Foldable t =>
(b -> a -> b) -> b -> t a -> b
foldl' (Int -> Word8 -> Int -> Word8
aux Int
i) Word8
0 [Int
0 .. ByteString -> Int
Bytes.length ByteString
c forall a. Num a => a -> a -> a
- Int
1]

    inputByte :: Int -> Word8
    inputByte :: Int -> Word8
inputByte Int
j = HasCallStack => ByteString -> Int -> Word8
Bytes.index ByteString
c Int
j

    aux :: Int -> Word8 -> Int -> Word8
    aux :: Int -> Word8 -> Int -> Word8
aux Int
i Word8
x Int
j =
      forall a. a -> a -> Bool -> a
bool
        forall a. a -> a
id
        (forall a. Bits a => a -> a -> a
`xor` Int -> Word8
inputByte Int
j)
        (Int
j forall a. Integral a => a -> a -> a
`mod` Int
n forall a. Eq a => a -> a -> Bool
== Int
i)
        Word8
x