Update examples to use (/\) instead of (&&) where appropriate,

and to squash other warnings related to the upcomming precedence change.
This commit is contained in:
Robert Dockins 2016-08-22 18:14:44 -07:00
parent e9c8b6ccd1
commit cd9ffed00b
20 changed files with 365 additions and 129 deletions

View File

@ -124,7 +124,7 @@ Rcon : [8] -> [4]GF28
Rcon i = [(gf28Pow (<| x |>, i-1)), 0, 0, 0]
SubWord : [4]GF28 -> [4]GF28
SubWord bs = [ SubByte b | b <- bs ]
SubWord bs = [ SubByte' b | b <- bs ]
RotWord : [4]GF28 -> [4]GF28
RotWord [a0, a1, a2, a3] = [a1, a2, a3, a0]

236
examples/AES.cry Normal file
View File

@ -0,0 +1,236 @@
// Cryptol AES Implementation
// Copyright (c) 2010-2013, Galois Inc.
// www.cryptol.net
// You can freely use this source code for educational purposes.
// This is a fairly close implementation of the FIPS-197 standard:
// http://csrc.nist.gov/publications/fips/fips197/fips-197.pdf
// Nk: Number of blocks in the key
// Must be one of 4 (AES128), 6 (AES192), or 8 (AES256)
// Aside from this line, no other code below needs to change for
// implementing AES128, AES192, or AES256
module AES where
type AES128 = 4
type AES192 = 6
type AES256 = 8
type Nk = AES128
// For Cryptol 2.x | x > 0
// NkValid: `Nk -> Bit
// property NkValid k = (k == `AES128) || (k == `AES192) || (k == `AES256)
// Number of blocks and Number of rounds
type Nb = 4
type Nr = 6 + Nk
type AESKeySize = (Nk*32)
// Helper type definitions
type GF28 = [8]
type State = [4][Nb]GF28
type RoundKey = State
type KeySchedule = (RoundKey, [Nr-1]RoundKey, RoundKey)
// GF28 operations
gf28Add : {n} (fin n) => [n]GF28 -> GF28
gf28Add ps = sums ! 0
where sums = [zero] # [ p ^ s | p <- ps | s <- sums ]
irreducible = <| x^^8 + x^^4 + x^^3 + x + 1 |>
gf28Mult : (GF28, GF28) -> GF28
gf28Mult (x, y) = pmod(pmult x y) irreducible
gf28Pow : (GF28, [8]) -> GF28
gf28Pow (n, k) = pow k
where sq x = gf28Mult (x, x)
odd x = x ! 0
pow i = if i == 0 then 1
else if odd i
then gf28Mult(n, sq (pow (i >> 1)))
else sq (pow (i >> 1))
gf28Inverse : GF28 -> GF28
gf28Inverse x = gf28Pow (x, 254)
gf28DotProduct : {n} (fin n) => ([n]GF28, [n]GF28) -> GF28
gf28DotProduct (xs, ys) = gf28Add [ gf28Mult (x, y) | x <- xs
| y <- ys ]
gf28VectorMult : {n, m} (fin n) => ([n]GF28, [m][n]GF28) -> [m]GF28
gf28VectorMult (v, ms) = [ gf28DotProduct(v, m) | m <- ms ]
gf28MatrixMult : {n, m, k} (fin m) => ([n][m]GF28, [m][k]GF28) -> [n][k]GF28
gf28MatrixMult (xss, yss) = [ gf28VectorMult(xs, yss') | xs <- xss ]
where yss' = transpose yss
// The affine transform and its inverse
xformByte : GF28 -> GF28
xformByte b = gf28Add [b, (b >>> 4), (b >>> 5), (b >>> 6), (b >>> 7), c]
where c = 0x63
xformByte' : GF28 -> GF28
xformByte' b = gf28Add [(b >>> 2), (b >>> 5), (b >>> 7), d] where d = 0x05
// The SubBytes transform and its inverse
SubByte : GF28 -> GF28
SubByte b = xformByte (gf28Inverse b)
SubByte' : GF28 -> GF28
SubByte' b = sbox@b
SubBytes : State -> State
SubBytes state = [ [ SubByte' b | b <- row ] | row <- state ]
InvSubByte : GF28 -> GF28
InvSubByte b = gf28Inverse (xformByte' b)
InvSubBytes : State -> State
InvSubBytes state = [ [ InvSubByte b | b <- row ] | row <- state ]
// The ShiftRows transform and its inverse
ShiftRows : State -> State
ShiftRows state = [ row <<< shiftAmount | row <- state
| shiftAmount <- [0 .. 3]
]
InvShiftRows : State -> State
InvShiftRows state = [ row >>> shiftAmount | row <- state
| shiftAmount <- [0 .. 3]
]
// The MixColumns transform and its inverse
MixColumns : State -> State
MixColumns state = gf28MatrixMult (m, state)
where m = [[2, 3, 1, 1],
[1, 2, 3, 1],
[1, 1, 2, 3],
[3, 1, 1, 2]]
InvMixColumns : State -> State
InvMixColumns state = gf28MatrixMult (m, state)
where m = [[0x0e, 0x0b, 0x0d, 0x09],
[0x09, 0x0e, 0x0b, 0x0d],
[0x0d, 0x09, 0x0e, 0x0b],
[0x0b, 0x0d, 0x09, 0x0e]]
// The AddRoundKey transform
AddRoundKey : (RoundKey, State) -> State
AddRoundKey (rk, s) = rk ^ s
// Key expansion
Rcon : [8] -> [4]GF28
Rcon i = [(gf28Pow (<| x |>, i-1)), 0, 0, 0]
SubWord : [4]GF28 -> [4]GF28
SubWord bs = [ SubByte' b | b <- bs ]
RotWord : [4]GF28 -> [4]GF28
RotWord [a0, a1, a2, a3] = [a1, a2, a3, a0]
NextWord : ([8],[4][8],[4][8]) -> [4][8]
NextWord(i, prev, old) = old ^ mask
where mask = if i % `Nk == 0
then SubWord(RotWord(prev)) ^ Rcon (i / `Nk)
else if (`Nk > 6) && (i % `Nk == 4)
then SubWord(prev)
else prev
ExpandKeyForever : [Nk][4][8] -> [inf]RoundKey
ExpandKeyForever seed = [ transpose g | g <- groupBy`{4} (keyWS seed) ]
keyWS : [Nk][4][8] -> [inf][4][8]
keyWS seed = xs
where xs = seed # [ NextWord(i, prev, old)
| i <- [ `Nk ... ]
| prev <- drop`{Nk-1} xs
| old <- xs
]
ExpandKey : [AESKeySize] -> KeySchedule
ExpandKey key = (keys @ 0, keys @@ [1 .. (Nr - 1)], keys @ `Nr)
where seed : [Nk][4][8]
seed = split (split key)
keys = ExpandKeyForever seed
fromKS : KeySchedule -> [Nr+1][4][32]
fromKS (f, ms, l) = [ formKeyWords (transpose k) | k <- [f] # ms # [l] ]
where formKeyWords bbs = [ join bs | bs <- bbs ]
// AES rounds and inverses
AESRound : (RoundKey, State) -> State
AESRound (rk, s) = AddRoundKey (rk, MixColumns (ShiftRows (SubBytes s)))
AESFinalRound : (RoundKey, State) -> State
AESFinalRound (rk, s) = AddRoundKey (rk, ShiftRows (SubBytes s))
AESInvRound : (RoundKey, State) -> State
AESInvRound (rk, s) =
InvMixColumns (AddRoundKey (rk, InvSubBytes (InvShiftRows s)))
AESFinalInvRound : (RoundKey, State) -> State
AESFinalInvRound (rk, s) = AddRoundKey (rk, InvSubBytes (InvShiftRows s))
// Converting a 128 bit message to a State and back
msgToState : [128] -> State
msgToState msg = transpose (split (split msg))
stateToMsg : State -> [128]
stateToMsg st = join (join (transpose st))
// AES Encryption
aesEncrypt : ([128], [AESKeySize]) -> [128]
aesEncrypt (pt, key) = stateToMsg (AESFinalRound (kFinal, rounds ! 0))
where (kInit, ks, kFinal) = ExpandKey key
state0 = AddRoundKey(kInit, msgToState pt)
rounds = [state0] # [ AESRound (rk, s) | rk <- ks
| s <- rounds
]
// AES Decryption
aesDecrypt : ([128], [AESKeySize]) -> [128]
aesDecrypt (ct, key) = stateToMsg (AESFinalInvRound (kFinal, rounds ! 0))
where (kFinal, ks, kInit) = ExpandKey key
state0 = AddRoundKey(kInit, msgToState ct)
rounds = [state0] # [ AESInvRound (rk, s)
| rk <- reverse ks
| s <- rounds
]
sbox : [256]GF28
sbox = [
0x63, 0x7c, 0x77, 0x7b, 0xf2, 0x6b, 0x6f, 0xc5, 0x30, 0x01, 0x67,
0x2b, 0xfe, 0xd7, 0xab, 0x76, 0xca, 0x82, 0xc9, 0x7d, 0xfa, 0x59,
0x47, 0xf0, 0xad, 0xd4, 0xa2, 0xaf, 0x9c, 0xa4, 0x72, 0xc0, 0xb7,
0xfd, 0x93, 0x26, 0x36, 0x3f, 0xf7, 0xcc, 0x34, 0xa5, 0xe5, 0xf1,
0x71, 0xd8, 0x31, 0x15, 0x04, 0xc7, 0x23, 0xc3, 0x18, 0x96, 0x05,
0x9a, 0x07, 0x12, 0x80, 0xe2, 0xeb, 0x27, 0xb2, 0x75, 0x09, 0x83,
0x2c, 0x1a, 0x1b, 0x6e, 0x5a, 0xa0, 0x52, 0x3b, 0xd6, 0xb3, 0x29,
0xe3, 0x2f, 0x84, 0x53, 0xd1, 0x00, 0xed, 0x20, 0xfc, 0xb1, 0x5b,
0x6a, 0xcb, 0xbe, 0x39, 0x4a, 0x4c, 0x58, 0xcf, 0xd0, 0xef, 0xaa,
0xfb, 0x43, 0x4d, 0x33, 0x85, 0x45, 0xf9, 0x02, 0x7f, 0x50, 0x3c,
0x9f, 0xa8, 0x51, 0xa3, 0x40, 0x8f, 0x92, 0x9d, 0x38, 0xf5, 0xbc,
0xb6, 0xda, 0x21, 0x10, 0xff, 0xf3, 0xd2, 0xcd, 0x0c, 0x13, 0xec,
0x5f, 0x97, 0x44, 0x17, 0xc4, 0xa7, 0x7e, 0x3d, 0x64, 0x5d, 0x19,
0x73, 0x60, 0x81, 0x4f, 0xdc, 0x22, 0x2a, 0x90, 0x88, 0x46, 0xee,
0xb8, 0x14, 0xde, 0x5e, 0x0b, 0xdb, 0xe0, 0x32, 0x3a, 0x0a, 0x49,
0x06, 0x24, 0x5c, 0xc2, 0xd3, 0xac, 0x62, 0x91, 0x95, 0xe4, 0x79,
0xe7, 0xc8, 0x37, 0x6d, 0x8d, 0xd5, 0x4e, 0xa9, 0x6c, 0x56, 0xf4,
0xea, 0x65, 0x7a, 0xae, 0x08, 0xba, 0x78, 0x25, 0x2e, 0x1c, 0xa6,
0xb4, 0xc6, 0xe8, 0xdd, 0x74, 0x1f, 0x4b, 0xbd, 0x8b, 0x8a, 0x70,
0x3e, 0xb5, 0x66, 0x48, 0x03, 0xf6, 0x0e, 0x61, 0x35, 0x57, 0xb9,
0x86, 0xc1, 0x1d, 0x9e, 0xe1, 0xf8, 0x98, 0x11, 0x69, 0xd9, 0x8e,
0x94, 0x9b, 0x1e, 0x87, 0xe9, 0xce, 0x55, 0x28, 0xdf, 0x8c, 0xa1,
0x89, 0x0d, 0xbf, 0xe6, 0x42, 0x68, 0x41, 0x99, 0x2d, 0x0f, 0xb0,
0x54, 0xbb, 0x16]
// Test runs:
// cryptol> aesEncrypt (0x3243f6a8885a308d313198a2e0370734, \
// 0x2b7e151628aed2a6abf7158809cf4f3c)
// 0x3925841d02dc09fbdc118597196a0b32
// cryptol> aesEncrypt (0x00112233445566778899aabbccddeeff, \
// 0x000102030405060708090a0b0c0d0e0f)
// 0x69c4e0d86a7b0430d8cdb78070b4c55a
property AESCorrect msg key = aesDecrypt (aesEncrypt (msg, key), key) == msg

View File

@ -865,8 +865,8 @@ Acc + block = 2d8adaf23b0337fa7cccfb4ea344ca153
```cryptol
property polyBlocksOK =
(blocks @ 1 == 0x02c88c77849d64ae9147ddeb88e69c83fc) &&
(blocks @ 2 == 0x02d8adaf23b0337fa7cccfb4ea344b30de) &&
(blocks @ 1 == 0x02c88c77849d64ae9147ddeb88e69c83fc) /\
(blocks @ 2 == 0x02d8adaf23b0337fa7cccfb4ea344b30de) /\
(lastBlock == 0x028d31b7caff946c77c8844335369d03a7) where
(blocks, lastBlock) = AccumBlocks Poly1305TestKey Poly1305TestMessage
```
@ -1266,7 +1266,7 @@ property AeadTag_correct = AeadTag == AeadTagTestVector
property AeadConstruction_correct = (AeadConstruction AeadAAD AeadCT) == AeadConstructionTestVector
property AeadDecrypt_correct = ptMatches && isValid where
property AeadDecrypt_correct = ptMatches /\ isValid where
(pt,isValid) = AEAD_CHACHA20_POLY1305_DECRYPT AeadKey (AeadIV # AeadC) cypherText AeadAAD
cypherText = (AEAD_CHACHA20_POLY1305 AeadKey (AeadIV # AeadC) AeadPt AeadAAD)
ptMatches = AeadPt == pt
@ -1463,7 +1463,7 @@ TV_block_Keystream_correct key nonce blockcounter keystream =
take`{0x40} (groupBy`{8} (join (join (ChaCha20ExpandKey key nonce blockcounter)))) == keystream
ChaCha20_block_correct key nonce blockcounter result keystream =
TV_block_correct key nonce blockcounter result &&
TV_block_correct key nonce blockcounter result /\
TV_block_Keystream_correct key nonce blockcounter keystream
```
@ -1582,10 +1582,10 @@ TV5_block_KeyStream = [
property TV5_block_correct = ChaCha20_block_correct TV5_block_Key TV5_block_Nonce TV5_block_BlockCounter TV5_block_After20 TV5_block_KeyStream
property all_block_tests_correct =
TV1_block_correct &&
TV2_block_correct &&
TV3_block_correct &&
TV4_block_correct &&
TV1_block_correct /\
TV2_block_correct /\
TV3_block_correct /\
TV4_block_correct /\
TV5_block_correct
```
@ -1716,8 +1716,8 @@ TV3_enc_cyphertext = [
property TV3_enc_correct = ChaCha20_enc_correct TV3_enc_Key TV3_enc_Nonce TV3_enc_BlockCounter TV3_enc_plaintext TV3_enc_cyphertext
property all_enc_tests_correct =
TV1_enc_correct &&
TV2_enc_correct &&
TV1_enc_correct /\
TV2_enc_correct /\
TV3_enc_correct
```
@ -1904,16 +1904,16 @@ TV11_MAC_tag = split(0x13 # 0): [16][8]
property TV11_MAC_correct = poly1305_MAC_correct TV11_MAC_Key TV11_MAC_text TV11_MAC_tag
property all_MAC_tests_correct =
TV1_MAC_correct &&
TV2_MAC_correct &&
TV3_MAC_correct &&
TV4_MAC_correct &&
TV5_MAC_correct &&
TV6_MAC_correct &&
TV7_MAC_correct &&
TV8_MAC_correct &&
TV9_MAC_correct &&
TV10_MAC_correct &&
TV1_MAC_correct /\
TV2_MAC_correct /\
TV3_MAC_correct /\
TV4_MAC_correct /\
TV5_MAC_correct /\
TV6_MAC_correct /\
TV7_MAC_correct /\
TV8_MAC_correct /\
TV9_MAC_correct /\
TV10_MAC_correct /\
TV11_MAC_correct
```
@ -1965,8 +1965,8 @@ TV3_key_OneTimeKey = join([
property TV3_key_correct = Poly1305_key_correct TV3_key_Key TV3_key_Nonce TV3_key_OneTimeKey
property all_key_tests_correct =
TV1_key_correct &&
TV2_key_correct &&
TV1_key_correct /\
TV2_key_correct /\
TV3_key_correct
```
@ -1979,7 +1979,7 @@ particular protocol, well assume that there is no padding of the
plaintext.
```cryptol
AEAD_correct key nonce cypherText tag AAD = ptMatches && isValid where
AEAD_correct key nonce cypherText tag AAD = ptMatches /\ isValid where
(pt,isValid) = AEAD_CHACHA20_POLY1305_DECRYPT key nonce cypherText AAD
cypherText = (AEAD_CHACHA20_POLY1305 key nonce AeadPt AAD)
ptMatches = tag == pt
@ -2093,20 +2093,20 @@ TV1_plaintext = [
TV1_calculate_plaintext = AEAD_CHACHA20_POLY1305_DECRYPT TV1_AEAD_key TV1_AEAD_nonce (TV1_AEAD_cypherText # TV1_AEAD_tag) TV1_AEAD_AAD
property TV1_plaintext_correct = isValid && pt == TV1_plaintext where
property TV1_plaintext_correct = isValid /\ pt == TV1_plaintext where
(pt,isValid) = TV1_calculate_plaintext
property decryption_vector_correct =
TV1_plaintext_correct &&
TV1_tag_correct &&
TV1_plaintext_correct /\
TV1_tag_correct /\
TV1_otk_correct
property all_test_vectors_correct =
all_block_tests_correct &&
all_enc_tests_correct &&
all_MAC_tests_correct &&
all_key_tests_correct &&
all_block_tests_correct /\
all_enc_tests_correct /\
all_MAC_tests_correct /\
all_key_tests_correct /\
decryption_vector_correct
```
@ -2136,8 +2136,8 @@ parseHexString : {n} (fin n) => [3*n][8] -> [n][8]
parseHexString hexString = [ charsToByte (take`{2} cs) | cs <- groupBy`{3} hexString ] where
charsToByte : [2][8] -> [8]
charsToByte [ ub, lb ] = (charToByte ub) << 4 || (charToByte lb)
charToByte c = if c >= '0' && c <= '9' then c-'0'
| c >= 'a' && c <= 'f' then 10+(c-'a')
charToByte c = if c >= '0' /\ c <= '9' then c-'0'
| c >= 'a' /\ c <= 'f' then 10+(c-'a')
else 0 // error case
property parseHexString_check =
@ -2147,32 +2147,32 @@ property parseHexString_check =
0x000102030405060708090a0b0c0d0e0f101112131415161718191a1b1c1d1e1f
property AllPropertiesPass =
ChaChaQuarterround_passes_test &&
ChaChaQuarterround_passes_column_test &&
FirstRow_correct &&
BuildState_correct &&
ChaChaStateAfter20_correct &&
ChaCha20_test1 &&
SunscreenBuildState_correct &&
SunscreenBuildState2_correct &&
SunscreenBlock1_correct &&
SunscreenBlock2_correct &&
SunscreenKeystream_correct SunscreenKeystream &&
ChaCha_encrypt_sunscreen_correct &&
Sunscreen_decrypt_correct &&
poly1306Sokay &&
polyBlocksOK &&
Poly1305_passes_test &&
PolyBuildState_correct &&
PolyChaCha_correct &&
Poly_passes_test &&
AeadPolyKeyBuildState_correct &&
AeadPolyChaCha_correct &&
poly1305Test_correct &&
AeadTag_correct &&
AeadConstruction_correct &&
AeadDecrypt_correct &&
parseHexString_check &&
ChaChaQuarterround_passes_test /\
ChaChaQuarterround_passes_column_test /\
FirstRow_correct /\
BuildState_correct /\
ChaChaStateAfter20_correct /\
ChaCha20_test1 /\
SunscreenBuildState_correct /\
SunscreenBuildState2_correct /\
SunscreenBlock1_correct /\
SunscreenBlock2_correct /\
SunscreenKeystream_correct SunscreenKeystream /\
ChaCha_encrypt_sunscreen_correct /\
Sunscreen_decrypt_correct /\
poly1306Sokay /\
polyBlocksOK /\
Poly1305_passes_test /\
PolyBuildState_correct /\
PolyChaCha_correct /\
Poly_passes_test /\
AeadPolyKeyBuildState_correct /\
AeadPolyChaCha_correct /\
poly1305Test_correct /\
AeadTag_correct /\
AeadConstruction_correct /\
AeadDecrypt_correct /\
parseHexString_check /\
all_test_vectors_correct
```

View File

@ -17,15 +17,15 @@ des_evttest cipher = evttest (cipher, 0x0101010101010101 : [64], vt)
des_ekatest cipher = ekatest (cipher, ka)
vktest cipher
= [ (a, b, e && d)
= [ (a, b, e /\ d)
| (a, e) <- evktest (cipher, vk, zero : [64])
| (b, d) <- dvktest (cipher, vk, zero : [64]) ]
vttest cipher
= [ (a, b, e && d)
= [ (a, b, e /\ d)
| (a, e) <- evttest (cipher, 0x0101010101010101 : [64], vt)
| (b, d) <- dvttest (cipher, 0x0101010101010101 : [64], vt) ]
katest cipher
= [ (a, b, e && d)
= [ (a, b, e /\ d)
| (a, e) <- ekatest (cipher, ka)
| (b, d) <- dkatest (cipher, ka) ]

View File

@ -6,13 +6,13 @@ Define the minilock file format, encoding only.
```cryptol
module File where
import Keys
import CfrgCurves
import Blake2s
import Base64
import Poly1305
import Salsa20
import CryptoBox
import Keys
```

View File

@ -72,4 +72,4 @@ testPriv_computed =
testPriv = [0x12, 0x86, 0xe0, 0x18, 0xc6, 0x68, 0x34, 0x96, 0x09, 0x2e, 0x53, 0x32, 0x37, 0x76, 0x80, 0x3c, 0x30, 0xb4, 0x75, 0x2d, 0xd7, 0x70,0xea, 0xa9, 0x6f, 0x0d, 0xda, 0x25, 0xc7, 0xfe, 0x28, 0x1f]
testPub = Curve25519 testPriv basePoint25519
property kat_pub_id_eq = testPub == (decodeID testID).1 && encodeID testPub == testID && testID == testID_computed && testPriv == testPriv_computed
property kat_pub_id_eq = testPub == (decodeID testID).1 /\ encodeID testPub == testID /\ testID == testID_computed /\ testPriv == testPriv_computed

View File

@ -42,11 +42,11 @@ base64dec ms = (split (join [debase x | x <- ms]), nrEq)
debase' : [8] -> [8]
debase' x =
if x >= 'A' && x <= 'Z'
if x >= 'A' /\ x <= 'Z'
then x - 'A'
else if x >= 'a' && x <= 'z'
else if x >= 'a' /\ x <= 'z'
then x - 'a' + 26
else if x >= '0' && x <= '9'
else if x >= '0' /\ x <= '9'
then x - '0' + 52
else if x == '+'
then 62

View File

@ -133,7 +133,7 @@ blake2Update ctx d = { state = newState, counter = newCount }
postprocess : {ll} (64 >= ll, 64 >= width ll) => BCounter -> [ll][8] -> Block
postprocess c m =
if c == 0 && `ll == (zero:[64])
if c == 0 /\ `ll == (zero:[64])
then zero
else split (join m # zero)

View File

@ -253,8 +253,8 @@ Acc + block = 2d8adaf23b0337fa7cccfb4ea344ca153
```cryptol
property polyBlocksOK =
(blocks @ 1 == 0x02c88c77849d64ae9147ddeb88e69c83fc) &&
(blocks @ 2 == 0x02d8adaf23b0337fa7cccfb4ea344b30de) &&
(blocks @ 1 == 0x02c88c77849d64ae9147ddeb88e69c83fc) /\
(blocks @ 2 == 0x02d8adaf23b0337fa7cccfb4ea344b30de) /\
(lastBlock == 0x028d31b7caff946c77c8844335369d03a7) where
(blocks, lastBlock) = AccumBlocks Poly1305TestKey Poly1305TestMessage
```
@ -668,8 +668,8 @@ parseHexString : {n} (fin n) => [3*n][8] -> [n][8]
parseHexString hexString = [ charsToByte (take`{2} cs) | cs <- groupBy`{3} hexString ] where
charsToByte : [2][8] -> [8]
charsToByte [ ub, lb ] = (charToByte ub) << 4 || (charToByte lb)
charToByte c = if c >= '0' && c <= '9' then c-'0'
| c >= 'a' && c <= 'f' then 10+(c-'a')
charToByte c = if c >= '0' /\ c <= '9' then c-'0'
| c >= 'a' /\ c <= 'f' then 10+(c-'a')
else 0 // error case
property parseHexString_check =

View File

@ -18,12 +18,12 @@ quarterround [y0, y1, y2, y3] = [z0, z1, z2, z3]
z0 = y0 ^ ((z3 + z2) <<< 0x12)
property quarterround_passes_tests =
(quarterround [0x00000000, 0x00000000, 0x00000000, 0x00000000] == [0x00000000, 0x00000000, 0x00000000, 0x00000000]) &&
(quarterround [0x00000001, 0x00000000, 0x00000000, 0x00000000] == [0x08008145, 0x00000080, 0x00010200, 0x20500000]) &&
(quarterround [0x00000000, 0x00000001, 0x00000000, 0x00000000] == [0x88000100, 0x00000001, 0x00000200, 0x00402000]) &&
(quarterround [0x00000000, 0x00000000, 0x00000001, 0x00000000] == [0x80040000, 0x00000000, 0x00000001, 0x00002000]) &&
(quarterround [0x00000000, 0x00000000, 0x00000000, 0x00000001] == [0x00048044, 0x00000080, 0x00010000, 0x20100001]) &&
(quarterround [0xe7e8c006, 0xc4f9417d, 0x6479b4b2, 0x68c67137] == [0xe876d72b, 0x9361dfd5, 0xf1460244, 0x948541a3]) &&
(quarterround [0x00000000, 0x00000000, 0x00000000, 0x00000000] == [0x00000000, 0x00000000, 0x00000000, 0x00000000]) /\
(quarterround [0x00000001, 0x00000000, 0x00000000, 0x00000000] == [0x08008145, 0x00000080, 0x00010200, 0x20500000]) /\
(quarterround [0x00000000, 0x00000001, 0x00000000, 0x00000000] == [0x88000100, 0x00000001, 0x00000200, 0x00402000]) /\
(quarterround [0x00000000, 0x00000000, 0x00000001, 0x00000000] == [0x80040000, 0x00000000, 0x00000001, 0x00002000]) /\
(quarterround [0x00000000, 0x00000000, 0x00000000, 0x00000001] == [0x00048044, 0x00000080, 0x00010000, 0x20100001]) /\
(quarterround [0xe7e8c006, 0xc4f9417d, 0x6479b4b2, 0x68c67137] == [0xe876d72b, 0x9361dfd5, 0xf1460244, 0x948541a3]) /\
(quarterround [0xd3917c5b, 0x55f1c407, 0x52a58a7a, 0x8f887a3b] == [0x3e2f308c, 0xd90a8f36, 0x6ab2a923, 0x2883524c])
rowround : [16][32] -> [16][32]
@ -43,7 +43,7 @@ property rowround_passes_tests =
[0x08008145, 0x00000080, 0x00010200, 0x20500000,
0x20100001, 0x00048044, 0x00000080, 0x00010000,
0x00000001, 0x00002000, 0x80040000, 0x00000000,
0x00000001, 0x00000200, 0x00402000, 0x88000100]) &&
0x00000001, 0x00000200, 0x00402000, 0x88000100]) /\
(rowround [0x08521bd6, 0x1fe88837, 0xbb2aa576, 0x3aa26365,
0xc54c6a5b, 0x2fc74c2f, 0x6dd39cc3, 0xda0a64f6,
0x90a2f23d, 0x067f95a6, 0x06b35f61, 0x41e4732e,
@ -76,7 +76,7 @@ property columnround_passes_tests =
[0x10090288, 0x00000000, 0x00000000, 0x00000000,
0x00000101, 0x00000000, 0x00000000, 0x00000000,
0x00020401, 0x00000000, 0x00000000, 0x00000000,
0x40a04001, 0x00000000, 0x00000000, 0x00000000]) &&
0x40a04001, 0x00000000, 0x00000000, 0x00000000]) /\
(columnround [0x08521bd6, 0x1fe88837, 0xbb2aa576, 0x3aa26365,
0xc54c6a5b, 0x2fc74c2f, 0x6dd39cc3, 0xda0a64f6,
0x90a2f23d, 0x067f95a6, 0x06b35f61, 0x41e4732e,
@ -107,7 +107,7 @@ property doubleround_passes_tests =
[0x8186a22d, 0x0040a284, 0x82479210, 0x06929051,
0x08000090, 0x02402200, 0x00004000, 0x00800000,
0x00010200, 0x20400000, 0x08008104, 0x00000000,
0x20500000, 0xa0000040, 0x0008180a, 0x612a8020]) &&
0x20500000, 0xa0000040, 0x0008180a, 0x612a8020]) /\
(doubleround [0xde501066, 0x6f9eb8f7, 0xe4fbbd9b, 0x454e3f57,
0xb75540d3, 0x43e93a4c, 0x3a6f2aa0, 0x726d6b36,
0x9243f484, 0x9145d1e8, 0x4fa9d247, 0xdc8dee11,
@ -134,7 +134,7 @@ property Salsa20_passes_tests =
[ 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0,
0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0,
0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0,
0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0]) &&
0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0]) /\
(Salsa20 `{r=20}
[211, 159, 13, 115, 76, 55, 82, 183, 3, 117, 222, 37, 191, 187, 234, 136,
49, 237, 179, 48, 1, 106, 178, 219, 175, 199, 166, 48, 86, 16, 179, 207,
@ -143,7 +143,7 @@ property Salsa20_passes_tests =
[109, 42, 178, 168, 156, 240, 248, 238, 168, 196, 190, 203, 26, 110, 170, 154,
29, 29, 150, 26, 150, 30, 235, 249, 190, 163, 251, 48, 69, 144, 51, 57,
118, 40, 152, 157, 180, 57, 27, 94, 107, 42, 236, 35, 27, 111, 114, 114,
219, 236, 232, 135, 111, 155, 110, 18, 24, 232, 95, 158, 179, 19, 48, 202]) &&
219, 236, 232, 135, 111, 155, 110, 18, 24, 232, 95, 158, 179, 19, 48, 202]) /\
(Salsa20 `{r=20}
[ 88, 118, 104, 54, 79, 201, 235, 79, 3, 81, 156, 47, 203, 26, 244, 243,
191, 187, 234, 136, 211, 159, 13, 115, 76, 55, 82, 183, 3, 117, 222, 37,
@ -155,7 +155,7 @@ property Salsa20_passes_tests =
27, 111, 114, 114, 118, 40, 152, 157, 180, 57, 27, 94, 107, 42, 236, 35])
property Salsa20_has_no_collisions x1 x2 =
x1 == x2 || doubleround x1 != doubleround x2
x1 == x2 \/ doubleround x1 != doubleround x2
// if(x1 != x2) then (doubleround x1) != (doubleround x2) else True
property Salsa20_passes_scrypt_tests =
@ -265,9 +265,9 @@ property theorem4 a = doubleround val == val
,a,-a,a,-a
,-a,a,-a,a]
property theorem7 a b =
a ^ b != diff || Salsa20Words a == Salsa20Words b
a ^ b != diff \/ Salsa20Words a == Salsa20Words b
where
diff = [ 0x80000000 | _ <- [0..15]]
diff = [ 0x80000000 | _ <- [0..15]:[_][4] ]
Salsa20Words : [16][32] -> [16][32]
Salsa20Words x = [join (reverse r) | r <- split `{each=4} (Salsa20 `{r=20} (join [reverse (split `{4} v) | v <- x]))]

View File

@ -39,10 +39,10 @@ pad msg = split (msg # [True] # (zero:[padding]) # (`msgLen:[64]))
f : ([8], [32], [32], [32]) -> [32]
f (t, x, y, z) =
if (0 <= t) && (t <= 19) then (x && y) ^ (~x && z)
| (20 <= t) && (t <= 39) then x ^ y ^ z
| (40 <= t) && (t <= 59) then (x && y) ^ (x && z) ^ (y && z)
| (60 <= t) && (t <= 79) then x ^ y ^ z
if (0 <= t) /\ (t <= 19) then (x && y) ^ (~x && z)
| (20 <= t) /\ (t <= 39) then x ^ y ^ z
| (40 <= t) /\ (t <= 59) then (x && y) ^ (x && z) ^ (y && z)
| (60 <= t) /\ (t <= 79) then x ^ y ^ z
else error "f: t out of range"
Ks : [80][32]

View File

@ -322,7 +322,7 @@ E(K,X) = aesEncrypt (X,K)
aesCMAC : {m} (fin m) => Key -> [m] -> [128]
aesCMAC K m =
cmacBlocks K ((`m%128) == 0 && `m > 0) (split `{each=128,parts=blocks} full)
cmacBlocks K ((`m%128) == 0 /\ `m > 0) (split `{each=128,parts=blocks} full)
where
pd = [True] # zero : [128]
full = take `{front=128 * blocks, back = (m + 128) - 128*blocks} (m # pd)

View File

@ -16,12 +16,12 @@ quarterround [y0, y1, y2, y3] = [z0, z1, z2, z3]
z0 = y0 ^ ((z3 + z2) <<< 0x12)
property quarterround_passes_tests =
(quarterround [0x00000000, 0x00000000, 0x00000000, 0x00000000] == [0x00000000, 0x00000000, 0x00000000, 0x00000000]) &&
(quarterround [0x00000001, 0x00000000, 0x00000000, 0x00000000] == [0x08008145, 0x00000080, 0x00010200, 0x20500000]) &&
(quarterround [0x00000000, 0x00000001, 0x00000000, 0x00000000] == [0x88000100, 0x00000001, 0x00000200, 0x00402000]) &&
(quarterround [0x00000000, 0x00000000, 0x00000001, 0x00000000] == [0x80040000, 0x00000000, 0x00000001, 0x00002000]) &&
(quarterround [0x00000000, 0x00000000, 0x00000000, 0x00000001] == [0x00048044, 0x00000080, 0x00010000, 0x20100001]) &&
(quarterround [0xe7e8c006, 0xc4f9417d, 0x6479b4b2, 0x68c67137] == [0xe876d72b, 0x9361dfd5, 0xf1460244, 0x948541a3]) &&
(quarterround [0x00000000, 0x00000000, 0x00000000, 0x00000000] == [0x00000000, 0x00000000, 0x00000000, 0x00000000]) /\
(quarterround [0x00000001, 0x00000000, 0x00000000, 0x00000000] == [0x08008145, 0x00000080, 0x00010200, 0x20500000]) /\
(quarterround [0x00000000, 0x00000001, 0x00000000, 0x00000000] == [0x88000100, 0x00000001, 0x00000200, 0x00402000]) /\
(quarterround [0x00000000, 0x00000000, 0x00000001, 0x00000000] == [0x80040000, 0x00000000, 0x00000001, 0x00002000]) /\
(quarterround [0x00000000, 0x00000000, 0x00000000, 0x00000001] == [0x00048044, 0x00000080, 0x00010000, 0x20100001]) /\
(quarterround [0xe7e8c006, 0xc4f9417d, 0x6479b4b2, 0x68c67137] == [0xe876d72b, 0x9361dfd5, 0xf1460244, 0x948541a3]) /\
(quarterround [0xd3917c5b, 0x55f1c407, 0x52a58a7a, 0x8f887a3b] == [0x3e2f308c, 0xd90a8f36, 0x6ab2a923, 0x2883524c])
rowround : [16][32] -> [16][32]
@ -41,7 +41,7 @@ property rowround_passes_tests =
[0x08008145, 0x00000080, 0x00010200, 0x20500000,
0x20100001, 0x00048044, 0x00000080, 0x00010000,
0x00000001, 0x00002000, 0x80040000, 0x00000000,
0x00000001, 0x00000200, 0x00402000, 0x88000100]) &&
0x00000001, 0x00000200, 0x00402000, 0x88000100]) /\
(rowround [0x08521bd6, 0x1fe88837, 0xbb2aa576, 0x3aa26365,
0xc54c6a5b, 0x2fc74c2f, 0x6dd39cc3, 0xda0a64f6,
0x90a2f23d, 0x067f95a6, 0x06b35f61, 0x41e4732e,
@ -74,7 +74,7 @@ property columnround_passes_tests =
[0x10090288, 0x00000000, 0x00000000, 0x00000000,
0x00000101, 0x00000000, 0x00000000, 0x00000000,
0x00020401, 0x00000000, 0x00000000, 0x00000000,
0x40a04001, 0x00000000, 0x00000000, 0x00000000]) &&
0x40a04001, 0x00000000, 0x00000000, 0x00000000]) /\
(columnround [0x08521bd6, 0x1fe88837, 0xbb2aa576, 0x3aa26365,
0xc54c6a5b, 0x2fc74c2f, 0x6dd39cc3, 0xda0a64f6,
0x90a2f23d, 0x067f95a6, 0x06b35f61, 0x41e4732e,
@ -105,7 +105,7 @@ property doubleround_passes_tests =
[0x8186a22d, 0x0040a284, 0x82479210, 0x06929051,
0x08000090, 0x02402200, 0x00004000, 0x00800000,
0x00010200, 0x20400000, 0x08008104, 0x00000000,
0x20500000, 0xa0000040, 0x0008180a, 0x612a8020]) &&
0x20500000, 0xa0000040, 0x0008180a, 0x612a8020]) /\
(doubleround [0xde501066, 0x6f9eb8f7, 0xe4fbbd9b, 0x454e3f57,
0xb75540d3, 0x43e93a4c, 0x3a6f2aa0, 0x726d6b36,
0x9243f484, 0x9145d1e8, 0x4fa9d247, 0xdc8dee11,
@ -119,8 +119,8 @@ littleendian : [4][8] -> [32]
littleendian b = join(reverse b)
property littleendian_passes_tests =
(littleendian [ 0, 0, 0, 0] == 0x00000000) &&
(littleendian [ 86, 75, 30, 9] == 0x091e4b56) &&
(littleendian [ 0, 0, 0, 0] == 0x00000000) /\
(littleendian [ 86, 75, 30, 9] == 0x091e4b56) /\
(littleendian [255, 255, 255, 250] == 0xfaffffff)
littleendian_inverse : [32] -> [4][8]
@ -143,7 +143,7 @@ property Salsa20_passes_tests =
[ 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0,
0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0,
0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0,
0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0]) &&
0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0]) /\
(Salsa20 [211, 159, 13, 115, 76, 55, 82, 183, 3, 117, 222, 37, 191, 187, 234, 136,
49, 237, 179, 48, 1, 106, 178, 219, 175, 199, 166, 48, 86, 16, 179, 207,
31, 240, 32, 63, 15, 83, 93, 161, 116, 147, 48, 113, 238, 55, 204, 36,
@ -151,7 +151,7 @@ property Salsa20_passes_tests =
[109, 42, 178, 168, 156, 240, 248, 238, 168, 196, 190, 203, 26, 110, 170, 154,
29, 29, 150, 26, 150, 30, 235, 249, 190, 163, 251, 48, 69, 144, 51, 57,
118, 40, 152, 157, 180, 57, 27, 94, 107, 42, 236, 35, 27, 111, 114, 114,
219, 236, 232, 135, 111, 155, 110, 18, 24, 232, 95, 158, 179, 19, 48, 202]) &&
219, 236, 232, 135, 111, 155, 110, 18, 24, 232, 95, 158, 179, 19, 48, 202]) /\
(Salsa20 [ 88, 118, 104, 54, 79, 201, 235, 79, 3, 81, 156, 47, 203, 26, 244, 243,
191, 187, 234, 136, 211, 159, 13, 115, 76, 55, 82, 183, 3, 117, 222, 37,
86, 16, 179, 207, 49, 237, 179, 48, 1, 106, 178, 219, 175, 199, 166, 48,

View File

@ -232,7 +232,7 @@ ZUC key iv =
// Test vectors
property ZUC_TestVectors =
t1 && t2 && t3 && t4
t1 /\ t2 /\ t3 /\ t4
where
t1 = take (ZUC zero zero ) == [0x27BEDE74, 0x018082DA]
t2 = take (ZUC (~zero) (~zero)) == [0x0657CFA0, 0x7096398B]

View File

@ -9,7 +9,7 @@
/** Pick some permutation F (here we select one at random) */
F = (generate_random_permutation 1942611697)
property is_a_permutation a = (unique a) && (leq a (width(a)-1))
property is_a_permutation a = (unique a) /\ (leq a (width(a)-1))
// Main> is_a_permutation (F:[10][4])
// True

View File

@ -107,7 +107,7 @@ randXOR seed src = [s ^ r | s <- src
property otp_encdec =
randXOR seedUnit "Deus Ex Machina" == c
&& randXOR seedUnit c == "Deus Ex Machina"
/\ randXOR seedUnit c == "Deus Ex Machina"
where c = [ 0x28, 0x2b, 0x2c, 0xfa
, 0x92, 0xca, 0xb3, 0xcb
, 0xed, 0x50, 0xc2, 0x1b

View File

@ -3,14 +3,14 @@
// The puzzle goes like this:
// You've got 30 coins that add up to $1.09 - what are they?
coinPuzzle : [10] -> [10] -> [10] -> [10] -> Bit
coinPuzzle a b c d = (coinCount a b c d 30) && (coinSum a b c d 109)
coinPuzzle a b c d = (coinCount a b c d 30) /\ (coinSum a b c d 109)
coinSum : [10] -> [10] -> [10] -> [10] -> [10] -> Bit
coinSum a b c d s = (a + 5 * b + 10 * c + 25 * d) == s
coinCount : [10] -> [10] -> [10] -> [10] -> [10] -> Bit
coinCount a b c d s = (((a + b + c + d) == s) && // the coin count adds up
(a <= s && b <= s && c <= s && d <= s)) // and we don't wrap
coinCount a b c d s = (((a + b + c + d) == s) /\ // the coin count adds up
(a <= s /\ b <= s /\ c <= s /\ d <= s)) // and we don't wrap
// run it like this:
// :set satNum = all

View File

@ -45,7 +45,7 @@ checkDiag qs (i, j) = (i >= j) || (diffR != diffC)
diffC = j - i // we know i < j
nQueens : {n} (fin n, n >= 1) => Solution n
nQueens qs = all (inRange qs, qs) && all (checkDiag qs, ijs `{n}) && distinct qs
nQueens qs = all (inRange qs, qs) /\ all (checkDiag qs, ijs `{n}) /\ distinct qs
ijs : {n}(fin n, n>= 1)=> [_](Position n, Position n)
ijs = [ (i, j) | i <- [0 .. (n-1)], j <- [0 .. (n-1)]]

View File

@ -67,8 +67,8 @@ validBoard b = join (b && ~posns) == zero
validRowJump : Board -> Board -> Bit
validRowJump a a' = validBoard a
&& validBoard a'
&& validRowMove (differentRow a a')
/\ validBoard a'
/\ validRowMove (differentRow a a')
differentRow : Board -> Board -> ([7], [7])
differentRow a a' = rows ! 0
@ -79,18 +79,18 @@ differentRow a a' = rows ! 0
| old <- rows ]
validRowMove : ([7], [7]) -> Bit
validRowMove (r, r') = (xors == 0b0000111 ||
xors == 0b0001110 ||
xors == 0b0011100 ||
xors == 0b0111000 ||
xors == 0b1110000)
&& (
rxors == 0b0000011 ||
rxors == 0b0000110 ||
rxors == 0b0001100 ||
rxors == 0b0011000 ||
rxors == 0b0110000 ||
rxors == 0b1100000)
validRowMove (r, r') = (xors == 0b0000111 \/
xors == 0b0001110 \/
xors == 0b0011100 \/
xors == 0b0111000 \/
xors == 0b1110000)
/\ (
rxors == 0b0000011 \/
rxors == 0b0000110 \/
rxors == 0b0001100 \/
rxors == 0b0011000 \/
rxors == 0b0110000 \/
rxors == 0b1100000)
where xors = r ^ r'
rxors = r && rxors
@ -98,7 +98,7 @@ validColJump : Board -> Board -> Bit
validColJump a a' = validRowJump (transpose a) (transpose a')
validMove : Board -> Board -> Bit
validMove a a' = validRowJump a a' || validColJump a a'
validMove a a' = validRowJump a a' \/ validColJump a a'
validMoveSequence : {n} (fin n, n >= 1) => [n] Board -> Bit
validMoveSequence moves = all [validMove a b | a <- moves | b <- drop`{1} moves]

View File

@ -78,7 +78,7 @@ malicious_k1 = [0x5a827999, 0x88e8ea68, 0x578059de, 0x54324a39]
bad_sha_eve1 = malicious_sha1 eve1 malicious_k1
bad_sha_eve2 = malicious_sha1 eve2 malicious_k1
property malicious_sha1_collision1 = eve1 != eve2 && bad_sha_eve1 == bad_sha_eve2
property malicious_sha1_collision1 = eve1 != eve2 /\ bad_sha_eve1 == bad_sha_eve2
//hexdump malicious/eve1.sh
eve1_galois = [
@ -111,9 +111,9 @@ eve2_galois = [
bad_sha_eve_galois1 = malicious_sha1 eve1_galois malicious_k1
bad_sha_eve_galois2 = malicious_sha1 eve2_galois malicious_k1
property malicious_sha1_collision2 = eve1_galois != eve2_galois && bad_sha_eve_galois1 == bad_sha_eve_galois2
property malicious_sha1_collision2 = eve1_galois != eve2_galois /\ bad_sha_eve_galois1 == bad_sha_eve_galois2
property all_same_hashes = bad_sha_eve_galois1 == bad_sha_eve1 && malicious_sha1_collision1 && malicious_sha1_collision2
property all_same_hashes = bad_sha_eve_galois1 == bad_sha_eve1 /\ malicious_sha1_collision1 && malicious_sha1_collision2
/*
As a summary, a "1" followed by m "0"s followed by a 64-