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
data ByteShare = ByteShare
{ shareId :: !Int
, reconstructionThreshold :: !Int
, shareValue :: !Int
}
deriving(Typeable,Eq,Generic)
instance Show ByteShare where
show = show . shareValue
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
encode :: Int
-> Int
-> ByteString
-> IO [Share]
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) * (m1))
coeffs <- (groupInto (m1) . map fromIntegral . take len )
`liftM` (getDiceRolls prime len)
let byteVecs = zipWith (encodeByte m n) coeffs $
map fromIntegral $ BL.unpack bstr
return [ Share $ map (V.! (i1)) byteVecs | i <- [1..n] ]
decode :: [Share]
-> ByteString
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.! (i1))) 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
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
newtype FField = FField { number :: $(primeField $ fromIntegral 1021) }
deriving(Show,Read,Ord,Eq,Num,Fractional,Generic,Typeable,FiniteField)
prime :: Int
prime = fromInteger $ order (0 :: FField)
type Polyn = [FField]
evalPolynomial :: Polyn -> FField -> FField
evalPolynomial coeffs x =
foldr (\c res -> c + (x * res)) 0 coeffs