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 \( \def\C{\mathbb{C}} \)
Safe HaskellNone
LanguageHaskell2010

Crypto.Lol.Utils.ShowType

Description

Class for pretty-printing type parameters to tests and benchmarks

Synopsis

Documentation

data ArgType (a :: k) Source #

Wrapper type for printing test/benchmark names.

Instances
Show (ArgType (InternalList xs)) => Show (ArgType xs) Source # 
Instance details

Defined in Crypto.Lol.Utils.ShowType

Methods

showsPrec :: Int -> ArgType xs -> ShowS #

show :: ArgType xs -> String #

showList :: [ArgType xs] -> ShowS #

Show (ArgType Double) Source # 
Instance details

Defined in Crypto.Lol.Utils.ShowType

Show (ArgType Int64) Source # 
Instance details

Defined in Crypto.Lol.Utils.ShowType

(Show (ArgType a), Show (ArgType b)) => Show (ArgType (a, b)) Source # 
Instance details

Defined in Crypto.Lol.Utils.ShowType

Methods

showsPrec :: Int -> ArgType (a, b) -> ShowS #

show :: ArgType (a, b) -> String #

showList :: [ArgType (a, b)] -> ShowS #

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

Defined in Crypto.Lol.Utils.ShowType

Reflects b Integer => Show (ArgType (BaseBGad b)) Source # 
Instance details

Defined in Crypto.Lol.Utils.ShowType

Show (ArgType TrivGad) Source # 
Instance details

Defined in Crypto.Lol.Utils.ShowType

(Mod (ZqBasic q z), Show z) => Show (ArgType (ZqBasic q z)) Source # 
Instance details

Defined in Crypto.Lol.Utils.ShowType

Methods

showsPrec :: Int -> ArgType (ZqBasic q z) -> ShowS #

show :: ArgType (ZqBasic q z) -> String #

showList :: [ArgType (ZqBasic q z)] -> ShowS #

KnownNat n => Show (ArgType n) Source # 
Instance details

Defined in Crypto.Lol.Utils.ShowType

Methods

showsPrec :: Int -> ArgType n -> ShowS #

show :: ArgType n -> String #

showList :: [ArgType n] -> ShowS #

(Show (ArgType a), Show (ArgType b)) => Show (ArgType ((,) a b)) Source # 
Instance details

Defined in Crypto.Lol.Utils.ShowType

Methods

showsPrec :: Int -> ArgType (a, b) -> ShowS #

show :: ArgType (a, b) -> String #

showList :: [ArgType (a, b)] -> ShowS #

(Show (ArgType a), Show (ArgType ((,) b c))) => Show (ArgType ((,,) a b c)) Source # 
Instance details

Defined in Crypto.Lol.Utils.ShowType

Methods

showsPrec :: Int -> ArgType (a, b, c) -> ShowS #

show :: ArgType (a, b, c) -> String #

showList :: [ArgType (a, b, c)] -> ShowS #

(Show (ArgType a), Show (ArgType ((,,) b c d))) => Show (ArgType ((,,,) a b c d)) Source # 
Instance details

Defined in Crypto.Lol.Utils.ShowType

Methods

showsPrec :: Int -> ArgType (a, b, c, d) -> ShowS #

show :: ArgType (a, b, c, d) -> String #

showList :: [ArgType (a, b, c, d)] -> ShowS #

(Show (ArgType a), Show (ArgType ((,,,) b c d e))) => Show (ArgType ((,,,,) a b c d e)) Source # 
Instance details

Defined in Crypto.Lol.Utils.ShowType

Methods

showsPrec :: Int -> ArgType (a, b, c, d, e) -> ShowS #

show :: ArgType (a, b, c, d, e) -> String #

showList :: [ArgType (a, b, c, d, e)] -> ShowS #

(Show (ArgType a), Show (ArgType ((,,,,) b c d e f))) => Show (ArgType ((,,,,,) a b c d e f)) Source # 
Instance details

Defined in Crypto.Lol.Utils.ShowType

Methods

showsPrec :: Int -> ArgType (a, b, c, d, e, f) -> ShowS #

show :: ArgType (a, b, c, d, e, f) -> String #

showList :: [ArgType (a, b, c, d, e, f)] -> ShowS #

(Show (ArgType a), Show (ArgType ((,,,,,) b c d e f g))) => Show (ArgType ((,,,,,,) a b c d e f g)) Source # 
Instance details

Defined in Crypto.Lol.Utils.ShowType

Methods

showsPrec :: Int -> ArgType (a, b, c, d, e, f, g) -> ShowS #

show :: ArgType (a, b, c, d, e, f, g) -> String #

showList :: [ArgType (a, b, c, d, e, f, g)] -> ShowS #

(Show (ArgType a), Show (ArgType ((,,,,,,) b c d e f g h))) => Show (ArgType ((,,,,,,,) a b c d e f g h)) Source # 
Instance details

Defined in Crypto.Lol.Utils.ShowType

Methods

showsPrec :: Int -> ArgType (a, b, c, d, e, f, g, h) -> ShowS #

show :: ArgType (a, b, c, d, e, f, g, h) -> String #

showList :: [ArgType (a, b, c, d, e, f, g, h)] -> ShowS #

Fact m => Show (ArgType m) Source # 
Instance details

Defined in Crypto.Lol.Utils.ShowType

Methods

showsPrec :: Int -> ArgType m -> ShowS #

show :: ArgType m -> String #

showList :: [ArgType m] -> ShowS #

showType :: forall a. Show (ArgType a) => Proxy a -> String Source #

Print a showable type argument.

type ShowType a = Show (ArgType a) Source #

Constraint synonym for printing test parameters.

type family Zq (a :: k) :: * where ... Source #

Converts ** syntax into nested pair representation.

Equations

Zq (a ** b) = (Zq a, Zq b) 
Zq q = ZqBasic q Int64 

data a ** b infixr 9 Source #

Convenient syntax for multiplication of moduli in a Zq.