{-# Language ImportQualifiedPost, QuasiQuotes, ViewPatterns #-}
module Main (main) where
import Advent.Format (format)
import Data.Foldable (traverse_)
import GHC.TypeNats (KnownNat, SomeNat(SomeNat), someNatVal)
import Math.NumberTheory.Moduli ((^%), Mod, cyclicGroup, discreteLogarithm, getVal, isMultElement, isPrimitiveRoot)
import Numeric.Natural (Natural)
data DHParams = DH Integer Natural
params :: DHParams
params :: DHParams
params = Integer -> Natural -> DHParams
DH Integer
7 Natural
20201227
main :: IO ()
IO ()
main =
do (Integer
pub1,Integer
pub2) <- [format|2020 25 %lu%n%lu%n|]
(Integer -> IO ()) -> Maybe Integer -> IO ()
forall (t :: * -> *) (f :: * -> *) a b.
(Foldable t, Applicative f) =>
(a -> f b) -> t a -> f ()
traverse_ Integer -> IO ()
forall a. Show a => a -> IO ()
print (DHParams -> Integer -> Integer -> Maybe Integer
hack DHParams
params Integer
pub1 Integer
pub2)
hack :: DHParams -> Integer -> Integer -> Maybe Integer
hack :: DHParams -> Integer -> Integer -> Maybe Integer
hack (DH Integer
g (Natural -> SomeNat
someNatVal -> SomeNat Proxy n
n)) (Proxy n -> Integer -> Mod n
forall (m :: Natural) (proxy :: Natural -> *).
KnownNat m =>
proxy m -> Integer -> Mod m
toMod Proxy n
n -> Mod n
public1) (Proxy n -> Integer -> Mod n
forall (m :: Natural) (proxy :: Natural -> *).
KnownNat m =>
proxy m -> Integer -> Mod m
toMod Proxy n
n -> Mod n
public2) =
do CyclicGroup Integer n
cg <- Maybe (CyclicGroup Integer n)
forall a (m :: Natural).
(Integral a, UniqueFactorisation a, KnownNat m) =>
Maybe (CyclicGroup a m)
cyclicGroup
PrimitiveRoot n
subject <- CyclicGroup Integer n -> Mod n -> Maybe (PrimitiveRoot n)
forall a (m :: Natural).
(Integral a, UniqueFactorisation a) =>
CyclicGroup a m -> Mod m -> Maybe (PrimitiveRoot m)
isPrimitiveRoot CyclicGroup Integer n
cg (Integer -> Mod n
forall a. Num a => Integer -> a
fromInteger Integer
g)
MultMod n
public' <- Mod n -> Maybe (MultMod n)
forall (m :: Natural). KnownNat m => Mod m -> Maybe (MultMod m)
isMultElement Mod n
public1
Integer -> Maybe Integer
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Mod n -> Integer
forall (m :: Natural). Mod m -> Integer
getVal (Mod n
public2 Mod n -> Natural -> Mod n
forall (m :: Natural) a.
(KnownNat m, Integral a) =>
Mod m -> a -> Mod m
^% CyclicGroup Integer n -> PrimitiveRoot n -> MultMod n -> Natural
forall (m :: Natural).
CyclicGroup Integer m -> PrimitiveRoot m -> MultMod m -> Natural
discreteLogarithm CyclicGroup Integer n
cg PrimitiveRoot n
subject MultMod n
public'))
toMod :: KnownNat m => proxy m -> Integer -> Mod m
toMod :: forall (m :: Natural) (proxy :: Natural -> *).
KnownNat m =>
proxy m -> Integer -> Mod m
toMod proxy m
_ = Integer -> Mod m
forall a. Num a => Integer -> a
fromInteger