lol-0.6.0.0: A library for lattice cryptography.

Copyright(c) Eric Crockett 2011-2017
Chris Peikert 2011-2017
LicenseGPL-2
Maintainerecrockett0@email.com
Stabilityexperimental
PortabilityPOSIX
Safe HaskellNone
LanguageHaskell2010

Crypto.Lol.Types.Unsafe.Complex

Description

Data type, functions, and instances for complex numbers. This module is "unsafe" because it exports the Complex constructor. This module should only be used to make tensor-specific instances for Complex. The safe way to use this type is to import Crypto.Lol.Types.

Synopsis

Documentation

newtype Complex a Source #

Newtype wrapper (with slightly different instances) for Number.Complex.

Constructors

Complex (T a) 

Instances

(Monad mon, Transcendental a) => CRTrans mon (Complex a) Source #

Complex numbers have CRTrans for any index \(m\)

Methods

crtInfo :: Reflects k1 m Int => TaggedT * k1 m mon (CRTInfo (Complex a)) Source #

Eq a => Eq (Complex a) Source # 

Methods

(==) :: Complex a -> Complex a -> Bool #

(/=) :: Complex a -> Complex a -> Bool #

Show a => Show (Complex a) Source # 

Methods

showsPrec :: Int -> Complex a -> ShowS #

show :: Complex a -> String #

showList :: [Complex a] -> ShowS #

Random a => Random (Complex a) Source # 

Methods

randomR :: RandomGen g => (Complex a, Complex a) -> g -> (Complex a, g) #

random :: RandomGen g => g -> (Complex a, g) #

randomRs :: RandomGen g => (Complex a, Complex a) -> g -> [Complex a] #

randoms :: RandomGen g => g -> [Complex a] #

randomRIO :: (Complex a, Complex a) -> IO (Complex a) #

randomIO :: IO (Complex a) #

NFData a => NFData (Complex a) Source # 

Methods

rnf :: Complex a -> () #

C a => C (Complex a) Source # 

Methods

(/) :: Complex a -> Complex a -> Complex a #

recip :: Complex a -> Complex a #

fromRational' :: Rational -> Complex a #

(^-) :: Complex a -> Integer -> Complex a #

Field a => C (Complex a) Source #

Custom instance replacing the one provided by numeric prelude: it always returns 0 as the remainder of a division. (The NP instance sometimes has precision issues, because it yields nonzero remainders, which is a problem for divG methods.)

Methods

div :: Complex a -> Complex a -> Complex a #

mod :: Complex a -> Complex a -> Complex a #

divMod :: Complex a -> Complex a -> (Complex a, Complex a) #

C a => C (Complex a) Source # 

Methods

isZero :: Complex a -> Bool #

C a => C (Complex a) Source # 

Methods

(*) :: Complex a -> Complex a -> Complex a #

one :: Complex a #

fromInteger :: Integer -> Complex a #

(^) :: Complex a -> Integer -> Complex a #

C a => C (Complex a) Source # 

Methods

zero :: Complex a #

(+) :: Complex a -> Complex a -> Complex a #

(-) :: Complex a -> Complex a -> Complex a #

negate :: Complex a -> Complex a #

Transcendental a => CRTEmbed (Complex a) Source #

Self-embed

Associated Types

type CRTExt (Complex a) :: * Source #

type CRTExt (Complex a) Source # 
type CRTExt (Complex a) = Complex a

roundComplex :: (RealRing a, ToInteger b) => Complex a -> (b, b) Source #

Rounds the real and imaginary components to the nearest integer.

cis :: Transcendental a => a -> Complex a Source #

cis \(t\) is a complex value with magnitude 1 and phase \(t \bmod 2\cdot\pi\)).

real :: Complex a -> a Source #

Real component of a complex number.

imag :: Complex a -> a Source #

Imaginary component of a complex number.

fromReal :: Additive a => a -> Complex a Source #

Embeds a scalar as the real component of a complex number.