EuCrypt Chapter 8: Bit-Level Keccak Sponge



February 1st, 2018 by Diana Coman

~ This is part of the EuCrypt series. Start with Introducing EuCrypt. ~

Implementing the Keccak Sponge at bit-level turns out to be a more enjoyable experience than the previous contortions for a "word"-level (64 bits to be precise) version of the sponge. The implementation itself is more straightforward and the resulting code really is way clearer and easier to follow, especially as it takes advantage of Ada's very convenient modular types. And as a bonus side effect, working at bit level means also that there really is no need anymore for importing those gnat-specific methods that I never wanted in the first place. As to the "but it's going to be slooooooow!" worries, I'll leave those for later: at this stage the goal is to have a reference implementation that is first of all clear and easy to understand. Once this is available, I can look into the speed issue and evaluate if needed the degree to which it really is an issue for Eulora's needs at any rate. Not to mention the fact that a bit-level Keccak does not in any way mean that a word-level Keccak cannot be made as well.

Without further delay, let's see what this patch adds: first of all a new component for EuCrypt, namely smg_bit_keccak. I decided to keep this bit-level implementation separate from the word-level one because I see this implementation as an alternative rather than a replacement necessarily. As a result, this chapter's vpatch will fork directly from EuCrypt's genesis yet again and to make this clear, I edited the eucrypt/README file first, adding the full list of current components of EuCyrpt:

Components:
1. mpi
  Arbitrary length integers and operations.
  Implemented in C.

2. smg_bit_keccak
  Bit-level implementation of the Keccak sponge according to The Keccak Reference v 3.0.
  Implemented in Ada.

3. smg_keccak
  Word (64 bits) level implementation of the Keccak sponge according to The Keccak Reference v 3.0.
  Implemented in Ada.

4. smg_serpent
  Serpent hash method.
  Implemented in Ada.

5. smg_rsa
  RSA implementation using TMSR specification.
  Implemented in C.

6. smg_comm
  Communications for Eulora (server <-> client). Relies on all the other components.

The description of the SMG_Bit_Keccak package is quite similar to that of the previous SMG_Keccak. The main difference is that the lanes of a Keccak state (i.e. the Z dimension) are now arrays of bits rather than values modulo 2^Z_Length. Reflecting this, the Bitword type is an array of Bit with index of ZCoord type specifically. The Sponge procedure itself has the very same signature since it still receives a Bitstream and a Keccak_Rate as input, while spitting a different Bitstream as output. There is no "Plane" type anymore because it is not actually needed when working at bit-level. The resulting public part of the SMG_Bit_Keccak package definition in eucrypt/smg_bit_keccak/smg_bit_keccak.ads:

 -- S.MG bit-level implementation of Keccak-f permutations
 -- (Based on The Keccak Reference, Version 3.0, January 14, 2011, by
 --   Guido Bertoni, Joan Daemen, Michael Peeters and Gilles Van Assche)

 -- S.MG, 2018

package SMG_Bit_Keccak is
	pragma Pure(SMG_Bit_Keccak);  --stateless, no side effects -> can cache calls

  --knobs (can change as per keccak design but fixed here for S.MG purposes)--
  Keccak_L: constant := 6;  --gives keccak z dimension of 2^6=64 bits and
                            --therefore keccak function 1600 with current
                            --constants (5*5*2^6)

  --constants: dimensions of keccak state and number of rounds
  XY_Length: constant := 5;
  Z_Length: constant := 2 ** Keccak_L;
  Width: constant := XY_Length * XY_Length * Z_Length;
  N_Rounds: constant := 12 + 2 * Keccak_L;

  --types
  type XYCoord is mod XY_Length;
  type ZCoord is mod Z_Length;
  type Round_Index is mod N_Rounds;

  type Bit is mod 2;
  type Bitstream is array( Natural range <> ) of Bit; -- any length; message
  type Bitword is array( ZCoord ) of Bit; -- a keccak "word" of bits

  type State is array( XYCoord, XYCoord ) of Bitword; -- the full keccak state

  type Round_Constants is array(Round_Index) of Bitword; --magic keccak values

  -- rate can be chosen by caller at each call, between 1 and width of state
  -- higher rate means sponge "eats" more bits at a time but has fewer bits in
  --   the "secret" part of the state (i.e. lower capacity)
  subtype Keccak_Rate is Positive range 1..Width;  -- capacity = width - rate

  -- public function, the sponge itself
  -- Keccak sponge structure using Keccak_Function, Pad and a given bitrate;
  -- Input - the stream of bits to hash (the message)
  -- Block_Len - the bitrate to use; this is effectively the block length
  --             for splitting Input AND squeezing output between scrambles
  -- Output - a bitstream of desired size for holding output
  procedure Sponge(Input      : in Bitstream;
                   Block_Len  : in Keccak_Rate;
                   Output     : out Bitstream);

In the private part of SMG_Bit_Keccak, there are 3 new methods, namely Next_Pos, First_Pos and BWRotate_Left. As you might guess, BWRotate_Left rotates a given Bitword to the left by the specified number of bits. This effectively replaces the previous gnat-specific Rotate_Left method and is used by one of the Keccak transformations of state. The First_Pos effectively sets the X, Y, Z coordinates to point to the first bit of the Keccak state. It's implemented as a method on its own because it is used in several places and moreover because the "first" position in the cuboid is at the end of the day a matter of convention. Similarly, Next_Pos receives a set of 3 values (X, Y, Z) and changes those to point to the *next* bit in the Keccak state. Once again, what constitutes "next" is a matter of convention - basically it depends on the direction in which one moves along the Z, Y and X dimensions.

