-
Notifications
You must be signed in to change notification settings - Fork 102
Commit
This commit does not belong to any branch on this repository, and may belong to a fork outside of the repository.
- Loading branch information
Showing
8 changed files
with
206 additions
and
0 deletions.
There are no files selected for viewing
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
Original file line number | Diff line number | Diff line change |
---|---|---|
@@ -0,0 +1,171 @@ | ||
{-# LANGUAGE OverloadedStrings #-} | ||
{-# LANGUAGE TypeOperators #-} | ||
{-# LANGUAGE DataKinds #-} | ||
{-# LANGUAGE DeriveAnyClass #-} | ||
{-# LANGUAGE DeriveGeneric #-} | ||
|
||
module Crypto.Hash.PoseidonNative (poseidonDefs, poseidon) where | ||
|
||
import Pact.Types.Runtime | ||
import Pact.Native.Internal | ||
|
||
poseidonDefs :: NativeModule | ||
poseidonDefs = ("PoseidonHash", [ poseidonDef ]) | ||
|
||
modulus :: Integer | ||
modulus = 21888242871839275222246405745257275088548364400416034343698204186575808495617 | ||
|
||
mulmod :: Integer -> Integer -> Integer | ||
mulmod a b = (a * b) `mod` modulus | ||
|
||
summod :: Integer -> Integer -> Integer | ||
summod a b = (a + b) `mod` modulus | ||
|
||
sig :: Integer -> Integer | ||
sig inVal = | ||
let in2 = mulmod inVal inVal | ||
in4 = mulmod in2 in2 | ||
in mulmod in4 inVal | ||
|
||
ark :: Integer -> Integer -> Integer | ||
ark inVal cc = summod inVal cc | ||
|
||
getMatrix :: Int -> Int -> Integer | ||
getMatrix i j = m_data !! i !! j | ||
where m_data = | ||
[ [ 12711080208452642132636348910936535131635469619255658927004323269777977499766, 11739432287187184656569880828944421268616385874806221589758215824904320817117, 4977258759536702998522229302103997878600602264560359702680165243908162277980] | ||
, [ 18634098492055214324873285470566015538548967469826511946578953323931218028182, 16872301185549870956030057498946148102848662396374401407323436343924021192350, 107933704346764130067829474107909495889716688591997879426350582457782826785] | ||
, [ 10964855577711430604889230155222964616951177623752692235240949905229827667414, 18618317300596756144100783409915332163189452886691331959651778092154775572832, 13596762909635538739079656925495736900379091964739248298531655823337482778123] | ||
] | ||
|
||
c :: Int -> Integer | ||
c i = cData !! i | ||
where | ||
cData = [14397397413755236225575615486459253198602422701513067526754101844196324375522, | ||
10405129301473404666785234951972711717481302463898292859783056520670200613128, | ||
5179144822360023508491245509308555580251733042407187134628755730783052214509, | ||
9132640374240188374542843306219594180154739721841249568925550236430986592615, | ||
20360807315276763881209958738450444293273549928693737723235350358403012458514, | ||
17933600965499023212689924809448543050840131883187652471064418452962948061619, | ||
3636213416533737411392076250708419981662897009810345015164671602334517041153, | ||
2008540005368330234524962342006691994500273283000229509835662097352946198608, | ||
16018407964853379535338740313053768402596521780991140819786560130595652651567, | ||
20653139667070586705378398435856186172195806027708437373983929336015162186471, | ||
17887713874711369695406927657694993484804203950786446055999405564652412116765, | ||
4852706232225925756777361208698488277369799648067343227630786518486608711772, | ||
8969172011633935669771678412400911310465619639756845342775631896478908389850, | ||
20570199545627577691240476121888846460936245025392381957866134167601058684375, | ||
16442329894745639881165035015179028112772410105963688121820543219662832524136, | ||
20060625627350485876280451423010593928172611031611836167979515653463693899374, | ||
16637282689940520290130302519163090147511023430395200895953984829546679599107, | ||
15599196921909732993082127725908821049411366914683565306060493533569088698214, | ||
16894591341213863947423904025624185991098788054337051624251730868231322135455, | ||
1197934381747032348421303489683932612752526046745577259575778515005162320212, | ||
6172482022646932735745595886795230725225293469762393889050804649558459236626, | ||
21004037394166516054140386756510609698837211370585899203851827276330669555417, | ||
15262034989144652068456967541137853724140836132717012646544737680069032573006, | ||
15017690682054366744270630371095785995296470601172793770224691982518041139766, | ||
15159744167842240513848638419303545693472533086570469712794583342699782519832, | ||
11178069035565459212220861899558526502477231302924961773582350246646450941231, | ||
21154888769130549957415912997229564077486639529994598560737238811887296922114, | ||
20162517328110570500010831422938033120419484532231241180224283481905744633719, | ||
2777362604871784250419758188173029886707024739806641263170345377816177052018, | ||
15732290486829619144634131656503993123618032247178179298922551820261215487562, | ||
6024433414579583476444635447152826813568595303270846875177844482142230009826, | ||
17677827682004946431939402157761289497221048154630238117709539216286149983245, | ||
10716307389353583413755237303156291454109852751296156900963208377067748518748, | ||
14925386988604173087143546225719076187055229908444910452781922028996524347508, | ||
8940878636401797005293482068100797531020505636124892198091491586778667442523, | ||
18911747154199663060505302806894425160044925686870165583944475880789706164410, | ||
8821532432394939099312235292271438180996556457308429936910969094255825456935, | ||
20632576502437623790366878538516326728436616723089049415538037018093616927643, | ||
71447649211767888770311304010816315780740050029903404046389165015534756512, | ||
2781996465394730190470582631099299305677291329609718650018200531245670229393, | ||
12441376330954323535872906380510501637773629931719508864016287320488688345525, | ||
2558302139544901035700544058046419714227464650146159803703499681139469546006, | ||
10087036781939179132584550273563255199577525914374285705149349445480649057058, | ||
4267692623754666261749551533667592242661271409704769363166965280715887854739, | ||
4945579503584457514844595640661884835097077318604083061152997449742124905548, | ||
17742335354489274412669987990603079185096280484072783973732137326144230832311, | ||
6266270088302506215402996795500854910256503071464802875821837403486057988208, | ||
2716062168542520412498610856550519519760063668165561277991771577403400784706, | ||
19118392018538203167410421493487769944462015419023083813301166096764262134232, | ||
9386595745626044000666050847309903206827901310677406022353307960932745699524, | ||
9121640807890366356465620448383131419933298563527245687958865317869840082266, | ||
3078975275808111706229899605611544294904276390490742680006005661017864583210, | ||
7157404299437167354719786626667769956233708887934477609633504801472827442743, | ||
14056248655941725362944552761799461694550787028230120190862133165195793034373, | ||
14124396743304355958915937804966111851843703158171757752158388556919187839849, | ||
11851254356749068692552943732920045260402277343008629727465773766468466181076, | ||
9799099446406796696742256539758943483211846559715874347178722060519817626047, | ||
10156146186214948683880719664738535455146137901666656566575307300522957959544, | ||
19908645952733301583346063785055921934459499091029406575311417879963332475861, | ||
11766105336238068471342414351862472329437473380853789942065610694000443387471, | ||
11002137593249972174092192767251572171769044073555430468487809799220351297047] | ||
|
||
mix :: Integer -> Integer -> Integer -> Int -> Integer | ||
mix in1 in2 in3 i = | ||
let lc0 = 0 | ||
lc1 = summod lc0 (mulmod (getMatrix i 0) in1) | ||
lc2 = summod lc1 (mulmod (getMatrix i 1) in2) | ||
lc3 = summod lc2 (mulmod (getMatrix i 2) in3) | ||
in lc3 | ||
|
||
ca :: Integer -> Integer -> Integer -> Int -> Int -> Integer | ||
ca m0 m1 m2 j i = ark (mix m0 m1 m2 j) (c i) | ||
|
||
poseidon :: [Integer] -> Integer | ||
poseidon inputs = poseidonWithRounds nRoundsF nRoundsP rounds inputs | ||
where | ||
nRoundsF = 8 | ||
nRoundsP = 53 | ||
rounds = (nRoundsF + nRoundsP) - 1 | ||
|
||
poseidonWithRounds :: Int -> Int -> Int -> [Integer] -> Integer | ||
poseidonWithRounds nRoundsF nRoundsP rounds inputs = | ||
let | ||
-- initial state | ||
a0 = ark (inputs !! 0) (c 0) | ||
a1 = ark (inputs !! 1) (c 0) | ||
a2 = ark 0 (c 0) | ||
m0 = sig a0 | ||
m1 = sig a1 | ||
m2 = sig a2 | ||
|
||
-- iterative rounds | ||
(m0''', m1''', m2''') = foldl applyRound (m0, m1, m2) [1..rounds] | ||
|
||
-- return | ||
out = mix m0''' m1''' m2''' 0 | ||
in | ||
out | ||
where | ||
applyRound :: (Integer, Integer, Integer) -> Int -> (Integer, Integer, Integer) | ||
applyRound (m0, m1, m2) roundNumber = | ||
let a0' = ca m0 m1 m2 0 roundNumber | ||
a1' = ca m0 m1 m2 1 roundNumber | ||
a2' = ca m0 m1 m2 2 roundNumber | ||
m0' = sig a0' | ||
m1' = if (roundNumber < nRoundsF `div` 2) || (roundNumber >= nRoundsP + nRoundsF `div` 2) then sig a1' else a1' | ||
m2' = if (roundNumber < nRoundsF `div` 2) || (roundNumber >= nRoundsP + nRoundsF `div` 2) then sig a2' else a2' | ||
in (m0', m1', m2') | ||
|
||
poseidon' :: RNativeFun e | ||
poseidon' _ [TLitInteger i, TLitInteger j] = return $ toTerm $ poseidon [i, j] | ||
poseidon' i as = argsError i as | ||
|
||
poseidonDef :: NativeDef | ||
poseidonDef = defRNative | ||
"poseidon-hash" | ||
poseidon' | ||
(funType tTyInteger [("i", tTyInteger), ("j", tTyInteger)]) | ||
[ "Poseidon Hash Function." | ||
, "The Poseidon hash function is a cryptographic hash function specifically designed" | ||
, "to work efficiently with elliptic curve cryptography." | ||
, "It's particularly optimized for zero-knowledge proofs and various privacy protocols." | ||
, " " | ||
, "Usage:" | ||
, "> (poseidon-hash integer1 integer2)" | ||
, "The input is two integers, and the output is the hash result as an integer." | ||
] | ||
"Poseidon hash function." |
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
Original file line number | Diff line number | Diff line change |
---|---|---|
@@ -0,0 +1,14 @@ | ||
{-# LANGUAGE TypeOperators #-} | ||
{-# LANGUAGE DataKinds #-} | ||
|
||
module PoseidonSpec (spec) where | ||
|
||
import Test.Hspec | ||
import Crypto.Hash.PoseidonNative | ||
|
||
spec :: Spec | ||
spec = describe "poseidon" $ do | ||
describe "poseidon-hash" $ do | ||
it "computes the poseidon hash for two integers" $ do | ||
poseidon [1, 2] `shouldBe` 12717992376338182279477285556390228582603857817939167998284243525425604090033 | ||
poseidon [999999999999999999999999999999999999999999999999999999999999999999999999999999999999999999999999999999999999999999999999999999999999999999999999999999999999999999999999999999999999999999999999999999, 88888888888888888888888888888888888888888888888888888888888888888888888888888888888888888888888888888888888888888888888888888888888888888888888888888888888888888888888888888888888888888888888888888888] `shouldBe` 1069652563792426660145833190237336045845917811967528486535167837537743676741 |
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
Original file line number | Diff line number | Diff line change |
---|---|---|
@@ -0,0 +1,4 @@ | ||
;; Test poseidon-hash | ||
|
||
(expect "1 2 should equal 12717992376338182279477285556390228582603857817939167998284243525425604090033" 12717992376338182279477285556390228582603857817939167998284243525425604090033 (poseidon-hash 1 2)) | ||
(expect "999999999999999999999999999999999999999999999999999999999999999999999999999999999999999999999999999999999999999999999999999999999999999999999999999999999999999999999999999999999999999999999999999999 88888888888888888888888888888888888888888888888888888888888888888888888888888888888888888888888888888888888888888888888888888888888888888888888888888888888888888888888888888888888888888888888888888888 should equal 1069652563792426660145833190237336045845917811967528486535167837537743676741" 1069652563792426660145833190237336045845917811967528486535167837537743676741 (poseidon-hash 999999999999999999999999999999999999999999999999999999999999999999999999999999999999999999999999999999999999999999999999999999999999999999999999999999999999999999999999999999999999999999999999999999 88888888888888888888888888888888888888888888888888888888888888888888888888888888888888888888888888888888888888888888888888888888888888888888888888888888888888888888888888888888888888888888888888888888)) |