Skip to content

Commit

Permalink
add columnround keelung
Browse files Browse the repository at this point in the history
  • Loading branch information
oxarbitrage committed Oct 7, 2023
1 parent 0aec85c commit d6328d2
Show file tree
Hide file tree
Showing 2 changed files with 23 additions and 1 deletion.
15 changes: 14 additions & 1 deletion src/Columnround.hs
Original file line number Diff line number Diff line change
Expand Up @@ -8,9 +8,11 @@ Portability : POSIX
We treat the columnround just as `Rowround` expressions with the input transposed.
-}
{-# LANGUAGE DataKinds #-}

module Columnround
(
columnroundCompute, columnroundDisplay, columnroundEquations,
columnroundCompute, columnroundDisplay, columnroundEquations, columnroundKeelung,
)
where

Expand All @@ -20,6 +22,8 @@ import Utils
import Data.Word
import Text.Printf

import Keelung hiding (input, eq)

-- |The columnround expression computed.
columnroundCompute :: [Word32] -> [Word32]
columnroundCompute input
Expand All @@ -37,3 +41,12 @@ columnroundEquations :: [String] -> [String]
columnroundEquations input
| length input == 16 = [printf "z%d = %s" (idx :: Int) eq | (idx, eq) <- zip [0..] (columnroundDisplay input)]
| otherwise = error "input to `columnroundEquations` must be a list of 16 `String` strings"

-- |The Keelung columnround expression.
columnroundKeelung :: [UInt 32] -> Comp [UInt 32]
columnroundKeelung input
| length input == 16 = do
let new_input = transpose input
k <- rowroundKeelung new_input
return $ transpose k
| otherwise = error "input to `columnroundCompute` must be a list of 16 `Word32` numbers"
9 changes: 9 additions & 0 deletions test/unit/keelung/Spec.hs
Original file line number Diff line number Diff line change
Expand Up @@ -2,6 +2,7 @@

import Quarterround
import Rowround
import Columnround

import Test.HUnit
import Keelung
Expand Down Expand Up @@ -57,5 +58,13 @@ main = do
putStrLn "Rowround simulated for input rowroundInputUInt:"
print rowround_interpreted2

let columnround_computed = columnroundCompute rowroundInputWord32
putStrLn "Columnround computed for input rowroundInputWord32:"
print columnround_computed

columnround_interpreted2 <- interpret gf181 (columnroundKeelung rowroundInputUInt) [] []
putStrLn "Columnround simulated for input rowroundInputUInt:"
print columnround_interpreted2

-- just return an empty `Count` so we don't have to return the one from a specific test:
return (Counts 0 0 0 0)

0 comments on commit d6328d2

Please sign in to comment.