private
  -- these are internals of the keccak implementation, not meant to be directly
  --  accessed/used
  -- moving one bit forwards in Keccak state
  procedure Next_Pos( X : in out XYCoord;
                      Y : in out XYCoord;
                      Z : in out ZCoord
                    );
  -- set coordinates to first bit of Keccak state
  procedure First_Pos( X : out XYCoord;
                       Y : out XYCoord;
                       Z : out ZCoord
                     );

  -- operations with Bitwords
  function BWRotate_Left( Input: in Bitword;
                          Count: in Natural)
                          return Bitword;

The rest of the SMG_Bit_Keccak package contains the SqueezeBlock and AbsorbBlock helper methods, the 5 Keccak transformations of state (Theta, Rho, Pi, Chi and Iota) and the Keccak function that does a full scramble of state by calling all the transformations together in the correct order and with the corresponding constants for each round. The only difference with respect to the word-level implementation is the way in which the round constants are given: here they are directly given as Bitword so arrays of bits. Moreover, the order of the bits in the array corresponds to the convention adopted for the Z dimension in this implementation:

  -- this will squeeze Block'Length bits out of state S
  -- NO scramble of state in here!
  -- NB: make SURE that Block'Length is the correct bitrate for this sponge
  -- in particular, Block'Length should be a correct bitrate aka LESS than Width
  procedure SqueezeBlock( Block: out Bitstream; S: in State);

  -- This absorbs into sponge the given block, modifying the state accordingly
  -- NO scramble of state in here so make sure the whole Block fits in state!
  -- NB: make SURE that Block'Length is *the correct bitrate* for this sponge
  -- in particular, Block'Length should be a correct bitrate aka LESS than Width
  procedure AbsorbBlock( Block: in Bitstream; S: in out State );

  -- Keccak magic bitwords
  RC : constant Round_Constants :=
    (
--   16#0000_0000_0000_0001#, round 0
     (0,0,0,0, 0,0,0,0, 0,0,0,0, 0,0,0,0,
      0,0,0,0, 0,0,0,0, 0,0,0,0, 0,0,0,0,
      0,0,0,0, 0,0,0,0, 0,0,0,0, 0,0,0,0,
      0,0,0,0, 0,0,0,0, 0,0,0,0, 0,0,0,1),
--   16#0000_0000_0000_8082#, round 1
     (0,0,0,0, 0,0,0,0, 0,0,0,0, 0,0,0,0,
      0,0,0,0, 0,0,0,0, 0,0,0,0, 0,0,0,0,
      0,0,0,0, 0,0,0,0, 0,0,0,0, 0,0,0,0,
      1,0,0,0, 0,0,0,0, 1,0,0,0, 0,0,1,0),
--   16#8000_0000_0000_808A#, round 2
     (1,0,0,0, 0,0,0,0, 0,0,0,0, 0,0,0,0,
      0,0,0,0, 0,0,0,0, 0,0,0,0, 0,0,0,0,
      0,0,0,0, 0,0,0,0, 0,0,0,0, 0,0,0,0,
      1,0,0,0, 0,0,0,0, 1,0,0,0, 1,0,1,0),

--   16#8000_0000_8000_8000#, round 3
     (1,0,0,0, 0,0,0,0, 0,0,0,0, 0,0,0,0,
      0,0,0,0, 0,0,0,0, 0,0,0,0, 0,0,0,0,
      1,0,0,0, 0,0,0,0, 0,0,0,0, 0,0,0,0,
      1,0,0,0, 0,0,0,0, 0,0,0,0, 0,0,0,0),

--   16#0000_0000_0000_808B#, round 4
     (0,0,0,0, 0,0,0,0, 0,0,0,0, 0,0,0,0,
      0,0,0,0, 0,0,0,0, 0,0,0,0, 0,0,0,0,
      0,0,0,0, 0,0,0,0, 0,0,0,0, 0,0,0,0,
      1,0,0,0, 0,0,0,0, 1,0,0,0, 1,0,1,1),

--   16#0000_0000_8000_0001#, round 5
     (0,0,0,0, 0,0,0,0, 0,0,0,0, 0,0,0,0,
      0,0,0,0, 0,0,0,0, 0,0,0,0, 0,0,0,0,
      1,0,0,0, 0,0,0,0, 0,0,0,0, 0,0,0,0,
      0,0,0,0, 0,0,0,0, 0,0,0,0, 0,0,0,1),

--   16#8000_0000_8000_8081#, round 6
     (1,0,0,0, 0,0,0,0, 0,0,0,0, 0,0,0,0,
      0,0,0,0, 0,0,0,0, 0,0,0,0, 0,0,0,0,
      1,0,0,0, 0,0,0,0, 0,0,0,0, 0,0,0,0,
      1,0,0,0, 0,0,0,0, 1,0,0,0, 0,0,0,1),

--   16#8000_0000_0000_8009#, round 7
     (1,0,0,0, 0,0,0,0, 0,0,0,0, 0,0,0,0,
      0,0,0,0, 0,0,0,0, 0,0,0,0, 0,0,0,0,
      0,0,0,0, 0,0,0,0, 0,0,0,0, 0,0,0,0,
      1,0,0,0, 0,0,0,0, 0,0,0,0, 1,0,0,1),

--   16#0000_0000_0000_008A#, round 8
     (0,0,0,0, 0,0,0,0, 0,0,0,0, 0,0,0,0,
      0,0,0,0, 0,0,0,0, 0,0,0,0, 0,0,0,0,
      0,0,0,0, 0,0,0,0, 0,0,0,0, 0,0,0,0,
      0,0,0,0, 0,0,0,0, 1,0,0,0, 1,0,1,0),

--   16#0000_0000_0000_0088#, round 9
     (0,0,0,0, 0,0,0,0, 0,0,0,0, 0,0,0,0,
      0,0,0,0, 0,0,0,0, 0,0,0,0, 0,0,0,0,
      0,0,0,0, 0,0,0,0, 0,0,0,0, 0,0,0,0,
      0,0,0,0, 0,0,0,0, 1,0,0,0, 1,0,0,0),

--   16#0000_0000_8000_8009#, round 10
     (0,0,0,0, 0,0,0,0, 0,0,0,0, 0,0,0,0,
      0,0,0,0, 0,0,0,0, 0,0,0,0, 0,0,0,0,
      1,0,0,0, 0,0,0,0, 0,0,0,0, 0,0,0,0,
      1,0,0,0, 0,0,0,0, 0,0,0,0, 1,0,0,1),

--   16#0000_0000_8000_000A#, round 11
     (0,0,0,0, 0,0,0,0, 0,0,0,0, 0,0,0,0,
      0,0,0,0, 0,0,0,0, 0,0,0,0, 0,0,0,0,
      1,0,0,0, 0,0,0,0, 0,0,0,0, 0,0,0,0,
      0,0,0,0, 0,0,0,0, 0,0,0,0, 1,0,1,0),

--   16#0000_0000_8000_808B#, round 12
     (0,0,0,0, 0,0,0,0, 0,0,0,0, 0,0,0,0,
      0,0,0,0, 0,0,0,0, 0,0,0,0, 0,0,0,0,
      1,0,0,0, 0,0,0,0, 0,0,0,0, 0,0,0,0,
      1,0,0,0, 0,0,0,0, 1,0,0,0, 1,0,1,1),

--   16#8000_0000_0000_008B#, round 13
     (1,0,0,0, 0,0,0,0, 0,0,0,0, 0,0,0,0,
      0,0,0,0, 0,0,0,0, 0,0,0,0, 0,0,0,0,
      0,0,0,0, 0,0,0,0, 0,0,0,0, 0,0,0,0,
      0,0,0,0, 0,0,0,0, 1,0,0,0, 1,0,1,1),

--   16#8000_0000_0000_8089#, round 14
     (1,0,0,0, 0,0,0,0, 0,0,0,0, 0,0,0,0,
      0,0,0,0, 0,0,0,0, 0,0,0,0, 0,0,0,0,
      0,0,0,0, 0,0,0,0, 0,0,0,0, 0,0,0,0,
      1,0,0,0, 0,0,0,0, 1,0,0,0, 1,0,0,1),

--   16#8000_0000_0000_8003#, round 15
     (1,0,0,0, 0,0,0,0, 0,0,0,0, 0,0,0,0,
      0,0,0,0, 0,0,0,0, 0,0,0,0, 0,0,0,0,
      0,0,0,0, 0,0,0,0, 0,0,0,0, 0,0,0,0,
      1,0,0,0, 0,0,0,0, 0,0,0,0, 0,0,1,1),

--   16#8000_0000_0000_8002#, round 16
     (1,0,0,0, 0,0,0,0, 0,0,0,0, 0,0,0,0,
      0,0,0,0, 0,0,0,0, 0,0,0,0, 0,0,0,0,
      0,0,0,0, 0,0,0,0, 0,0,0,0, 0,0,0,0,
      1,0,0,0, 0,0,0,0, 0,0,0,0, 0,0,1,0),

--   16#8000_0000_0000_0080#, round 17
     (1,0,0,0, 0,0,0,0, 0,0,0,0, 0,0,0,0,
      0,0,0,0, 0,0,0,0, 0,0,0,0, 0,0,0,0,
      0,0,0,0, 0,0,0,0, 0,0,0,0, 0,0,0,0,
      0,0,0,0, 0,0,0,0, 1,0,0,0, 0,0,0,0),

--   16#0000_0000_0000_800A#, round 18
     (0,0,0,0, 0,0,0,0, 0,0,0,0, 0,0,0,0,
      0,0,0,0, 0,0,0,0, 0,0,0,0, 0,0,0,0,
      0,0,0,0, 0,0,0,0, 0,0,0,0, 0,0,0,0,
      1,0,0,0, 0,0,0,0, 0,0,0,0, 1,0,1,0),

--   16#8000_0000_8000_000A#, round 19
     (1,0,0,0, 0,0,0,0, 0,0,0,0, 0,0,0,0,
      0,0,0,0, 0,0,0,0, 0,0,0,0, 0,0,0,0,
      1,0,0,0, 0,0,0,0, 0,0,0,0, 0,0,0,0,
      0,0,0,0, 0,0,0,0, 0,0,0,0, 1,0,1,0),

--   16#8000_0000_8000_8081#, round 20
     (1,0,0,0, 0,0,0,0, 0,0,0,0, 0,0,0,0,
      0,0,0,0, 0,0,0,0, 0,0,0,0, 0,0,0,0,
      1,0,0,0, 0,0,0,0, 0,0,0,0, 0,0,0,0,
      1,0,0,0, 0,0,0,0, 1,0,0,0, 0,0,0,1),

--   16#8000_0000_0000_8080#, round 21
     (1,0,0,0, 0,0,0,0, 0,0,0,0, 0,0,0,0,
      0,0,0,0, 0,0,0,0, 0,0,0,0, 0,0,0,0,
      0,0,0,0, 0,0,0,0, 0,0,0,0, 0,0,0,0,
      1,0,0,0, 0,0,0,0, 1,0,0,0, 0,0,0,0),

--   16#0000_0000_8000_0001#, round 22
     (0,0,0,0, 0,0,0,0, 0,0,0,0, 0,0,0,0,
      0,0,0,0, 0,0,0,0, 0,0,0,0, 0,0,0,0,
      1,0,0,0, 0,0,0,0, 0,0,0,0, 0,0,0,0,
      0,0,0,0, 0,0,0,0, 0,0,0,0, 0,0,0,1),

--   16#8000_0000_8000_8008#, round 23
     (1,0,0,0, 0,0,0,0, 0,0,0,0, 0,0,0,0,
      0,0,0,0, 0,0,0,0, 0,0,0,0, 0,0,0,0,
      1,0,0,0, 0,0,0,0, 0,0,0,0, 0,0,0,0,
      1,0,0,0, 0,0,0,0, 0,0,0,0, 1,0,0,0)
    );

  -- Keccak transformations of the internal state
  function Theta ( Input       : in State ) return State;
  function Rho   ( Input       : in State ) return State;
  function Pi    ( Input       : in State ) return State;
  function Chi   ( Input       : in State ) return State;
  function Iota  ( Round_Const : in Bitword; Input : in State ) return State;

  -- Keccak function with block width currently 1600 (Width constant above)
  -- It simply applies *all* keccak transformations in the correct order, using
  -- the keccak magic numbers (round constants) as per keccak reference
  function Keccak_Function(Input: in State) return State;

