module Curve
( module Curve
, module Group
) where
import Protolude
import Control.Monad.Random (Random(..))
import GaloisField (GaloisField)
import PrimeField (PrimeField, toInt)
import Test.Tasty.QuickCheck (Arbitrary(..), suchThatMap)
import Group (Group(..))
class (GaloisField q, GaloisField r, Group (Point f c e q r))
=> Curve (f :: Form) (c :: Coordinates) e q r where
{-# MINIMAL char, cof, disc, fromA, point, pointX, toA, yX #-}
char :: Point f c e q r -> Integer
cof :: Point f c e q r -> Integer
disc :: Point f c e q r -> q
data family Point f c e q r :: *
mul :: r ~ PrimeField p => Point f c e q r -> r -> Point f c e q r
mul = (. toInt) . mul'
{-# INLINABLE mul #-}
point :: q -> q -> Maybe (Point f c e q r)
pointX :: q -> Maybe (Point f c e q r)
yX :: Point f c e q r -> q -> Maybe q
fromA :: Point f 'Affine e q r -> Point f c e q r
toA :: Point f c e q r -> Point f 'Affine e q r
data Form = Binary
| Edwards
| Montgomery
| Weierstrass
data Coordinates = Affine
| Jacobian
| Projective
instance Curve f c e q r => Monoid (Point f c e q r) where
mempty = id
{-# INLINABLE mempty #-}
instance Curve f c e q r => Semigroup (Point f c e q r) where
p <> q = if p == q then dbl p else add p q
{-# INLINABLE (<>) #-}
instance Curve f c e q r => Arbitrary (Point f c e q r) where
arbitrary = suchThatMap arbitrary pointX
{-# INLINABLE arbitrary #-}
instance Curve f c e q r => Random (Point f c e q r) where
random g = let (x, g') = random g in case pointX x of
Just p -> (p, g')
_ -> random g'
{-# INLINABLE random #-}
randomR = panic "not implemented."