elliptic-curve-0.2.2: Elliptic curve library

Safe HaskellNone
LanguageHaskell2010

Group.Field

Synopsis

Documentation

class (Arbitrary g, Eq g, Generic g, Monoid g, Pretty g, Random g, Show g) => Group g where Source #

Groups.

Minimal complete definition

add, dbl, def, gen, id, inv, order

Methods

add :: g -> g -> g Source #

Element addition.

dbl :: g -> g Source #

Element doubling.

def :: g -> Bool Source #

Check well-defined.

gen :: g Source #

Group generator.

id :: g Source #

Identity element.

inv :: g -> g Source #

Element inversion.

mul' :: g -> Integer -> g Source #

Element multiplication.

order :: g -> Integer Source #

Curve order.

rnd :: MonadRandom m => m g Source #

Random element.

Instances
FGroup r q => Group (Element r q) Source # 
Instance details

Defined in Group.Field

Methods

add :: Element r q -> Element r q -> Element r q Source #

dbl :: Element r q -> Element r q Source #

def :: Element r q -> Bool Source #

gen :: Element r q Source #

id :: Element r q Source #

inv :: Element r q -> Element r q Source #

mul' :: Element r q -> Integer -> Element r q Source #

order :: Element r q -> Integer Source #

rnd :: MonadRandom m => m (Element r q) Source #

WPCurve e q r => Group (WPPoint e q r) Source # 
Instance details

Defined in Curve.Weierstrass

Methods

add :: WPPoint e q r -> WPPoint e q r -> WPPoint e q r Source #

dbl :: WPPoint e q r -> WPPoint e q r Source #

def :: WPPoint e q r -> Bool Source #

gen :: WPPoint e q r Source #

id :: WPPoint e q r Source #

inv :: WPPoint e q r -> WPPoint e q r Source #

mul' :: WPPoint e q r -> Integer -> WPPoint e q r Source #

order :: WPPoint e q r -> Integer Source #

rnd :: MonadRandom m => m (WPPoint e q r) Source #

WJCurve e q r => Group (WJPoint e q r) Source # 
Instance details

Defined in Curve.Weierstrass

Methods

add :: WJPoint e q r -> WJPoint e q r -> WJPoint e q r Source #

dbl :: WJPoint e q r -> WJPoint e q r Source #

def :: WJPoint e q r -> Bool Source #

gen :: WJPoint e q r Source #

id :: WJPoint e q r Source #

inv :: WJPoint e q r -> WJPoint e q r Source #

mul' :: WJPoint e q r -> Integer -> WJPoint e q r Source #

order :: WJPoint e q r -> Integer Source #

rnd :: MonadRandom m => m (WJPoint e q r) Source #

WACurve e q r => Group (WAPoint e q r) Source # 
Instance details

Defined in Curve.Weierstrass

Methods

add :: WAPoint e q r -> WAPoint e q r -> WAPoint e q r Source #

dbl :: WAPoint e q r -> WAPoint e q r Source #

def :: WAPoint e q r -> Bool Source #

gen :: WAPoint e q r Source #

id :: WAPoint e q r Source #

inv :: WAPoint e q r -> WAPoint e q r Source #

mul' :: WAPoint e q r -> Integer -> WAPoint e q r Source #

order :: WAPoint e q r -> Integer Source #

rnd :: MonadRandom m => m (WAPoint e q r) Source #

MACurve e q r => Group (MAPoint e q r) Source # 
Instance details

Defined in Curve.Montgomery

Methods

add :: MAPoint e q r -> MAPoint e q r -> MAPoint e q r Source #

dbl :: MAPoint e q r -> MAPoint e q r Source #

def :: MAPoint e q r -> Bool Source #

gen :: MAPoint e q r Source #

id :: MAPoint e q r Source #

inv :: MAPoint e q r -> MAPoint e q r Source #

mul' :: MAPoint e q r -> Integer -> MAPoint e q r Source #

order :: MAPoint e q r -> Integer Source #

rnd :: MonadRandom m => m (MAPoint e q r) Source #

EPCurve e q r => Group (EPPoint e q r) Source # 
Instance details

Defined in Curve.Edwards

Methods

add :: EPPoint e q r -> EPPoint e q r -> EPPoint e q r Source #

dbl :: EPPoint e q r -> EPPoint e q r Source #

def :: EPPoint e q r -> Bool Source #

gen :: EPPoint e q r Source #

id :: EPPoint e q r Source #

inv :: EPPoint e q r -> EPPoint e q r Source #

mul' :: EPPoint e q r -> Integer -> EPPoint e q r Source #

order :: EPPoint e q r -> Integer Source #

rnd :: MonadRandom m => m (EPPoint e q r) Source #

EACurve e q r => Group (EAPoint e q r) Source # 
Instance details

Defined in Curve.Edwards

Methods

add :: EAPoint e q r -> EAPoint e q r -> EAPoint e q r Source #

dbl :: EAPoint e q r -> EAPoint e q r Source #

def :: EAPoint e q r -> Bool Source #

gen :: EAPoint e q r Source #

id :: EAPoint e q r Source #

inv :: EAPoint e q r -> EAPoint e q r Source #

mul' :: EAPoint e q r -> Integer -> EAPoint e q r Source #

order :: EAPoint e q r -> Integer Source #

