module Crypto.Lol.Cyclotomic.Linear
( Linear, ExtendLinIdx
, linearDec, evalLin, extendLin
) where
import Crypto.Lol.Cyclotomic.Cyc
import Crypto.Lol.LatticePrelude
import Algebra.Additive as Additive (C)
import Control.Applicative
import Control.DeepSeq
newtype Linear t z (e::Factored) (r::Factored) (s::Factored) = D [Cyc t s z]
deriving instance (NFData (Cyc t s z)) => NFData (Linear t z e r s)
type role Linear representational nominal representational representational nominal
linearDec :: forall t z e r s .
(e `Divides` r, e `Divides` s, CElt t z)
=> [Cyc t s z] -> Linear t z e r s
linearDec ys = let ps = proxy powBasis (Proxy::Proxy e) `asTypeOf` ys
in if length ys <= length ps then D (adviseCRT <$> ys)
else error $ "linearDec: too many entries: "
++ show (length ys) ++ " versus "
++ show (length ps)
evalLin :: forall t z e r s .
(e `Divides` r, e `Divides` s, CElt t z)
=> Linear t z e r s -> Cyc t r z -> Cyc t s z
evalLin (D ys) r = sum (zipWith (*) ys $
embed <$> (coeffsCyc Dec r :: [Cyc t e z]))
instance Additive (Cyc t s z) => Additive.C (Linear t z e r s) where
zero = D []
(D as) + (D bs) = D $ sumall as bs
where sumall [] ys = ys
sumall xs [] = xs
sumall (x:xs) (y:ys) = x+y : sumall xs ys
negate (D as) = D $ negate <$> as
instance (Reduce z zq, Fact s, CElt t z, CElt t zq)
=> Reduce (Linear t z e r s) (Linear t zq e r s) where
reduce (D ys) = D $ reduce <$> ys
instance (CElt t zp, CElt t z, z ~ LiftOf zp, Lift zp z, Fact s)
=> Lift' (Linear t zp e r s) where
type LiftOf (Linear t zp e r s) = Linear t (LiftOf zp) e r s
lift (D ys) = D $ liftCyc Pow <$> ys
type ExtendLinIdx e r s e' r' s' =
(Fact r, e ~ FGCD r e', r' ~ FLCM r e',
e' `Divides` s', s `Divides` s')
extendLin :: (ExtendLinIdx e r s e' r' s', CElt t z)
=> Linear t z e r s -> Linear t z e' r' s'
extendLin (D ys) = D (embed <$> ys)