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 \( \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 Source #

Wrapper type for printing test/benchmark names

Instances

Show (ArgType * (InternalList [k] xs)) => Show (ArgType [k] xs) Source # 

Methods

showsPrec :: Int -> ArgType [k] xs -> ShowS #

show :: ArgType [k] xs -> String #

showList :: [ArgType [k] xs] -> ShowS #

Show (ArgType * Int64) Source # 
(Show (ArgType * a), Show (ArgType * b)) => Show (ArgType * (a, b)) Source # 

Methods

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

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

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

Reflects k b Integer => Show (ArgType * (BaseBGad k b)) Source # 

Methods

showsPrec :: Int -> ArgType * (BaseBGad k b) -> ShowS #

show :: ArgType * (BaseBGad k b) -> String #

showList :: [ArgType * (BaseBGad k b)] -> ShowS #

Show (ArgType * TrivGad) Source # 
(Mod (ZqBasic k q i), Show i) => Show (ArgType * (ZqBasic k q i)) Source # 

Methods

showsPrec :: Int -> ArgType * (ZqBasic k q i) -> ShowS #

show :: ArgType * (ZqBasic k q i) -> String #

showList :: [ArgType * (ZqBasic k q i)] -> ShowS #

KnownNat n => Show (ArgType Nat n) Source # 

Methods

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

show :: ArgType Nat n -> String #

showList :: [ArgType Nat n] -> ShowS #

(Show (ArgType k1 a), Show (ArgType k b)) => Show (ArgType (k1, k) ((,) k1 k a b)) Source # 

Methods

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

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

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

(Show (ArgType k2 a), Show (ArgType (k1, k) ((,) k1 k b c))) => Show (ArgType (k2, k1, k) ((,,) k2 k1 k a b c)) Source # 

Methods

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

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

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

(Show (ArgType k3 a), Show (ArgType (k2, k1, k) ((,,) k2 k1 k b c d))) => Show (ArgType (k3, k2, k1, k) ((,,,) k3 k2 k1 k a b c d)) Source # 

Methods

showsPrec :: Int -> ArgType (k3, k2, k1, k) ((k3, k2, k1, k) a b c d) -> ShowS #

show :: ArgType (k3, k2, k1, k) ((k3, k2, k1, k) a b c d) -> String #

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

(Show (ArgType k4 a), Show (ArgType (k3, k2, k1, k) ((,,,) k3 k2 k1 k b c d e))) => Show (ArgType (k4, k3, k2, k1, k) ((,,,,) k4 k3 k2 k1 k a b c d e)) Source # 

Methods

showsPrec :: Int -> ArgType (k4, k3, k2, k1, k) ((k4, k3, k2, k1, k) a b c d e) -> ShowS #

show :: ArgType (k4, k3, k2, k1, k) ((k4, k3, k2, k1, k) a b c d e) -> String #

showList :: [ArgType (k4, k3, k2, k1, k) ((k4, k3, k2, k1, k) a b c d e)] -> ShowS #

(Show (ArgType k5 a), Show (ArgType (k4, k3, k2, k1, k) ((,,,,) k4 k3 k2 k1 k b c d e f))) => Show (ArgType (k5, k4, k3, k2, k1, k) ((,,,,,) k5 k4 k3 k2 k1 k a b c d e f)) Source # 

Methods

showsPrec :: Int -> ArgType (k5, k4, k3, k2, k1, k) ((k5, k4, k3, k2, k1, k) a b c d e f) -> ShowS #

show :: ArgType (k5, k4, k3, k2, k1, k) ((k5, k4, k3, k2, k1, k) a b c d e f) -> String #

showList :: [ArgType (k5, k4, k3, k2, k1, k) ((k5, k4, k3, k2, k1, k) a b c d e f)] -> ShowS #

(Show (ArgType k6 a), Show (ArgType (k5, k4, k3, k2, k1, k) ((,,,,,) k5 k4 k3 k2 k1 k b c d e f g))) => Show (ArgType (k6, k5, k4, k3, k2, k1, k) ((,,,,,,) k6 k5 k4 k3 k2 k1 k a b c d e f g)) Source # 

Methods

showsPrec :: Int -> ArgType (k6, k5, k4, k3, k2, k1, k) ((k6, k5, k4, k3, k2, k1, k) a b c d e f g) -> ShowS #

show :: ArgType (k6, k5, k4, k3, k2, k1, k) ((k6, k5, k4, k3, k2, k1, k) a b c d e f g) -> String #

showList :: [ArgType (k6, k5, k4, k3, k2, k1, k) ((k6, k5, k4, k3, k2, k1, k) a b c d e f g)] -> ShowS #

(Show (ArgType k7 a), Show (ArgType (k6, k5, k4, k3, k2, k1, k) ((,,,,,,) k6 k5 k4 k3 k2 k1 k b c d e f g h))) => Show (ArgType (k7, k6, k5, k4, k3, k2, k1, k) ((,,,,,,,) k7 k6 k5 k4 k3 k2 k1 k a b c d e f g h)) Source # 

Methods

showsPrec :: Int -> ArgType (k7, k6, k5, k4, k3, k2, k1, k) ((k7, k6, k5, k4, k3, k2, k1, k) a b c d e f g h) -> ShowS #

show :: ArgType (k7, k6, k5, k4, k3, k2, k1, k) ((k7, k6, k5, k4, k3, k2, k1, k) a b c d e f g h) -> String #

showList :: [ArgType (k7, k6, k5, k4, k3, k2, k1, k) ((k7, k6, k5, k4, k3, k2, k1, k) a b c d e f g h)] -> ShowS #

Fact m => Show (ArgType Factored m) Source # 

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