lol-0.7.0.0: A library for lattice cryptography.

Copyright(c) Eric Crockett 2011-2017
Chris Peikert 2011-2017
LicenseGPL-3
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
Transcendental a => CRTrans Maybe (Complex a) Source #

For testing ergonomics, we also have a Maybe instance of CRTrans for complex numbers.

Instance details

Defined in Crypto.Lol.CRTrans

Transcendental a => CRTrans Identity (Complex a) Source #

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

Instance details

Defined in Crypto.Lol.CRTrans

Eq a => Eq (Complex a) Source # 
Instance details

Defined in Crypto.Lol.Types.Unsafe.Complex

Methods

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

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

Show a => Show (Complex a) Source # 
Instance details

Defined in Crypto.Lol.Types.Unsafe.Complex

Methods

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

show :: Complex a -> String #

showList :: [Complex a] -> ShowS #

Random a => Random (Complex a) Source # 
Instance details

Defined in Crypto.Lol.Types.Unsafe.Complex

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 # 
Instance details

Defined in Crypto.Lol.Types.Unsafe.Complex

Methods

rnf :: Complex a -> () #

C a => C (Complex a) Source # 
Instance details

Defined in Crypto.Lol.Types.Unsafe.Complex

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.)

Instance details

Defined in Crypto.Lol.Types.Unsafe.Complex

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 # 
Instance details

Defined in Crypto.Lol.Types.Unsafe.Complex

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 # 
Instance details

Defined in Crypto.Lol.Types.Unsafe.Complex

Methods

isZero :: Complex a -> Bool #

C a => C (Complex a) Source # 
Instance details

Defined in Crypto.Lol.Types.Unsafe.Complex

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

Instance details

Defined in Crypto.Lol.CRTrans

Associated Types

type CRTExt (Complex a) :: Type Source #

ApproxEqual (Complex Double) Source # 
Instance details

Defined in Crypto.Lol.Utils.Tests

Show (ArgType (Complex Double)) Source # 
Instance details

Defined in Crypto.Lol.Utils.ShowType

type CRTExt (Complex a) Source # 
Instance details

Defined in Crypto.Lol.CRTrans

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.