bulletproofs-0.3.0

Safe HaskellNone
LanguageHaskell2010

Bulletproofs.Fq

Synopsis

Documentation

newtype Fq Source #

Prime field with characteristic _q

Constructors

Fq Integer

Use new instead of this constructor

Instances
Eq Fq Source # 
Instance details

Defined in Bulletproofs.Fq

Methods

(==) :: Fq -> Fq -> Bool #

(/=) :: Fq -> Fq -> Bool #

Fractional Fq Source # 
Instance details

Defined in Bulletproofs.Fq

Methods

(/) :: Fq -> Fq -> Fq #

recip :: Fq -> Fq #

fromRational :: Rational -> Fq #

Num Fq Source # 
Instance details

Defined in Bulletproofs.Fq

Methods

(+) :: Fq -> Fq -> Fq #

(-) :: Fq -> Fq -> Fq #

(*) :: Fq -> Fq -> Fq #

negate :: Fq -> Fq #

abs :: Fq -> Fq #

signum :: Fq -> Fq #

fromInteger :: Integer -> Fq #

Ord Fq Source # 
Instance details

Defined in Bulletproofs.Fq

Methods

compare :: Fq -> Fq -> Ordering #

(<) :: Fq -> Fq -> Bool #

(<=) :: Fq -> Fq -> Bool #

(>) :: Fq -> Fq -> Bool #

(>=) :: Fq -> Fq -> Bool #

max :: Fq -> Fq -> Fq #

min :: Fq -> Fq -> Fq #

Show Fq Source # 
Instance details

Defined in Bulletproofs.Fq

Methods

showsPrec :: Int -> Fq -> ShowS #

show :: Fq -> String #

showList :: [Fq] -> ShowS #

Generic Fq Source # 
Instance details

Defined in Bulletproofs.Fq

Associated Types

type Rep Fq :: * -> * #

Methods

from :: Fq -> Rep Fq x #

to :: Rep Fq x -> Fq #

Bits Fq Source # 
Instance details

Defined in Bulletproofs.Fq

Methods

(.&.) :: Fq -> Fq -> Fq #

(.|.) :: Fq -> Fq -> Fq #

xor :: Fq -> Fq -> Fq #

complement :: Fq -> Fq #

shift :: Fq -> Int -> Fq #

rotate :: Fq -> Int -> Fq #

zeroBits :: Fq #

bit :: Int -> Fq #

setBit :: Fq -> Int -> Fq #

clearBit :: Fq -> Int -> Fq #

complementBit :: Fq -> Int -> Fq #

testBit :: Fq -> Int -> Bool #

bitSizeMaybe :: Fq -> Maybe Int #

bitSize :: Fq -> Int #

isSigned :: Fq -> Bool #

shiftL :: Fq -> Int -> Fq #

unsafeShiftL :: Fq -> Int -> Fq #

shiftR :: Fq -> Int -> Fq #

unsafeShiftR :: Fq -> Int -> Fq #

rotateL :: Fq -> Int -> Fq #

rotateR :: Fq -> Int -> Fq #

popCount :: Fq -> Int #

NFData Fq Source # 
Instance details

Defined in Bulletproofs.Fq

Methods

rnf :: Fq -> () #

Field Fq Source # 
Instance details

Defined in Bulletproofs.Utils

Methods

fSquare :: Fq -> Fq Source #

AsInteger Fq Source # 
Instance details

Defined in Bulletproofs.Utils

Methods

asInteger :: Fq -> Integer Source #

type Rep Fq Source # 
Instance details

Defined in Bulletproofs.Fq

type Rep Fq = D1 (MetaData "Fq" "Bulletproofs.Fq" "bulletproofs-0.3.0-KGNnjqv8oXE3Ja1bDTt0Hv" True) (C1 (MetaCons "Fq" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Integer)))

new :: Integer -> Fq Source #

Turn an integer into an Fq number, should be used instead of the Fq constructor.

norm :: Fq -> Fq Source #

fqAdd :: Fq -> Fq -> Fq Source #

fqMul :: Fq -> Fq -> Fq Source #

fqDiv :: Fq -> Fq -> Fq Source #

fqInv :: Fq -> Fq Source #

Multiplicative inverse

fqZero :: Fq Source #

Additive identity

fqOne :: Fq Source #

Multiplicative identity

inv :: Fq -> Fq Source #

euclidean :: Integral a => a -> a -> a Source #

Euclidean algorithm to compute inverse in an integral domain a

inv' :: Integral a => a -> a -> (a, a) Source #