summaryrefslogtreecommitdiffhomepage
diff options
context:
space:
mode:
-rw-r--r--CHANGELOG3
-rw-r--r--Crypto/SecretSharing.hs36
-rw-r--r--Crypto/SecretSharing/Internal.hs152
-rw-r--r--Share.hs29
-rw-r--r--keysafe.cabal11
-rw-r--r--stack.yaml3
6 files changed, 28 insertions, 206 deletions
diff --git a/CHANGELOG b/CHANGELOG
index 6439417..1859882 100644
--- a/CHANGELOG
+++ b/CHANGELOG
@@ -1,6 +1,9 @@
keysafe (0.20160820) UNRELEASED; urgency=medium
* Server implementation.
+ * Removed embedded copy of secret-sharing library, since finite-field
+ only supports prime fields. This caused shares to be twice the size of
+ the input value.
-- Joey Hess <id@joeyh.name> Mon, 22 Aug 2016 13:56:16 -0400
diff --git a/Crypto/SecretSharing.hs b/Crypto/SecretSharing.hs
deleted file mode 100644
index a2a4f07..0000000
--- a/Crypto/SecretSharing.hs
+++ /dev/null
@@ -1,36 +0,0 @@
------------------------------------------------------------------------------
--- |
--- Module : Crypto.SecretSharing
--- Copyright : Peter Robinson 2014
--- License : LGPL
---
--- Maintainer : Peter Robinson <peter.robinson@monoid.at>
--- Stability : experimental
--- Portability : portable
---
--- Implementation of an (@m@,@n@)-threshold secret sharing scheme.
--- A given ByteString @b@ (the secret) is split into @n@ shares,
--- and any @m@ shares are sufficient to reconstruct @b@.
--- The scheme preserves perfect secrecy in the sense that the knowledge of up
--- to @m-1@ shares does not reveal any information about the secret @b@.
---
--- Typically, there are @n@ parties and we would like to give the @i@-th party
--- the @i@-share of each byte.
--- For example, to encode a bytestring @secret@ as @10@ shares, any @5@ of which
--- are sufficient for reconstruction we could write:
---
--- > shares <- encode 5 10 secret
---
--- Note that each byte is encoded separately using a fresh set of random
--- coefficients.
---
--- The mathematics behind the secret sharing scheme is described in:
--- \"How to share a secret.\" by Shamir, Adi.
--- In Communications of the ACM 22 (11): 612–613, 1979.
---
---
------------------------------------------------------------------------------
-
-module Crypto.SecretSharing( encode, decode, Share )
-where
-import Crypto.SecretSharing.Internal
diff --git a/Crypto/SecretSharing/Internal.hs b/Crypto/SecretSharing/Internal.hs
deleted file mode 100644
index 5fff416..0000000
--- a/Crypto/SecretSharing/Internal.hs
+++ /dev/null
@@ -1,152 +0,0 @@
-{-# LANGUAGE DeriveDataTypeable, DeriveGeneric, GeneralizedNewtypeDeriving, TemplateHaskell #-}
------------------------------------------------------------------------------
--- |
--- Module : Crypto.SecretSharing.Internal
--- Copyright : Peter Robinson 2014
--- License : LGPL
---
--- Maintainer : Peter Robinson <peter.robinson@monoid.at>
--- Stability : experimental
--- Portability : portable
---
------------------------------------------------------------------------------
-
-module Crypto.SecretSharing.Internal
-where
-import Math.Polynomial.Interpolation
-
-import Data.ByteString.Lazy( ByteString )
-import qualified Data.ByteString.Lazy as BL
-import qualified Data.ByteString.Lazy.Char8 as BLC
-import qualified Data.List as L
-import Data.Char
-import Data.Vector( Vector )
-import qualified Data.Vector as V
-import Data.Typeable
-import Control.Exception
-import Control.Monad
-import Data.Binary( Binary )
-import GHC.Generics
-import Data.FiniteField.PrimeField as PF
-import Data.FiniteField.Base(FiniteField,order)
-import System.Random.Dice
-
-
-
--- | A share of an encoded byte.
-data ByteShare = ByteShare
- { shareId :: !Int -- ^ the index of this share
- , reconstructionThreshold :: !Int -- ^ number of shares required for
- -- reconstruction
- , shareValue :: !Int -- ^ the value of p(shareId) where p(x) is the
- -- generated (secret) polynomial
- }
- deriving(Typeable,Eq,Generic)
-
-instance Show ByteShare where
- show = show . shareValue
-
--- | A share of the encoded secret.
-data Share = Share
- { theShare :: ![ByteShare] }
- deriving(Typeable,Eq,Generic)
-
-instance Show Share where
- show s = show (shareId $ head $ theShare s,BLC.pack $ map (chr . shareValue) $ theShare s)
-
-instance Binary ByteShare
-instance Binary Share
-
--- | Encodes a 'ByteString' as a list of n shares, m of which are required for
--- reconstruction.
--- Lives in the 'IO' to access a random source.
-encode :: Int -- ^ m
- -> Int -- ^ n
- -> ByteString -- ^ the secret that we want to share
- -> IO [Share] -- a list of n-shares (per byte)
-encode m n bstr
- | n >= prime || m > n = throw $ AssertionFailed $
- "encode: require n < " ++ show prime ++ " and m<=n."
- | BL.null bstr = return []
- | otherwise = do
- let len = max 1 ((fromIntegral $ BL.length bstr) * (m-1))
- coeffs <- (groupInto (m-1) . map fromIntegral . take len )
- `liftM` (getDiceRolls prime len)
- let byteVecs = zipWith (encodeByte m n) coeffs $
- map fromIntegral $ BL.unpack bstr
- return [ Share $ map (V.! (i-1)) byteVecs | i <- [1..n] ]
-
-
--- | Reconstructs a (secret) bytestring from a list of (at least @m@) shares.
--- Throws 'AssertionFailed' if the number of shares is too small.
-decode :: [Share] -- ^ list of at least @m@ shares
- -> ByteString -- ^ reconstructed secret
-decode [] = BL.pack []
-decode shares@((Share s):_)
- | length shares < reconstructionThreshold (head s) = throw $ AssertionFailed
- "decode: not enough shares for reconstruction."
- | otherwise =
- let origLength = length s in
- let byteVecs = map (V.fromList . theShare) shares in
- let byteShares = [ map ((V.! (i-1))) byteVecs | i <- [1..origLength] ] in
- BL.pack . map (fromInteger . PF.toInteger . number)
- . map decodeByte $ byteShares
-
-
-encodeByte :: Int -> Int -> Polyn -> FField -> Vector ByteShare
-encodeByte m n coeffs secret =
- V.fromList[ ByteShare i m $ fromInteger . PF.toInteger . number $
- evalPolynomial (secret:coeffs) (fromIntegral i::FField)
- | i <- [1..n]
- ]
-
-
-decodeByte :: [ByteShare] -> FField
-decodeByte ss =
- let m = reconstructionThreshold $ head ss in
- if length ss < m
- then throw $ AssertionFailed "decodeByte: insufficient number of shares for reconstruction!"
- else
- let shares = take m ss
- pts = map (\s -> (fromIntegral $ shareId s,fromIntegral $ shareValue s))
- shares
- in
- polyInterp pts 0
-
-
--- | Groups a list into blocks of certain size. Running time: /O(n)/
-groupInto :: Int -> [a] -> [[a]]
-groupInto num as
- | num < 0 = throw $ AssertionFailed "groupInto: Need positive number as argument."
- | otherwise =
- let (fs,ss) = L.splitAt num as in
- if L.null ss
- then [fs]
- else fs : groupInto num ss
-
-
--- | A finite prime field. All computations are performed in this field.
---
--- This is modified from the secret-sharing library to use 256
--- instead of 1021. That allows values in the field to be efficiently
--- packed into bytes. It's beleived that the finite field can be a power of
--- a prime number (in this case, 2).
-newtype FField = FField { number :: $(primeField $ fromIntegral (256 :: Integer)) }
- deriving(Show,Read,Ord,Eq,Num,Fractional,Generic,Typeable,FiniteField)
-
-
--- | The size of the finite field
-prime :: Int
-prime = fromInteger $ order (0 :: FField)
-
-
--- | A polynomial over the finite field given as a list of coefficients.
-type Polyn = [FField]
-
--- | Evaluates the polynomial at a given point.
-evalPolynomial :: Polyn -> FField -> FField
-evalPolynomial coeffs x =
- foldr (\c res -> c + (x * res)) 0 coeffs
--- let clist = zipWith (\pow c -> (\x -> c * (x^pow))) [0..] coeffs
--- in L.foldl' (+) 0 [ c x | c <- clist ]
-
diff --git a/Share.hs b/Share.hs
index 76d118c..e511afd 100644
--- a/Share.hs
+++ b/Share.hs
@@ -19,6 +19,7 @@ import qualified Raaz.Hash.Sha256 as Raaz
import qualified Data.Text as T
import qualified Data.Text.Encoding as E
import qualified Data.Set as S
+import Data.Word
import Data.Monoid
data ShareIdents = ShareIdents
@@ -92,20 +93,34 @@ combineShares tunables shares
fromStorableObject so
sharesneeded = neededObjects (shareParams tunables)
--- | This efficient encoding relies on the share using a finite field of
--- size 256, so it maps directly to bytes.
---
-- Note that this does not include the share number in the encoded
-- bytestring. This prevents an attacker from partitioning their shares
-- by share number.
encodeShare :: SS.Share -> B.ByteString
-encodeShare = B.pack . map (fromIntegral . SS.shareValue) . SS.theShare
+encodeShare = B.pack . concatMap (encodeShare' . SS.shareValue) . SS.theShare
decodeShare :: Int -> Int -> B.ByteString -> SS.Share
-decodeShare sharenum sharesneeded = SS.Share . map mk . B.unpack
+decodeShare sharenum sharesneeded = SS.Share . map mk . decodeShare' . B.unpack
where
- mk w = SS.ByteShare
+ mk v = SS.ByteShare
{ SS.shareId = sharenum
, SS.reconstructionThreshold = sharesneeded
- , SS.shareValue = fromIntegral w
+ , SS.shareValue = v
}
+
+-- | Each input byte generates a share in a finite field of size 1021,
+-- so encode it as the product of two bytes. This is inneffient; if the
+-- finite field was 255 then the encoded share would be the same size as
+-- the input. But, the finite-field library used by secret-sharing does
+-- not support a non-prime size.
+encodeShare' :: Int -> [Word8]
+encodeShare' v =
+ let (q, r) = quotRem v 255
+ in [fromIntegral q, fromIntegral r]
+
+decodeShare' :: [Word8] -> [Int]
+decodeShare' = go []
+ where
+ go c [] = reverse c
+ go c (q:r:rest) = go (((255 * fromIntegral q) + fromIntegral r):c) rest
+ go _ _ = error "Badly encoded share has odd number of bytes"
diff --git a/keysafe.cabal b/keysafe.cabal
index 60ce645..47a7dcd 100644
--- a/keysafe.cabal
+++ b/keysafe.cabal
@@ -30,6 +30,7 @@ Executable keysafe
, bytestring == 0.10.*
, deepseq == 1.4.*
, random == 1.1.*
+ , secret-sharing == 1.0.*
, raaz == 0.0.2
, time == 1.5.*
, containers == 0.5.*
@@ -53,15 +54,6 @@ Executable keysafe
, http-client == 0.4.*
, transformers == 0.4.*
, stm == 2.4.*
-
- -- Inlined to change the finite field size to 256
- -- for efficient serialization.
- -- secret-sharing == 1.0.*
- , dice-entropy-conduit >= 1.0.0.0
- , binary >=0.5.1.1
- , vector >=0.10.11.0
- , finite-field >=0.8.0
- , polynomial >= 0.7.1
-- Temporarily inlined due to https://github.com/ocharles/argon2/issues/3
-- argon2 == 1.1.*
Extra-Libraries: argon2
@@ -70,7 +62,6 @@ Executable keysafe
Crypto.Argon2
CmdLine
Cost
- Crypto.SecretSharing.Internal
Encryption
Entropy
ExpensiveHash
diff --git a/stack.yaml b/stack.yaml
index ebf1257..82ac935 100644
--- a/stack.yaml
+++ b/stack.yaml
@@ -2,9 +2,10 @@ packages:
- '.'
resolver: lts-6.12
extra-deps:
+ - secret-sharing-1.0.0.3
- dice-entropy-conduit-1.0.0.1
- - finite-field-0.8.0
- polynomial-0.7.2
+ - finite-field-0.8.0
- raaz-0.0.2
- zxcvbn-c-1.0.0
- servant-0.7.1