rnd :: MonadRandom m => m (EAPoint e q r) Source #

BPCurve e q r => Group (BPPoint e q r) Source # 
Instance details

Defined in Curve.Binary

Methods

add :: BPPoint e q r -> BPPoint e q r -> BPPoint e q r Source #

dbl :: BPPoint e q r -> BPPoint e q r Source #

def :: BPPoint e q r -> Bool Source #

gen :: BPPoint e q r Source #

id :: BPPoint e q r Source #

inv :: BPPoint e q r -> BPPoint e q r Source #

mul' :: BPPoint e q r -> Integer -> BPPoint e q r Source #

order :: BPPoint e q r -> Integer Source #

rnd :: MonadRandom m => m (BPPoint e q r) Source #

BACurve e q r => Group (BAPoint e q r) Source # 
Instance details

Defined in Curve.Binary

Methods

add :: BAPoint e q r -> BAPoint e q r -> BAPoint e q r Source #

dbl :: BAPoint e q r -> BAPoint e q r Source #

def :: BAPoint e q r -> Bool Source #

gen :: BAPoint e q r Source #

id :: BAPoint e q r Source #

inv :: BAPoint e q r -> BAPoint e q r Source #

mul' :: BAPoint e q r -> Integer -> BAPoint e q r Source #

order :: BAPoint e q r -> Integer Source #

rnd :: MonadRandom m => m (BAPoint e q r) Source #

newtype Element r q Source #

Field elements.

Constructors

F q 
Instances
Functor (Element r) Source # 
Instance details

Defined in Group.Field

Methods

fmap :: (a -> b) -> Element r a -> Element r b #

(<$) :: a -> Element r b -> Element r a #

Eq q => Eq (Element r q) Source # 
Instance details

Defined in Group.Field

Methods

(==) :: Element r q -> Element r q -> Bool #

(/=) :: Element r q -> Element r q -> Bool #

Read q => Read (Element r q) Source # 
Instance details

Defined in Group.Field

Show q => Show (Element r q) Source # 
Instance details

Defined in Group.Field

Methods

showsPrec :: Int -> Element r q -> ShowS #

show :: Element r q -> String #

showList :: [Element r q] -> ShowS #

Generic (Element r q) Source # 
Instance details

Defined in Group.Field

Associated Types

type Rep (Element r q) :: Type -> Type #

Methods

from :: Element r q -> Rep (Element r q) x #

to :: Rep (Element r q) x -> Element r q #

FGroup r q => Semigroup (Element r q) Source # 
Instance details

Defined in Group.Field

Methods

(<>) :: Element r q -> Element r q -> Element r q #

sconcat :: NonEmpty (Element r q) -> Element r q #

stimes :: Integral b => b -> Element r q -> Element r q #

FGroup r q => Monoid (Element r q) Source # 
Instance details

Defined in Group.Field

Methods

mempty :: Element r q #

mappend :: Element r q -> Element r q -> Element r q #

mconcat :: [Element r q] -> Element r q #

FGroup r q => Random (Element r q) Source # 
Instance details

Defined in Group.Field

Methods

randomR :: RandomGen g => (Element r q, Element r q) -> g -> (Element r q, g) #

random :: RandomGen g => g -> (Element r q, g) #

randomRs :: RandomGen g => (Element r q, Element r q) -> g -> [Element r q] #

randoms :: RandomGen g => g -> [Element r q] #

randomRIO :: (Element r q, Element r q) -> IO (Element r q) #

randomIO :: IO (Element r q) #

FGroup r q => Arbitrary (Element r q) Source # 
Instance details

Defined in Group.Field

Methods

arbitrary :: Gen (Element r q) #

shrink :: Element r q -> [Element r q] #

NFData q => NFData (Element r q) Source # 
Instance details

Defined in Group.Field

Methods

rnf :: Element r q -> () #

FGroup r q => Pretty (Element r q) Source # 
Instance details

Defined in Group.Field

Methods

pretty :: Element r q -> Doc #

prettyList :: [Element r q] -> Doc #

FGroup r q => Group (Element r q) Source # 
Instance details

Defined in Group.Field

Methods

add :: Element r q -> Element r q -> Element r q Source #

dbl :: Element r q -> Element r q Source #

def :: Element r q -> Bool Source #

gen :: Element r q Source #

id :: Element r q Source #

inv :: Element r q -> Element r q Source #

mul' :: Element r q -> Integer -> Element r q Source #

order :: Element r q -> Integer Source #

rnd :: MonadRandom m => m (Element r q) Source #

type Rep (Element r q) Source # 
Instance details

Defined in Group.Field

type Rep (Element r q) = D1 (MetaData "Element" "Group.Field" "elliptic-curve-0.2.2-GZMYFFpur3HJhgxx5eqVvs" True) (C1 (MetaCons "F" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 q)))

class (GaloisField q, PrimeField' r) => FGroup r q where Source #

Field groups.

Methods

g_ Source #

Arguments

:: Element r q

Group generator.

h_ Source #

Arguments

:: Element r q 
-> Integer

Group cofactor.

q_ Source #

Arguments

:: Element r q 
-> Integer

Group characteristic.

r_ Source #

Arguments

:: Element r q 
-> Integer

Group order.

Instances
FGroup Fr Fq12 Source #

BN254TF group is a field group.

Instance details

Defined in Group.Field.BN254TF