Safe Haskell | None |
---|---|
Language | Haskell2010 |
Pairing.Group
Contents
Description
Definitions of the groups the pairing is defined on
Synopsis
- class Monoid g => CyclicGroup g where
- type G1 = Point Fq
- type G2 = Point Fq2
- type GT = Fq12
- isOnCurveG1 :: G1 -> Bool
- isOnCurveG2 :: G2 -> Bool
- isInGT :: GT -> Bool
- g1 :: G1
- g2 :: G2
- b1 :: Fq
- b2 :: Fq2
- hashToG1 :: MonadRandom m => ByteString -> m (Maybe G1)
- groupFromX :: (Validate (Point a), FromX a) => Bool -> a -> Maybe (Point a)
- fromByteStringG1 :: ByteString -> Either Text G1
- fromByteStringG2 :: ByteString -> Either Text G2
- fromByteStringGT :: ByteString -> Either Text GT
Documentation
class Monoid g => CyclicGroup g where Source #
Methods
order :: Proxy g -> Integer Source #
expn :: AsInteger e => g -> e -> g Source #
random :: MonadRandom m => g -> m g Source #
Instances
CyclicGroup GT Source # | |
CyclicGroup G2 Source # | |
CyclicGroup G1 Source # | |
isOnCurveG1 :: G1 -> Bool Source #
Test whether a value in G1 satisfies the corresponding curve equation
isOnCurveG2 :: G2 -> Bool Source #
Test whether a value in G2 satisfies the corresponding curve equation
hashToG1 :: MonadRandom m => ByteString -> m (Maybe G1) Source #
fromByteStringG1 :: ByteString -> Either Text G1 Source #
fromByteStringG2 :: ByteString -> Either Text G2 Source #
fromByteStringGT :: ByteString -> Either Text GT Source #
Orphan instances
Semigroup GT Source # | |
Semigroup G2 Source # | |
Semigroup G1 Source # | |
Monoid GT Source # | |
Monoid G2 Source # | |
Monoid G1 Source # | |
Validate GT Source # | |
Methods isValidElement :: GT -> Bool Source # | |
Validate G2 Source # | |
Methods isValidElement :: G2 -> Bool Source # | |
Validate G1 Source # | |
Methods isValidElement :: G1 -> Bool Source # | |
CyclicGroup GT Source # | |
CyclicGroup G2 Source # | |
CyclicGroup G1 Source # | |
ToUncompressedForm GT Source # | |
Methods | |
ToUncompressedForm G2 Source # | |
Methods | |
ToUncompressedForm G1 Source # | |
Methods | |
ToCompressedForm G2 Source # | |
Methods serializeCompressed :: G2 -> Maybe ByteString Source # | |
ToCompressedForm G1 Source # | |
Methods serializeCompressed :: G1 -> Maybe ByteString Source # | |
Arbitrary (Point Fq) Source # | |
Arbitrary (Point Fq2) Source # | |