{-# LANGUAGE AllowAmbiguousTypes #-}
{-# LANGUAGE DeriveAnyClass #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE DerivingStrategies #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE InstanceSigs #-}
{-# LANGUAGE UndecidableInstances #-}
{-# OPTIONS_GHC -fno-warn-orphans #-}
module Voting.Protocol.FFC where
import Control.Arrow (first)
import Control.DeepSeq (NFData)
import Control.Monad (Monad(..), unless)
import Data.Aeson (ToJSON(..), FromJSON(..), (.:), (.:?), (.=))
import Data.Bool
import Data.Either (Either(..))
import Data.Eq (Eq(..))
import Data.Function (($), (.))
import Data.Functor ((<$>))
import Data.Maybe (Maybe(..), fromMaybe, fromJust)
import Data.Monoid (Monoid(..))
import Data.Ord (Ord(..))
import Data.Proxy (Proxy(..))
import Data.Reflection (Reifies(..), reify)
import Data.Semigroup (Semigroup(..))
import Data.Text (Text)
import GHC.Generics (Generic)
import GHC.Natural (minusNaturalMaybe)
import Numeric.Natural (Natural)
import Prelude (Integral(..), fromIntegral)
import Text.Read (readMaybe, readEither)
import Text.Show (Show(..))
import qualified Crypto.KDF.PBKDF2 as Crypto
import qualified Data.Aeson as JSON
import qualified Data.Aeson.Types as JSON
import qualified Data.Char as Char
import qualified Data.Text as Text
import qualified Data.Text.Encoding as Text
import qualified System.Random as Random
import Voting.Protocol.Arithmetic
import Voting.Protocol.Cryptography
import Voting.Protocol.Credential
data FFC = FFC
{ FFC -> Text
ffc_name :: !Text
, FFC -> Natural
ffc_fieldCharac :: !Natural
, FFC -> Natural
ffc_groupGen :: !Natural
, FFC -> Natural
ffc_groupOrder :: !Natural
} deriving (FFC -> FFC -> Bool
(FFC -> FFC -> Bool) -> (FFC -> FFC -> Bool) -> Eq FFC
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: FFC -> FFC -> Bool
$c/= :: FFC -> FFC -> Bool
== :: FFC -> FFC -> Bool
$c== :: FFC -> FFC -> Bool
Eq,Int -> FFC -> ShowS
[FFC] -> ShowS
FFC -> String
(Int -> FFC -> ShowS)
-> (FFC -> String) -> ([FFC] -> ShowS) -> Show FFC
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [FFC] -> ShowS
$cshowList :: [FFC] -> ShowS
show :: FFC -> String
$cshow :: FFC -> String
showsPrec :: Int -> FFC -> ShowS
$cshowsPrec :: Int -> FFC -> ShowS
Show,(forall x. FFC -> Rep FFC x)
-> (forall x. Rep FFC x -> FFC) -> Generic FFC
forall x. Rep FFC x -> FFC
forall x. FFC -> Rep FFC x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep FFC x -> FFC
$cfrom :: forall x. FFC -> Rep FFC x
Generic,FFC -> ()
(FFC -> ()) -> NFData FFC
forall a. (a -> ()) -> NFData a
rnf :: FFC -> ()
$crnf :: FFC -> ()
NFData)
instance ToJSON FFC where
toJSON :: FFC -> Value
toJSON FFC{Natural
Text
ffc_groupOrder :: Natural
ffc_groupGen :: Natural
ffc_fieldCharac :: Natural
ffc_name :: Text
ffc_groupOrder :: FFC -> Natural
ffc_groupGen :: FFC -> Natural
ffc_fieldCharac :: FFC -> Natural
ffc_name :: FFC -> Text
..} =
[Pair] -> Value
JSON.object ([Pair] -> Value) -> [Pair] -> Value
forall a b. (a -> b) -> a -> b
$
(if Text -> Bool
Text.null Text
ffc_name then [] else [Text
"name" Text -> Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= Text
ffc_name] ) [Pair] -> [Pair] -> [Pair]
forall a. Semigroup a => a -> a -> a
<>
[ Text
"p" Text -> String -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= Natural -> String
forall a. Show a => a -> String
show Natural
ffc_fieldCharac
, Text
"g" Text -> String -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= Natural -> String
forall a. Show a => a -> String
show Natural
ffc_groupGen
, Text
"q" Text -> String -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= Natural -> String
forall a. Show a => a -> String
show Natural
ffc_groupOrder
]
toEncoding :: FFC -> Encoding
toEncoding FFC{Natural
Text
ffc_groupOrder :: Natural
ffc_groupGen :: Natural
ffc_fieldCharac :: Natural
ffc_name :: Text
ffc_groupOrder :: FFC -> Natural
ffc_groupGen :: FFC -> Natural
ffc_fieldCharac :: FFC -> Natural
ffc_name :: FFC -> Text
..} =
Series -> Encoding
JSON.pairs (Series -> Encoding) -> Series -> Encoding
forall a b. (a -> b) -> a -> b
$
(if Text -> Bool
Text.null Text
ffc_name then Series
forall a. Monoid a => a
mempty else Text
"name" Text -> Text -> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= Text
ffc_name) Series -> Series -> Series
forall a. Semigroup a => a -> a -> a
<>
Text
"p" Text -> String -> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= Natural -> String
forall a. Show a => a -> String
show Natural
ffc_fieldCharac Series -> Series -> Series
forall a. Semigroup a => a -> a -> a
<>
Text
"g" Text -> String -> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= Natural -> String
forall a. Show a => a -> String
show Natural
ffc_groupGen Series -> Series -> Series
forall a. Semigroup a => a -> a -> a
<>
Text
"q" Text -> String -> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= Natural -> String
forall a. Show a => a -> String
show Natural
ffc_groupOrder
instance FromJSON FFC where
parseJSON :: Value -> Parser FFC
parseJSON = String -> (Object -> Parser FFC) -> Value -> Parser FFC
forall a. String -> (Object -> Parser a) -> Value -> Parser a
JSON.withObject String
"FFC" ((Object -> Parser FFC) -> Value -> Parser FFC)
-> (Object -> Parser FFC) -> Value -> Parser FFC
forall a b. (a -> b) -> a -> b
$ \Object
o -> do
Text
ffc_name <- Text -> Maybe Text -> Text
forall a. a -> Maybe a -> a
fromMaybe Text
"" (Maybe Text -> Text) -> Parser (Maybe Text) -> Parser Text
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (Object
o Object -> Text -> Parser (Maybe Text)
forall a. FromJSON a => Object -> Text -> Parser (Maybe a)
.:? Text
"name")
Text
p <- Object
o Object -> Text -> Parser Text
forall a. FromJSON a => Object -> Text -> Parser a
.: Text
"p"
Text
g <- Object
o Object -> Text -> Parser Text
forall a. FromJSON a => Object -> Text -> Parser a
.: Text
"g"
Text
q <- Object
o Object -> Text -> Parser Text
forall a. FromJSON a => Object -> Text -> Parser a
.: Text
"q"
Natural
ffc_fieldCharac <- case String -> Either String Natural
forall a. Read a => String -> Either String a
readEither (Text -> String
Text.unpack Text
p) of
Left String
err -> String -> Value -> Parser Natural
forall a. String -> Value -> Parser a
JSON.typeMismatch (String
"FFC: fieldCharac: "String -> ShowS
forall a. Semigroup a => a -> a -> a
<>String
err) (Text -> Value
JSON.String Text
p)
Right Natural
a -> Natural -> Parser Natural
forall (m :: * -> *) a. Monad m => a -> m a
return Natural
a
Natural
ffc_groupGen <- case String -> Either String Natural
forall a. Read a => String -> Either String a
readEither (Text -> String
Text.unpack Text
g) of
Left String
err -> String -> Value -> Parser Natural
forall a. String -> Value -> Parser a
JSON.typeMismatch (String
"FFC: groupGen: "String -> ShowS
forall a. Semigroup a => a -> a -> a
<>String
err) (Text -> Value
JSON.String Text
g)
Right Natural
a -> Natural -> Parser Natural
forall (m :: * -> *) a. Monad m => a -> m a
return Natural
a
Natural
ffc_groupOrder <- case String -> Either String Natural
forall a. Read a => String -> Either String a
readEither (Text -> String
Text.unpack Text
q) of
Left String
err -> String -> Value -> Parser Natural
forall a. String -> Value -> Parser a
JSON.typeMismatch (String
"FFC: groupOrder: "String -> ShowS
forall a. Semigroup a => a -> a -> a
<>String
err) (Text -> Value
JSON.String Text
q)
Right Natural
a -> Natural -> Parser Natural
forall (m :: * -> *) a. Monad m => a -> m a
return Natural
a
Bool -> Parser () -> Parser ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless (Natural -> Natural
forall a. ToNatural a => a -> Natural
nat Natural
ffc_groupGen Natural -> Natural -> Bool
forall a. Ord a => a -> a -> Bool
< Natural
ffc_fieldCharac) (Parser () -> Parser ()) -> Parser () -> Parser ()
forall a b. (a -> b) -> a -> b
$
String -> Value -> Parser ()
forall a. String -> Value -> Parser a
JSON.typeMismatch String
"FFC: groupGen is not lower than fieldCharac" (Object -> Value
JSON.Object Object
o)
Bool -> Parser () -> Parser ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless (Natural
ffc_groupOrder Natural -> Natural -> Bool
forall a. Ord a => a -> a -> Bool
< Natural
ffc_fieldCharac) (Parser () -> Parser ()) -> Parser () -> Parser ()
forall a b. (a -> b) -> a -> b
$
String -> Value -> Parser ()
forall a. String -> Value -> Parser a
JSON.typeMismatch String
"FFC: groupOrder is not lower than fieldCharac" (Object -> Value
JSON.Object Object
o)
Bool -> Parser () -> Parser ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless (Natural -> Natural
forall a. ToNatural a => a -> Natural
nat Natural
ffc_groupGen Natural -> Natural -> Bool
forall a. Ord a => a -> a -> Bool
> Natural
1) (Parser () -> Parser ()) -> Parser () -> Parser ()
forall a b. (a -> b) -> a -> b
$
String -> Value -> Parser ()
forall a. String -> Value -> Parser a
JSON.typeMismatch String
"FFC: groupGen is not greater than 1" (Object -> Value
JSON.Object Object
o)
Bool -> Parser () -> Parser ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless (Maybe Natural -> Natural
forall a. HasCallStack => Maybe a -> a
fromJust (Natural
ffc_fieldCharacNatural -> Natural -> Maybe Natural
`minusNaturalMaybe`Natural
forall a. Semiring a => a
one) Natural -> Natural -> Natural
forall a. Integral a => a -> a -> a
`rem` Natural
ffc_groupOrder Natural -> Natural -> Bool
forall a. Eq a => a -> a -> Bool
== Natural
0) (Parser () -> Parser ()) -> Parser () -> Parser ()
forall a b. (a -> b) -> a -> b
$
String -> Value -> Parser ()
forall a. String -> Value -> Parser a
JSON.typeMismatch String
"FFC: groupOrder does not divide fieldCharac-1" (Object -> Value
JSON.Object Object
o)
FFC -> Parser FFC
forall (m :: * -> *) a. Monad m => a -> m a
return FFC :: Text -> Natural -> Natural -> Natural -> FFC
FFC{Natural
Text
ffc_groupOrder :: Natural
ffc_groupGen :: Natural
ffc_fieldCharac :: Natural
ffc_name :: Text
ffc_groupOrder :: Natural
ffc_groupGen :: Natural
ffc_fieldCharac :: Natural
ffc_name :: Text
..}
instance Reifies c FFC => CryptoParams FFC c where
groupGen :: G FFC c
groupGen = FieldElement FFC -> G FFC c
forall crypto c. FieldElement crypto -> G crypto c
G (FieldElement FFC -> G FFC c) -> FieldElement FFC -> G FFC c
forall a b. (a -> b) -> a -> b
$ FFC -> Natural
ffc_groupGen (FFC -> Natural) -> FFC -> Natural
forall a b. (a -> b) -> a -> b
$ Proxy c -> FFC
forall k (s :: k) a (proxy :: k -> *). Reifies s a => proxy s -> a
reflect (Proxy c
forall k (t :: k). Proxy t
Proxy::Proxy c)
groupOrder :: Proxy c -> Natural
groupOrder Proxy c
c = FFC -> Natural
ffc_groupOrder (FFC -> Natural) -> FFC -> Natural
forall a b. (a -> b) -> a -> b
$ Proxy c -> FFC
forall k (s :: k) a (proxy :: k -> *). Reifies s a => proxy s -> a
reflect Proxy c
c
instance ReifyCrypto FFC where
reifyCrypto :: FFC
-> (forall c. (Reifies c FFC, CryptoParams FFC c) => Proxy c -> r)
-> r
reifyCrypto = FFC
-> (forall c. (Reifies c FFC, CryptoParams FFC c) => Proxy c -> r)
-> r
forall a r. a -> (forall s. Reifies s a => Proxy s -> r) -> r
reify
instance Key FFC where
cryptoType :: FFC -> Text
cryptoType FFC
_ = Text
"FFC"
cryptoName :: FFC -> Text
cryptoName = FFC -> Text
ffc_name
randomSecretKey :: StateT r m (SecretKey FFC c)
randomSecretKey = StateT r m (SecretKey FFC c)
forall (m :: * -> *) r i.
(Monad m, RandomGen r, Random i, Bounded i) =>
StateT r m i
random
credentialSecretKey :: UUID -> Credential -> SecretKey FFC c
credentialSecretKey (UUID Text
uuid) (Credential Text
cred) =
Natural -> SecretKey FFC c
forall a. FromNatural a => Natural -> a
fromNatural (Natural -> SecretKey FFC c) -> Natural -> SecretKey FFC c
forall a b. (a -> b) -> a -> b
$ ByteString -> Natural
decodeBigEndian (ByteString -> Natural) -> ByteString -> Natural
forall a b. (a -> b) -> a -> b
$
Parameters -> ByteString -> ByteString -> ByteString
forall password salt out.
(ByteArrayAccess password, ByteArrayAccess salt, ByteArray out) =>
Parameters -> password -> salt -> out
Crypto.fastPBKDF2_SHA256
Parameters :: Int -> Int -> Parameters
Crypto.Parameters
{ iterCounts :: Int
Crypto.iterCounts = Int
1000
, outputLength :: Int
Crypto.outputLength = Int
32
}
(Text -> ByteString
Text.encodeUtf8 Text
cred)
(Text -> ByteString
Text.encodeUtf8 Text
uuid)
publicKey :: SecretKey FFC c -> PublicKey FFC c
publicKey = (forall c. CryptoParams FFC c => G FFC c
forall crypto c. CryptoParams crypto c => G crypto c
groupGen @FFC PublicKey FFC c -> SecretKey FFC c -> PublicKey FFC c
forall crypto c.
(Reifies c crypto, Semiring (G crypto c)) =>
G crypto c -> E crypto c -> G crypto c
^)
fieldCharac :: forall c. Reifies c FFC => Natural
fieldCharac :: Natural
fieldCharac = FFC -> Natural
ffc_fieldCharac (FFC -> Natural) -> FFC -> Natural
forall a b. (a -> b) -> a -> b
$ Proxy c -> FFC
forall k (s :: k) a (proxy :: k -> *). Reifies s a => proxy s -> a
reflect (Proxy c
forall k (t :: k). Proxy t
Proxy::Proxy c)
weakFFC :: FFC
weakFFC :: FFC
weakFFC = FFC :: Text -> Natural -> Natural -> Natural -> FFC
FFC
{ ffc_name :: Text
ffc_name = Text
"weakFFC"
, ffc_fieldCharac :: Natural
ffc_fieldCharac = Natural
263
, ffc_groupGen :: Natural
ffc_groupGen = Natural
2
, ffc_groupOrder :: Natural
ffc_groupOrder = Natural
131
}
beleniosFFC :: FFC
beleniosFFC :: FFC
beleniosFFC = FFC :: Text -> Natural -> Natural -> Natural -> FFC
FFC
{ ffc_name :: Text
ffc_name = Text
"beleniosFFC"
, ffc_fieldCharac :: Natural
ffc_fieldCharac = Natural
20694785691422546401013643657505008064922989295751104097100884787057374219242717401922237254497684338129066633138078958404960054389636289796393038773905722803605973749427671376777618898589872735865049081167099310535867780980030790491654063777173764198678527273474476341835600035698305193144284561701911000786737307333564123971732897913240474578834468260652327974647951137672658693582180046317922073668860052627186363386088796882120769432366149491002923444346373222145884100586421050242120365433561201320481118852408731077014151666200162313177169372189248078507711827842317498073276598828825169183103125680162072880719
, ffc_groupGen :: Natural
ffc_groupGen = Natural
2402352677501852209227687703532399932712287657378364916510075318787663274146353219320285676155269678799694668298749389095083896573425601900601068477164491735474137283104610458681314511781646755400527402889846139864532661215055797097162016168270312886432456663834863635782106154918419982534315189740658186868651151358576410138882215396016043228843603930989333662772848406593138406010231675095763777982665103606822406635076697764025346253773085133173495194248967754052573659049492477631475991575198775177711481490920456600205478127054728238140972518639858334115700568353695553423781475582491896050296680037745308460627
, ffc_groupOrder :: Natural
ffc_groupOrder = Natural
78571733251071885079927659812671450121821421258408794611510081919805623223441
}
type instance FieldElement FFC = Natural
deriving newtype instance Eq (G FFC c)
deriving newtype instance Ord (G FFC c)
deriving newtype instance NFData (G FFC c)
deriving newtype instance Show (G FFC c)
instance Reifies c FFC => FromJSON (G FFC c) where
parseJSON :: Value -> Parser (G FFC c)
parseJSON (JSON.String Text
s)
| Just (Char
c0,Text
_) <- Text -> Maybe (Char, Text)
Text.uncons Text
s
, Char
c0 Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
/= Char
'0'
, (Char -> Bool) -> Text -> Bool
Text.all Char -> Bool
Char.isDigit Text
s
, Just Natural
x <- String -> Maybe Natural
forall a. Read a => String -> Maybe a
readMaybe (Text -> String
Text.unpack Text
s)
, Natural
x Natural -> Natural -> Bool
forall a. Ord a => a -> a -> Bool
< Reifies c FFC => Natural
forall c. Reifies c FFC => Natural
fieldCharac @c
, G FFC c
r <- FieldElement FFC -> G FFC c
forall crypto c. FieldElement crypto -> G crypto c
G Natural
FieldElement FFC
x
, G FFC c
r G FFC c -> E FFC c -> G FFC c
forall crypto c.
(Reifies c crypto, Semiring (G crypto c)) =>
G crypto c -> E crypto c -> G crypto c
^ Natural -> E FFC c
forall crypto c. Natural -> E crypto c
E (Proxy c -> Natural
forall crypto c. CryptoParams crypto c => Proxy c -> Natural
groupOrder @FFC (Proxy c
forall k (t :: k). Proxy t
Proxy @c)) G FFC c -> G FFC c -> Bool
forall a. Eq a => a -> a -> Bool
== G FFC c
forall a. Semiring a => a
one
= G FFC c -> Parser (G FFC c)
forall (m :: * -> *) a. Monad m => a -> m a
return G FFC c
r
parseJSON Value
json = String -> Value -> Parser (G FFC c)
forall a. String -> Value -> Parser a
JSON.typeMismatch String
"GroupElement" Value
json
instance ToJSON (G FFC c) where
toJSON :: G FFC c -> Value
toJSON (G FieldElement FFC
x) = String -> Value
forall a. ToJSON a => a -> Value
JSON.toJSON (Natural -> String
forall a. Show a => a -> String
show Natural
FieldElement FFC
x)
instance Reifies c FFC => FromNatural (G FFC c) where
fromNatural :: Natural -> G FFC c
fromNatural Natural
i = FieldElement FFC -> G FFC c
forall crypto c. FieldElement crypto -> G crypto c
G (FieldElement FFC -> G FFC c) -> FieldElement FFC -> G FFC c
forall a b. (a -> b) -> a -> b
$ Natural -> Natural
abs (Natural -> Natural) -> Natural -> Natural
forall a b. (a -> b) -> a -> b
$ Natural
i Natural -> Natural -> Natural
forall a. Integral a => a -> a -> a
`mod` Reifies c FFC => Natural
forall c. Reifies c FFC => Natural
fieldCharac @c
where
abs :: Natural -> Natural
abs Natural
x | Natural
x Natural -> Natural -> Bool
forall a. Ord a => a -> a -> Bool
< Natural
0 = Natural
x Natural -> Natural -> Natural
forall a. Additive a => a -> a -> a
+ Reifies c FFC => Natural
forall c. Reifies c FFC => Natural
fieldCharac @c
| Bool
otherwise = Natural
x
instance ToNatural (G FFC c) where
nat :: G FFC c -> Natural
nat = G FFC c -> Natural
forall crypto c. G crypto c -> FieldElement crypto
unG
instance Reifies c FFC => Additive (G FFC c) where
zero :: G FFC c
zero = FieldElement FFC -> G FFC c
forall crypto c. FieldElement crypto -> G crypto c
G FieldElement FFC
0
G FieldElement FFC
x + :: G FFC c -> G FFC c -> G FFC c
+ G FieldElement FFC
y = FieldElement FFC -> G FFC c
forall crypto c. FieldElement crypto -> G crypto c
G (FieldElement FFC -> G FFC c) -> FieldElement FFC -> G FFC c
forall a b. (a -> b) -> a -> b
$ (Natural
FieldElement FFC
x Natural -> Natural -> Natural
forall a. Additive a => a -> a -> a
+ Natural
FieldElement FFC
y) Natural -> Natural -> Natural
forall a. Integral a => a -> a -> a
`mod` Reifies c FFC => Natural
forall c. Reifies c FFC => Natural
fieldCharac @c
instance Reifies c FFC => Semiring (G FFC c) where
one :: G FFC c
one = FieldElement FFC -> G FFC c
forall crypto c. FieldElement crypto -> G crypto c
G FieldElement FFC
1
G FieldElement FFC
x * :: G FFC c -> G FFC c -> G FFC c
* G FieldElement FFC
y = FieldElement FFC -> G FFC c
forall crypto c. FieldElement crypto -> G crypto c
G (FieldElement FFC -> G FFC c) -> FieldElement FFC -> G FFC c
forall a b. (a -> b) -> a -> b
$ (Natural
FieldElement FFC
x Natural -> Natural -> Natural
forall a. Semiring a => a -> a -> a
* Natural
FieldElement FFC
y) Natural -> Natural -> Natural
forall a. Integral a => a -> a -> a
`mod` Reifies c FFC => Natural
forall c. Reifies c FFC => Natural
fieldCharac @c
instance Reifies c FFC => Ring (G FFC c) where
negate :: G FFC c -> G FFC c
negate (G FieldElement FFC
x)
| Natural
FieldElement FFC
x Natural -> Natural -> Bool
forall a. Eq a => a -> a -> Bool
== Natural
0 = G FFC c
forall a. Additive a => a
zero
| Bool
otherwise = FieldElement FFC -> G FFC c
forall crypto c. FieldElement crypto -> G crypto c
G (FieldElement FFC -> G FFC c) -> FieldElement FFC -> G FFC c
forall a b. (a -> b) -> a -> b
$ Maybe Natural -> Natural
forall a. HasCallStack => Maybe a -> a
fromJust (Maybe Natural -> Natural) -> Maybe Natural -> Natural
forall a b. (a -> b) -> a -> b
$ Natural -> Natural
forall a. ToNatural a => a -> Natural
nat (Reifies c FFC => Natural
forall c. Reifies c FFC => Natural
fieldCharac @c)Natural -> Natural -> Maybe Natural
`minusNaturalMaybe`Natural
FieldElement FFC
x
instance Reifies c FFC => EuclideanRing (G FFC c) where
inverse :: G FFC c -> G FFC c
inverse = (G FFC c -> E FFC c -> G FFC c
forall crypto c.
(Reifies c crypto, Semiring (G crypto c)) =>
G crypto c -> E crypto c -> G crypto c
^ Natural -> E FFC c
forall crypto c. Natural -> E crypto c
E (Maybe Natural -> Natural
forall a. HasCallStack => Maybe a -> a
fromJust (Maybe Natural -> Natural) -> Maybe Natural -> Natural
forall a b. (a -> b) -> a -> b
$ Proxy c -> Natural
forall crypto c. CryptoParams crypto c => Proxy c -> Natural
groupOrder @FFC (Proxy c
forall k (t :: k). Proxy t
Proxy @c)Natural -> Natural -> Maybe Natural
`minusNaturalMaybe`Natural
1))
instance Reifies c FFC => Random.Random (G FFC c) where
randomR :: (G FFC c, G FFC c) -> g -> (G FFC c, g)
randomR (G FieldElement FFC
lo, G FieldElement FFC
hi) =
(Integer -> G FFC c) -> (Integer, g) -> (G FFC c, g)
forall (a :: * -> * -> *) b c d.
Arrow a =>
a b c -> a (b, d) (c, d)
first (Natural -> G FFC c
forall crypto c. FieldElement crypto -> G crypto c
G (Natural -> G FFC c) -> (Integer -> Natural) -> Integer -> G FFC c
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Integer -> Natural
forall a b. (Integral a, Num b) => a -> b
fromIntegral) ((Integer, g) -> (G FFC c, g))
-> (g -> (Integer, g)) -> g -> (G FFC c, g)
forall b c a. (b -> c) -> (a -> b) -> a -> c
.
(Integer, Integer) -> g -> (Integer, g)
forall a g. (Random a, RandomGen g) => (a, a) -> g -> (a, g)
Random.randomR
( Integer
0Integer -> Integer -> Integer
forall a. Ord a => a -> a -> a
`max`Natural -> Integer
forall a. Integral a => a -> Integer
toInteger Natural
FieldElement FFC
lo
, Natural -> Integer
forall a. Integral a => a -> Integer
toInteger Natural
FieldElement FFC
hiInteger -> Integer -> Integer
forall a. Ord a => a -> a -> a
`min`(Natural -> Integer
forall a. Integral a => a -> Integer
toInteger (Reifies c FFC => Natural
forall c. Reifies c FFC => Natural
fieldCharac @c) Integer -> Integer -> Integer
forall a. Ring a => a -> a -> a
- Integer
1) )
random :: g -> (G FFC c, g)
random =
(Integer -> G FFC c) -> (Integer, g) -> (G FFC c, g)
forall (a :: * -> * -> *) b c d.
Arrow a =>
a b c -> a (b, d) (c, d)
first (Natural -> G FFC c
forall crypto c. FieldElement crypto -> G crypto c
G (Natural -> G FFC c) -> (Integer -> Natural) -> Integer -> G FFC c
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Integer -> Natural
forall a b. (Integral a, Num b) => a -> b
fromIntegral) ((Integer, g) -> (G FFC c, g))
-> (g -> (Integer, g)) -> g -> (G FFC c, g)
forall b c a. (b -> c) -> (a -> b) -> a -> c
.
(Integer, Integer) -> g -> (Integer, g)
forall a g. (Random a, RandomGen g) => (a, a) -> g -> (a, g)
Random.randomR (Integer
0, Natural -> Integer
forall a. Integral a => a -> Integer
toInteger (Reifies c FFC => Natural
forall c. Reifies c FFC => Natural
fieldCharac @c) Integer -> Integer -> Integer
forall a. Ring a => a -> a -> a
- Integer
1)