end SMG_Bit_Keccak;

The actual implementation of the bit-level Keccak is in eucrypt/smg_bit_keccak/smg_bit_keccak.adb:

 -- S.MG, 2018

package body SMG_Bit_Keccak is

  -- public function, sponge
  procedure Sponge( Input      : in Bitstream;
                    Block_Len  : in Keccak_Rate;
                    Output     : out Bitstream) is
    Internal  : State := (others => (others => (others => 0)));
  begin
    --absorb input into sponge in a loop on available blocks, including padding
    declare
      -- number of input blocks after padding (between 2 and block_len bits pad)
      Padded_Blocks : constant Positive := 1 + (Input'Length + 1) / Block_Len;
      Padded        : Bitstream ( 1 .. Padded_Blocks * Block_Len );
      Block         : Bitstream ( 1 .. Block_Len );
    begin
      -- initialise Padded with 0 everywhere
      Padded := ( others => 0 );
      -- copy and pad input with rule 10*1
      Padded( Padded'First .. Padded'First + Input'Length - 1 ) := Input;
      Padded( Padded'First + Input'Length )                     := 1;
      Padded( Padded'Last )                                     := 1;

      -- loop through padded input and absorb block by block into sponge
      -- padded input IS a multiple of blocks, so no stray bits left
      for B in 0 .. Padded_Blocks - 1 loop
        -- first get the current block to absorb
        Block   := Padded( Padded'First + B * Block_Len ..
                           Padded'First + (B+1) * Block_Len - 1 );
        AbsorbBlock( Block, Internal );
        -- scramble state with Keccak function
        Internal := Keccak_Function( Internal );

      end loop; -- end absorb loop for blocks
    end; -- end absorb stage

    --squeeze required bits from sponge in a loop as needed
    declare
      -- full blocks per output
      BPO     : constant Natural := Output'Length / Block_Len;
      -- stray bits per output
      SPO     : constant Natural := Output'Length mod Block_Len;
      Block   : Bitstream( 1 .. Block_Len );
    begin
      -- squeeze block by block (if at least one full block is needed)
      for I in 0 .. BPO - 1 loop
        SqueezeBlock( Block, Internal );
        Output( Output'First + I * Block_Len ..
                Output'First + (I + 1) * Block_Len -1) := Block;

        -- scramble state
        Internal := Keccak_Function( Internal );
      end loop;  -- end squeezing full blocks

      -- squeeze any partial block needed (stray bits)
      if SPO > 0 then
        SqueezeBlock( Block, Internal );
        Output( Output'Last - SPO + 1 .. Output'Last ) :=
                Block( Block'First .. Block'First + SPO - 1 );
      end if; -- end squeezing partial last block (stray bits)

    end; -- end squeeze stage

  end Sponge;

  -- helper procedures for sponge absorb/squeeze

  -- NO scramble here, this will absorb ALL given block, make sure it fits!
  procedure AbsorbBlock( Block: in Bitstream; S: in out State ) is
    X, Y                  : XYCoord;
    Z                     : ZCoord;
  begin
    -- xor current block, bit by bit, into first Block'Length bits of state
    First_Pos( X, Y, Z);
    for B of Block loop
      -- xor this bit into the state
      S( X, Y )( Z ) := S( X, Y )( Z ) + B;
      -- move to next bit of the state
      Next_Pos( X, Y, Z );
    end loop;
  end AbsorbBlock;

  -- NO scramble here, this will squeeze Block'Length bits out of *same* state S
  procedure SqueezeBlock( Block: out Bitstream; S: in State) is
    X, Y    : XYCoord;
    Z       : ZCoord;
  begin
    -- start with first position of the state
    First_Pos( X, Y, Z );
    -- squeeze bit by bit, as many bits as needed to fill Block
    for I in Block'Range loop
      -- squeeze current bit from state
      Block( I ) := S( X, Y )( Z );
      -- advance to next bit of state
      Next_Pos( X, Y, Z);
    end loop;
  end SqueezeBlock;

  -- moving one bit forwards in Keccak state
  procedure Next_Pos( X : in out XYCoord;
                      Y : in out XYCoord;
                      Z : in out ZCoord
                    ) is
  begin
    Z := Z - 1;
    if Z = ZCoord'Last then
      X := X + 1;
      if X = XYCoord'First then
        Y := Y + 1;
      end if;
    end if;
  end Next_Pos;

  -- position of first bit in Keccak state
  procedure First_Pos( X : out XYCoord;
                       Y : out XYCoord;
                       Z : out ZCoord
                     ) is
  begin
    X := XYCoord'First;
    Y := XYCoord'First;
    Z := ZCoord'Last;
  end First_Pos;

  -- operations with Bitwords
  function BWRotate_Left( Input: in Bitword;
                          Count: in Natural)
                          return Bitword is
    Output  : Bitword;
    Advance : constant ZCoord := ZCoord( Count mod Z_Length );
  begin
    for I in ZCoord loop
      Output( I ) := Input( I + Advance );
    end loop;
    return Output;
  end BWRotate_Left;

  -- Keccak transformations of the internal state
  function Theta ( Input       : in State) return State is
    Output : State;
    S1, S2 : Bit;
  begin
    for X in XYCoord loop
      for Y in XYCoord loop
        for Z in ZCoord loop
          S1 := 0;
          S2 := 0;
          for Y1 in XYCoord loop
            S1 := S1 + Input( X - 1, Y1 )( Z );
            -- Z direction is opposite to the one assumed in the ref so Z + 1
            S2 := S2 + Input( X + 1, Y1 )( Z + 1 );
          end loop;
          Output( X, Y )(Z) := Input( X, Y )( Z ) + S1 + S2;
        end loop;
      end loop;
    end loop;

    return Output;
  end Theta;

  function Rho   ( Input       : in State) return State is
    Output      : State;
    X, Y, Old_Y : XYCoord;
  begin
    Output( 0, 0) := Input( 0, 0);
    X := 1;
    Y := 0;

    for T in 0 .. 23 loop
      Output(X, Y) := BWRotate_Left(Input(X,Y), (T+1)*(T+2)/2);
      Old_Y := Y;
      Y := 2 * X + 3 * Y;
      X := Old_Y;
    end loop;
    return Output;
  end Rho;

  function Pi    ( Input       : in State) return State is
    Output : State;
  begin
    for X in XYCoord loop
      for Y in XYCoord loop
        Output( Y, 2 * X + 3 * Y ) := Input( X, Y );
      end loop;
    end loop;

    return Output;
  end Pi;

  function Chi   ( Input       : in State) return State is
    Output : State;
  begin
    for Y in XYCoord loop
      for X in XYCoord loop
        for Z in ZCoord loop
          Output(X, Y)(Z) :=   Input( X, Y )( Z ) +
                             ( Input( X + 1, Y )( Z ) + 1 ) *
                             ( Input( X + 2, Y )( Z )     );
        end loop;
      end loop;
    end loop;

    return Output;
  end Chi;

  function Iota  ( Round_Const : in Bitword; Input : in State) return State is
    Output : State;
  begin
    Output := Input;
    for Z in ZCoord loop
      Output( 0, 0 )(Z) := Input( 0, 0 )( Z ) + Round_Const( Z );
    end loop;
    return Output;
  end Iota;

  function Keccak_Function(Input: in State) return State is
    Output: State;
  begin
    Output := Input;
    for I in Round_Index loop
      Output := Iota(RC(I), Chi(Pi(Rho(Theta(Output)))));
    end loop;

    return Output;
  end Keccak_Function;

end SMG_Bit_Keccak;

Note in the above that the Sponge, AbsorbBlock and SqueezeBlock methods are rather simpler than they used to be. Absorbing/squeezing one block is now simply a matter of reading bit by bit from the Keccak state from the starting position and up to the block length. While one could arguably read Bitword by Bitword rather than bit by bit, I kept it bit by bit for clarity for now. Moreover, when absorbing a block, the xor would still need to be performed bit by bit essentially since the Z dimension of the state is defined as an array of bits rather than a value.

The Next_Pos procedure above takes advantage of the fact that all coordinates in a Keccak sponge are modular types so they will automatically wrap-around as needed. Consequently, to advance one position further, it's enough to decrease the Z coordinate (by convention movement is in the negative direction of the Z axis here) and then, if needed, to increase X in order to move on to a different Bitword and/or possibly Y as well in order to move on to a different plane of the cuboid too.

The First_Pos procedure simply sets X, Y and Z to match the convention that movement in a Keccak state happens in the positive direction of the X and Y axes but in the negative direction of the Z axis.

The Theta transformation of the state is a direct implementation of Theta's definition, working directly bit by bit. By contrast, the implementation from the previous chapter used the algorithm given in the reference paper, which took advantage of the fact that lanes were represented as values. However, this bit-level implementation does not gain anything from using that algorithm (on the contrary, it would end up with even more operations) so the direct implementation of Theta's definition is preferred. Note that the "Z-1" from Theta's definition effectively means "the bit before Z", which translates to "Z+1" with the current convention for movement on the Z axis. The rest of the Keccak transformations remain quite similar to the previous implementation.

As usual, there are some automated tests using existing test vectors for the transformations as well as for the sponge itself. The long of it is in eucrypt/smg_bit_keccak/tests/smg_bit_keccak-test.adb:

with SMG_Bit_Keccak; use SMG_Bit_Keccak;
with Ada.Exceptions; use Ada.Exceptions;
with Ada.Text_IO; use Ada.Text_IO;
with Ada.Strings.Fixed; use Ada.Strings.Fixed;
with Interfaces; use Interfaces;

procedure SMG_Bit_Keccak.Test is
  --types
  type Keccak_Perms is ( None, Theta, Rho, Pi, Chi, Iota );
  type Test_Vector  is array( Keccak_Perms ) of State;
  type Test_Round   is array( Round_Index ) of Test_Vector;
  subtype Hexstring is String( 1 .. Z_Length / 4 ); --word as hex string
  subtype Bitstring is String( 1 .. Z_Length ); -- word as binary string
  type Bithex       is array( 0 .. 3 ) of Bit;

  -- helper methods
  procedure HexCharToBit( H : in Character; B: out Bithex) is
  begin
    case H is
      when '0' => B := (0, 0, 0, 0);
      when '1' => B := (0, 0, 0, 1);
      when '2' => B := (0, 0, 1, 0);
      when '3' => B := (0, 0, 1, 1);
      when '4' => B := (0, 1, 0, 0);
      when '5' => B := (0, 1, 0, 1);
      when '6' => B := (0, 1, 1, 0);
      when '7' => B := (0, 1, 1, 1);
      when '8' => B := (1, 0, 0, 0);
      when '9' => B := (1, 0, 0, 1);
      when 'A' => B := (1, 0, 1, 0);
      when 'B' => B := (1, 0, 1, 1);
      when 'C' => B := (1, 1, 0, 0);
      when 'D' => B := (1, 1, 0, 1);
      when 'E' => B := (1, 1, 1, 0);
      when 'F' => B := (1, 1, 1, 1);
      when others => null;
    end case;
  end HexCharToBit;

  function HexToBitword( H: in Hexstring ) return Bitword is
    BW         : Bitword;
    B1, B2     : Bithex;
    PosH, PosB : Natural;
  begin
    -- read the hexstring octet by octet
    for I in 1 .. Z_Length / 8 loop
      PosH := Integer(H'First) + (I - 1) * 2;
      HexCharToBit( H(PosH), B1 );
      HexCharToBit( H(PosH + 1), B2 );

      PosB := Integer(BW'First) + (I - 1) * 8;
      for J in 0 .. 3 loop
        BW ( ZCoord(PosB + J) ) := B1(J);
        BW ( ZCoord(PosB + 4 + J) ) := B2(J);
      end loop;
    end loop;
    return BW;
  end HexToBitword;

  -- prints one bitword as an array of bits
  procedure print_bitword( B: in Bitword ) is
    bstr: Bitstring;
  begin
    for I in ZCoord loop
      if B( I ) > 0 then
        bstr( Bitstring'First + Integer(I) ) := '1';
      else
        bstr( Bitstring'First + Integer(I) ) := '0';
      end if;
    end loop;
    Put(bstr);
  end print_bitword;

  -- prints a keccak state, bitword by bitword
  procedure print_state( S: in State; Title: in String) is
  begin
    Put_Line("---------" & Title & "---------");
    for Y in XYCoord loop
      for X in XYCoord loop
        Put( "S(" & XYCoord'Image(X) & ", " & XYCoord'Image(Y) & ")= ");
        print_bitword( S( X, Y ) );
        new_line(1);
      end loop;
    end loop;
  end print_state;

  function read_state(File: in FILE_TYPE; Oct: Positive :=8) return State is
    S: State;
    Line1: String := "0000000000000000 " &
                     "0000000000000000 " &
                     "0000000000000000 " &
                     "0000000000000000 " &
                     "0000000000000000";
    StartPos, EndPos: Positive;
    Len: Positive := Oct*2;
    HStr: Hexstring;
  begin
    for Y in XYCoord loop
      Line1 := Get_Line(File);
      StartPos := Line1'First;
      EndPos := StartPos + Len-1;

      for X in XYCoord loop
        HStr := Line1( StartPos .. EndPos );
        S( X, Y ) := HexToBitword(HStr);
        StartPos := EndPos + 2;	--one space to skip
        EndPos := StartPos + Len - 1;
      end loop;
    end loop;
    return S;
  end read_state;

  --reads a full test round from specified file (pre-defined format)
  function read_from_file (filename : in String;
                           T        : out Test_Round)
                           return Boolean is
    file: FILE_TYPE;
    InputMarker: String := "lanes as 64-bit words:";
    octets: Positive := 8;
    RoundNo: Round_Index;
  begin
    -- try to open the input file
    begin
      open(file, In_File, filename);
    exception
      when others =>
        Put_Line(Standard_Error,
                 "Can not open the file '" & filename & "'. Does it exist?");
        return False;
    end;

  -- find & read input state first
    RoundNo := -1;
    loop
      declare
        Line: String := Get_Line(file);
      begin
        --check if this is test data of any known kind
        if index(Line, InputMarker, 1) > 0 then
          T(0)(None) := read_state(file, octets);
          print_state(T(0)(None), "Read Input State");
        elsif index(Line, "Round ", 1) > 0 then
          RoundNo := RoundNo +1;
        elsif index(Line, "theta", 1) > 0 then
          T(RoundNo)(Theta) := read_state(file, octets);
          if (RoundNo > 0) then
            T(RoundNo)(None) := T(RoundNo-1)(Iota);  -- previous state as input
          end if;
        elsif index(Line, "rho", 1) > 0 then
          T(RoundNo)(Rho) := read_state(file, octets);
        elsif index(Line, "pi", 1) > 0 then
          T(RoundNo)(Pi) := read_state(file, octets);
        elsif index(Line, "chi", 1) > 0 then
          T(RoundNo)(Chi) := read_state(file, octets);
        elsif index(Line, "iota", 1) > 0 then
          T(RoundNo)(Iota) := read_state(file, octets);
        end if;
        exit when End_Of_File(file);
      end;
    end loop;
    Close(file);
    return True;
  end read_from_file;

  -- performs one single round of Keccak, step by step
  -- each permutation is tested separately
  -- test fails with exception raised at first output not matching expected
  procedure test_one_round(T: Test_Vector; Round: Round_Index) is
    Input: State;
    Expected: State;
    Output: State;
    Test_One_Round_Fail: Exception;
  begin
    Input := T(None);
    for I in Keccak_Perms range Theta..Iota loop
      Expected := T(I);
      case I is
        when Theta  => Output := SMG_Bit_Keccak.Theta(Input);
        when Rho    => Output := SMG_Bit_Keccak.Rho(Input);
        when Pi     => Output := SMG_Bit_Keccak.Pi(Input);
        when Chi    => Output := SMG_Bit_Keccak.Chi(Input);
        when Iota   => Output := SMG_Bit_Keccak.Iota(RC(Round), Input);
        when others => null;
      end case;

      if (Output /= Expected) then
        print_state(Output, "----------real output-------");
        print_state(Expected, "----------expected output--------");
        raise Test_One_Round_Fail;
      else
        Put_Line("PASSED: " & Keccak_Perms'Image(I));
      end if;
      -- get ready for next permutation
      Input := Expected;
    end loop;
  end test_one_round;

  procedure test_bwrotate_left( Input    : in Bitword;
                                N        : Positive;
                                Expected : in Bitword) is
    Output: Bitword;
  begin
    Output := BWRotate_Left( Input, N );
    if Output /= Expected then
      Put_Line("FAIL: test bitword rotate left");
      Put_Line("Output:");
      print_bitword( Output );
      Put_Line("Expected:");
      print_bitword( Expected );
    else
      Put_Line("PASS: test bitword rotate left");
    end if;
  end test_bwrotate_left;

  procedure test_keccak_function(T: in Test_Round) is
    S: State;
  begin
    Put_Line("---Full Keccak Function test---");
    S := Keccak_Function(T(Round_Index'First)(None));
    if S /= T(Round_Index'Last)(Iota) then
      Put_Line("FAILED: full keccak function test");
    else
      Put_Line("PASSED: full keccak function test");
    end if;
  end test_keccak_function;

  procedure test_sponge is
    Bitrate   : constant Keccak_Rate := 1344;
    Input1    : Bitstream( 1 .. 5 ) := (1, 1, 0, 0, 1);
    Input2    : Bitstream( 1 .. 30) := (1, 1, 0, 0,
                                        1, 0, 1, 0,
                                        0, 0, 0, 1,
                                        1, 0, 1, 0,
                                        1, 1, 0, 1,
                                        1, 1, 1, 0,
                                        1, 0, 0, 1,
                                        1, 0);
    Hex       : array(0..15) of Character := ("0123456789ABCDEF");
    C         : Natural;
    ExpHex1   : constant String :=
              "CB7FFB7CE7572A06C537858A0090FC2888C3C6BA9A3ADAB4"&
              "FE7C9AB4EFE7A1E619B834C843A5A79E23F3F7E314AA597D"&
              "9DAD376E8413A005984D00CF954F62F59EF30B050C99EA64"&
              "E958335DAE684195D439B6E6DFD0E402518B5E7A227C48CF"&
              "239CEA1C391241D7605733A9F4B8F3FFBE74EE45A40730ED"&
              "1E2FDEFCCA941F518708CBB5B6D5A69C30263267B97D7B29"&
              "AC87043880AE43033B1017EFB75C33248E2962892CE69DA8"&
              "BAF1DF4C0902B16C64A1ADD42FF458C94C4D3B0B32711BBA"&
              "22104989982543D1EF1661AFAF2573687D588C81113ED7FA"&
              "F7DDF912021FC03D0E98ACC0200A9F7A0E9629DBA33BA0A3"&
              "C03CCA5A7D3560A6DB589422AC64882EF14A62AD9807B353"&
              "8DEE1548194DBD456F92B568CE76827F41E0FB3C7F25F3A4"&
              "C707AD825B289730FEBDFD22A3E742C6FB7125DE0E38B130"&
              "F3059450CA6185156A7EEE2AB7C8E4709956DC6D5E9F99D5"&
              "0A19473EA7D737AC934815D68C0710235483DB8551FD8756"&
              "45692B4E5E16BB9B1142AE300F5F69F43F0091D534F372E1"&
              "FFC2E522E71003E4D27EF6ACCD36B2756FB5FF02DBF0C96B"&
              "CAE68E7D6427810582F87051590F6FB65D7B948A9C9D6C93"&
              "AF4562367A0AD79109D6F3087C775FE6D60D66B74F8D29FB"&
              "4BA80D0168693A748812EA0CD3CA23854CC84D4E716F4C1A"&
              "A3B340B1DED2F304DFDBACC1D792C8AC9A1426913E3F67DB"&
              "790FD5CFB77DAA29";
    ExpHex2   : constant String :=
              "35F4FBA9D29E833B1DB17CA2077C11B3348C8AF2A29344AE"&
              "6AAA1F63FC4536CE795C54F0359953B97CEA27491691E93E"&
              "E4829EAB388211E6E8BD3EDA74366D0947DFA3D65D127593"&
              "0AFC42884B7324717DCB003D7B3B5C2E92B84F478CC8DBB5"&
              "174EB4BAC6207BD22E56FCC6E5FB11BC598FDBE6208913CE"&
              "34BC03837FDBFCDFF9407D948531B5FC7FFE7029F30E7EDC"&
              "F9282F0A630FA99839776F5EEA485449F62E421552AF9571";
    HexStr1   : String( 1 .. ExpHex1'Length );
    Output1   : Bitstream( 1 .. ExpHex1'Length * 4 );
    HexStr2   : String( 1 .. ExpHex2'Length );
    Output2   : Bitstream( 1 .. ExpHex2'Length * 4 );
    Error     : Natural;
    Pos       : Natural;
    HexPos    : Natural;
  begin

  -- test 1
    Put_Line("---sponge test 1---");
    Sponge(Input1, Bitrate, Output1);
    Put_Line("Input is:");
    for I of Input1 loop
      Put(Bit'Image(I));
    end loop;
    new_line(1);

    Put_Line("Output is:");
    for I of Output1 loop
      Put(Bit'Image(I));
    end loop;
    new_line(1);

    Error := 0;
    for I in 1..Output1'Length/4 loop
      Pos := Output1'First + (I-1)*4;
      C := Natural( Output1( Pos ) ) +
           Natural( Output1( Pos + 1 ) ) * 2 +
           Natural( Output1( Pos + 2 ) ) * 4 +
           Natural( Output1( Pos + 3 ) ) * 8;
      HexPos := I + 2 * ( I mod 2 ) - 1;
			Hexstr1( HexPos ) := Hex(C);
      if Hexstr1( HexPos ) /= ExpHex1( HexPos ) then
        Error := Error + 1;
      end if;
    end loop;
    Put_Line("Expected: ");
    Put_Line(ExpHex1);
    Put_Line("Obtained: ");
    Put_Line(Hexstr1);
    Put_Line("Errors found: " & Natural'Image(Error));

  -- test 2
    Put_Line("---sponge test 2---");
    Sponge(Input2, Bitrate, Output2);
    Put_Line("Input is:");
    for I of Input2 loop
      Put(Bit'Image(I));
    end loop;
    new_line(1);

    Put_Line("Output is:");
    for I of Output2 loop
      Put(Bit'Image(I));
    end loop;
    new_line(1);

    Error := 0;
    for I in 1..Output2'Length/4 loop
      Pos := Output2'First + (I-1)*4;
      C := Natural( Output2( Pos ) ) +
           Natural( Output2( Pos + 1 ) ) * 2 +
           Natural( Output2( Pos + 2 ) ) * 4 +
           Natural( Output2( Pos + 3 ) ) * 8;
      HexPos := I + 2 * ( I mod 2 ) - 1;
			Hexstr2( HexPos ) := Hex(C);
      if Hexstr2( HexPos ) /= ExpHex2( HexPos ) then
        Error := Error + 1;
      end if;
    end loop;
    Put_Line("Expected: ");
    Put_Line(ExpHex2);
    Put_Line("Obtained: ");
    Put_Line(Hexstr2);
    Put_Line("Errors found: " & Natural'Image(Error));

  end test_sponge;

  -- end of helper methods

	--variables
  T     : Test_Round;
  BW, E : Bitword;
begin
  BW:=(0,0,0,0, 0,0,0,0, 0,0,0,0, 0,0,0,0, 0,0,0,0, 0,0,0,0, 0,0,0,0, 0,0,0,0,
       0,0,0,0, 0,0,0,0, 0,0,0,0, 0,0,0,0, 0,0,0,0, 0,0,0,0, 0,0,0,0, 0,0,1,0);
  E:=(0,0,0,0, 0,0,0,0, 0,0,0,0, 0,0,0,0, 0,0,0,0, 0,0,0,0, 0,0,0,0, 0,0,0,0,
       0,0,0,0, 0,0,0,0, 0,0,0,0, 0,0,0,0, 0,0,0,0, 0,0,0,0, 0,0,0,0, 1,0,0,0);
  test_bwrotate_left(BW, 2, E);

  Put_Line("-----Testing with zero state as input------");
  if (not read_from_file("testvectorszero.txt", T)) then
    return;
  end if;

  for I in Round_Index loop
    Put_Line("---round " & Round_Index'Image(I) & "---");
    test_one_round(T(I), I);
  end loop;

  -- test also Keccak_Function as a whole --
  test_keccak_function(T);

  Put_Line("-----Testing with non-zero state as input------");
  if (not read_from_file("testvectorsnonzero.txt", T)) then
    return;
  end if;

  for I in Round_Index loop
    Put_Line("---round " & Round_Index'Image(I) & "---");
    test_one_round(T(I), I);
  end loop;

  -- test also Keccak_Function as a whole --
  test_keccak_function(T);

  -- test Sponge construction
  test_sponge;

end SMG_Bit_Keccak.Test;

To test both Keccak transformations and the sponge construction itself, I used this time only data from the existing test vectors for Keccak. While the testing of the Keccak transformations themselves did not provide any surprises, the testing of the sponge did provide a bit of a headache due to the fact that existing test data is really meant at octet (byte) level rather than bit level - both as input and as output of the sponge. While the "input bits" are given explicitly, the output is specified only in hexadecimal and it turns out that the squeezing from Keccak is *also* meant to be one octet at a time rather than 1 bit at a time. This wouldn't be a problem, of course, if it weren't for the different order in which the bits end up in the output stream depending on how you squeeze them from the state. To give an example: the "octet" 0011 0101 (or 35 in hex) is squeezed as 10101100, basically back to front.

At the moment this slight issue of bit order is "handled" outside of Keccak itself based on the reasoning that octet-level interpretation is outside of Keccak itself and therefore entirely up to the user of Keccak - they can use any rule they want regarding the value represented by 8 (or any other number) of squeezed bits. As long as the output bits from Keccak are correct and in consistent order, the implementation is correct from my point of view. However, there are of course a few other potential approaches to this and I'm still considering them. For now though, here is the .vpatch with the full bit-level Keccak transformations+sponge as described above, together with the corresponding signature:

Comments feed: RSS 2.0

3 Responses to “EuCrypt Chapter 8: Bit-Level Keccak Sponge”

  1. […] potential bit disorder trouble with Keccak highlighted at the end of the previous chapter calls for some decision to be made since a hash function won’t be of much help if bits come […]

  2. […] I finally have both Keccak at bit-level (reference version) and Keccak at word-level (working horse version because reality bytes), the […]

  3. […] cl-keccak does not seem to agree with s.mg keccak on return hashes. For instance, if we […]

Leave a Reply to EuCrypt Chapter 10: OAEP with Keccak a la TMSR in Ossasepia