module Protocol.Arith where import Data.Bits import Data.Bool import Data.Eq (Eq(..)) import Data.Foldable (Foldable(..)) import Data.Function ((.), on) import Data.Int (Int) import Data.Ord (Ord(..), Ordering(..)) import Data.Semigroup (Semigroup(..)) import Data.String (IsString(..)) import Prelude (Integer, Integral(..), fromIntegral) import Text.Show (Show(..)) import qualified Crypto.Hash as Crypto import qualified Data.ByteArray as ByteArray import qualified Data.ByteString as BS import qualified Prelude as N -- * Type 'F' -- | The type of the elements of a 'PrimeField'. -- -- A field must satisfy the following properties: -- -- * @(f, ('+'), 'zero')@ forms an abelian group, -- called the 'Additive' group of 'f'. -- -- * @('NonNull' f, ('*'), 'one')@ forms an abelian group, -- called the 'Multiplicative' group of 'f'. -- -- * ('*') is associative: -- @(a'*'b)'*'c == a'*'(b'*'c)@ and -- @a'*'(b'*'c) == (a'*'b)'*'c@. -- -- * ('*') and ('+') are both commutative: -- @a'*'b == b'*'a@ and -- @a'+'b == b'+'a@ -- -- * ('*') and ('+') are both left and right distributive: -- @a'*'(b'+'c) == (a'*'b) '+' (a'*'c)@ and -- @(a'+'b)'*'c == (a'*'c) '+' (b'*'c)@ -- -- WARNING: the underlying 'Integer' may be anything -- (though most of the time 'mod'ulo 'fieldCharac' to keep it "small"), -- use 'runF' to get a normalized value. newtype F p = F { unF :: Integer } deriving (Show) -- | @('runF' f)@ returns the element of the 'PrimeField' 'f' -- as an 'Integer' within @[0..'fieldCharac'-1]@. runF :: forall p. PrimeField p => F p -> Integer runF (F i) = abs (i `mod` fieldCharac @p) where abs z | z < 0 = z + fieldCharac @p | otherwise = z primeField :: forall p i. PrimeField p => Integral i => i -> F p primeField i = F (fromIntegral i `mod` fieldCharac @p) instance PrimeField p => Eq (F p) where (==) = (==) `on` runF @p instance PrimeField p => Ord (F p) where compare = compare `on` runF @p instance PrimeField p => Additive (F p) where zero = F 0 F x + F y = F ((x + y) `mod` fieldCharac @p) instance PrimeField p => Negable (F p) where neg (F x) = F (N.negate x) instance PrimeField p => Multiplicative (F p) where one = F 1 -- | Because 'fieldCharac' is prime, -- all elements of the field are invertible modulo 'fieldCharac'. F x * F y = F ((x * y) `mod` fieldCharac @p) infixr 8 ^ -- | @(b ^ e)@ returns the modular exponentiation of base 'b' by exponent 'e'. (^) :: PrimeField p => SubGroup q => P q ~ p => G q (F p) -> F p -> G q (F p) (^) b e = case e`compare`zero of LT -> inv b ^ e EQ -> one GT -> t * (b*b) ^ F (unF e`shiftR`1) where t | testBit (unF e) 0 = G (F (runG b)) | otherwise = one -- ** Class 'PrimeField' -- | Parameter for a prime field. class PrimeField p where -- | The prime number characteristic of a 'PrimeField'. -- -- ElGamal's hardness to decrypt -- requires a large prime number to form the 'Multiplicative' 'SubGroup'. fieldCharac :: Integer -- fieldCharac = reflect (Proxy::Proxy p) -- ** Class 'Additive' class Additive a where zero :: a (+) :: a -> a -> a; infixl 6 + instance Additive Integer where zero = 0 (+) = (N.+) instance Additive Int where zero = 0 (+) = (N.+) -- *** Class 'Negable' class Additive a => Negable a where neg :: a -> a (-) :: a -> a -> a; infixl 6 - x-y = x + (neg y) instance Negable Integer where neg = N.negate instance Negable Int where neg = N.negate -- ** Class 'Multiplicative' class Multiplicative a where one :: a (*) :: a -> a -> a; infixl 7 * instance Multiplicative Integer where one = 1 (*) = (N.*) instance Multiplicative Int where one = 1 (*) = (N.*) -- ** Class 'Invertible' class Multiplicative a => Invertible a where inv :: a -> a (/) :: a -> a -> a; infixl 7 / x/y = x * inv y -- * Type 'G' -- | The type of the elements of a 'Multiplicative' 'SubGroup' of a 'PrimeField'. newtype G q f = G { unG :: f } deriving (Show) -- | @('runG' g)@ returns the element of the 'SubGroup' 'g' -- as an 'Integer' within @[0..'fieldCharac'-1]@. runG :: PrimeField p => G q (F p) -> Integer runG = runF . unG instance PrimeField p => Eq (G q (F p)) where (==) = (==) `on` unG instance PrimeField p => Ord (G q (F p)) where compare = compare `on` unG -- ** Class 'SubGroupOfPrimeField' -- | A 'SubGroup' of a 'PrimeField'. -- Used for signing (Schnorr) and encrypting (ElGamal). class Invertible (G q (F (P q))) => SubGroup q where -- | Setting 'q' determines 'p', equals to @'P' q@. type P q :: * -- | A generator of the 'SubGroup'. -- NOTE: since @F p@ is a 'PrimeField', -- the 'Multiplicative' 'SubGroup' is cyclic, -- and there are phi('fieldCharac'-1) many choices for the generator of the group, -- where phi is the Euler totient function. groupGen :: G q (F (P q)) -- | The order of the 'SubGroup'. -- -- WARNING: 'groupOrder' MUST be a prime number dividing @('fieldCharac'-1)@ -- to ensure that ensures that ElGamal is secure in terms -- of the DDH assumption. groupOrder :: F (P q) instance ( PrimeField p , SubGroup q , P q ~ p , Multiplicative (F p) ) => Multiplicative (G q (F p)) where one = G one -- NOTE: add 'groupOrder' so the exponent given to (^) is positive. G x * G y = G (x * y) instance ( PrimeField p , SubGroup q , P q ~ p , Multiplicative (F p) ) => Invertible (G q (F p)) where inv = (^ (neg one + groupOrder @q)) -- | @(hash prefix gs)@ returns as a number in @('F' p)@ -- the SHA256 of the given 'prefix' prefixing the decimal representation -- of given 'SubGroup' elements 'gs', each one postfixed with a comma (","). hash :: PrimeField p => SubGroup q => BS.ByteString -> [G q (F p)] -> F p hash prefix gs = let s = prefix <> foldMap (\x -> fromString (show (unF (unG x))) <> fromString ",") gs in let h = ByteArray.convert (Crypto.hashWith Crypto.SHA256 s) in primeField (BS.foldl' (\acc b -> acc`shiftL`3 + fromIntegral b) (0::Integer) h) -- * Groups -- ** Type 'WeakParams' -- | Weak parameters for debugging purposes only. data WeakParams instance PrimeField WeakParams where fieldCharac = 263 instance SubGroup WeakParams where type P WeakParams = WeakParams groupGen = G (F 2) groupOrder = F 131 -- ** Type 'BeleniosParams' -- | Parameters used in Belenios. -- A 2048-bit 'fieldCharac' of a 'PrimeField', -- with a 256-bit 'groupOrder' for a 'Multiplicative' 'SubGroup' -- generated by 'groupGen', data BeleniosParams instance PrimeField BeleniosParams where fieldCharac = 20694785691422546401013643657505008064922989295751104097100884787057374219242717401922237254497684338129066633138078958404960054389636289796393038773905722803605973749427671376777618898589872735865049081167099310535867780980030790491654063777173764198678527273474476341835600035698305193144284561701911000786737307333564123971732897913240474578834468260652327974647951137672658693582180046317922073668860052627186363386088796882120769432366149491002923444346373222145884100586421050242120365433561201320481118852408731077014151666200162313177169372189248078507711827842317498073276598828825169183103125680162072880719 instance SubGroup BeleniosParams where type P BeleniosParams = BeleniosParams groupGen = G (F 2402352677501852209227687703532399932712287657378364916510075318787663274146353219320285676155269678799694668298749389095083896573425601900601068477164491735474137283104610458681314511781646755400527402889846139864532661215055797097162016168270312886432456663834863635782106154918419982534315189740658186868651151358576410138882215396016043228843603930989333662772848406593138406010231675095763777982665103606822406635076697764025346253773085133173495194248967754052573659049492477631475991575198775177711481490920456600205478127054728238140972518639858334115700568353695553423781475582491896050296680037745308460627) groupOrder = F 78571733251071885079927659812671450121821421258408794611510081919805623223441