hjugement-protocol-0.0.4.20190711: A cryptographic protocol for the Majority Judgment.

Safe HaskellNone
LanguageHaskell2010

Voting.Protocol.FFC

Contents

Description

Finite Field Cryptography (FFC) is a method of implementing discrete logarithm cryptography using finite field mathematics.

Synopsis

Documentation

class ToNatural a where Source #

Methods

nat :: a -> Natural Source #

Instances
ToNatural Natural Source # 
Instance details

Defined in Voting.Protocol.FFC

Methods

nat :: Natural -> Natural Source #

ToNatural (E c) Source # 
Instance details

Defined in Voting.Protocol.FFC

Methods

nat :: E c -> Natural Source #

ToNatural (G c) Source # 
Instance details

Defined in Voting.Protocol.FFC

Methods

nat :: G c -> Natural Source #

ToNatural (F c) Source # 
Instance details

Defined in Voting.Protocol.FFC

Methods

nat :: F c -> Natural Source #

class FromNatural a where Source #

Methods

fromNatural :: Natural -> a Source #

Instances
Reifies c FFC => FromNatural (E c) Source # 
Instance details

Defined in Voting.Protocol.FFC

Methods

fromNatural :: Natural -> E c Source #

Reifies c FFC => FromNatural (G c) Source # 
Instance details

Defined in Voting.Protocol.FFC

Methods

fromNatural :: Natural -> G c Source #

Reifies c FFC => FromNatural (F c) Source # 
Instance details

Defined in Voting.Protocol.FFC

Methods

fromNatural :: Natural -> F c Source #

newtype E c Source #

An exponent of a (necessarily cyclic) subgroup of a Finite Prime Field. The value is always in [0..groupOrder-1].

Constructors

E 

Fields

Instances
Reifies c FFC => Enum (E c) Source # 
Instance details

Defined in Voting.Protocol.FFC

Methods

succ :: E c -> E c #

pred :: E c -> E c #

toEnum :: Int -> E c #

fromEnum :: E c -> Int #

enumFrom :: E c -> [E c] #

enumFromThen :: E c -> E c -> [E c] #

enumFromTo :: E c -> E c -> [E c] #

enumFromThenTo :: E c -> E c -> E c -> [E c] #

Eq (E c) Source # 
Instance details

Defined in Voting.Protocol.FFC

Methods

(==) :: E c -> E c -> Bool #

(/=) :: E c -> E c -> Bool #

Ord (E c) Source # 
Instance details

Defined in Voting.Protocol.FFC

Methods

compare :: E c -> E c -> Ordering #

(<) :: E c -> E c -> Bool #

(<=) :: E c -> E c -> Bool #

(>) :: E c -> E c -> Bool #

(>=) :: E c -> E c -> Bool #

max :: E c -> E c -> E c #

min :: E c -> E c -> E c #

Show (E c) Source # 
Instance details

Defined in Voting.Protocol.FFC

Methods

showsPrec :: Int -> E c -> ShowS #

show :: E c -> String #

showList :: [E c] -> ShowS #

ToJSON (E c) Source # 
Instance details

Defined in Voting.Protocol.FFC

Methods

toJSON :: E c -> Value #

toEncoding :: E c -> Encoding #

toJSONList :: [E c] -> Value #

toEncodingList :: [E c] -> Encoding #

Reifies c FFC => FromJSON (E c) Source # 
Instance details

Defined in Voting.Protocol.FFC

Methods

parseJSON :: Value -> Parser (E c) #

parseJSONList :: Value -> Parser [E c] #

NFData (E c) Source # 
Instance details

Defined in Voting.Protocol.FFC

Methods

rnf :: E c -> () #

Reifies c FFC => Random (E c) Source # 
Instance details

Defined in Voting.Protocol.FFC

Methods

randomR :: RandomGen g => (E c, E c) -> g -> (E c, g) #

random :: RandomGen g => g -> (E c, g) #

randomRs :: RandomGen g => (E c, E c) -> g -> [E c] #

randoms :: RandomGen g => g -> [E c] #

randomRIO :: (E c, E c) -> IO (E c) #

randomIO :: IO (E c) #

ToNatural (E c) Source # 
Instance details

Defined in Voting.Protocol.FFC

Methods

nat :: E c -> Natural Source #

Reifies c FFC => FromNatural (E c) Source # 
Instance details

Defined in Voting.Protocol.FFC

Methods

fromNatural :: Natural -> E c Source #

Reifies c FFC => Multiplicative (E c) Source # 
Instance details

Defined in Voting.Protocol.FFC

Methods

one :: E c Source #

(*) :: E c -> E c -> E c Source #

Reifies c FFC => Negable (E c) Source # 
Instance details

Defined in Voting.Protocol.FFC

Methods

neg :: E c -> E c Source #

(-) :: E c -> E c -> E c Source #

Reifies c FFC => Additive (E c) Source # 
Instance details

Defined in Voting.Protocol.FFC

Methods

zero :: E c Source #

(+) :: E c -> E c -> E c Source #

sum :: Foldable f => f (E c) -> E c Source #

newtype G c Source #

The type of the elements of a Multiplicative subgroup of a Finite Prime Field.

Constructors

G 

Fields

Instances
Eq (G c) Source # 
Instance details

Defined in Voting.Protocol.FFC

Methods

(==) :: G c -> G c -> Bool #

(/=) :: G c -> G c -> Bool #

Ord (G c) Source # 
Instance details

Defined in Voting.Protocol.FFC

Methods

compare :: G c -> G c -> Ordering #

(<) :: G c -> G c -> Bool #

(<=) :: G c -> G c -> Bool #

(>) :: G c -> G c -> Bool #

(>=) :: G c -> G c -> Bool #

max :: G c -> G c -> G c #

min :: G c -> G c -> G c #

Show (G c) Source # 
Instance details

Defined in Voting.Protocol.FFC

Methods

showsPrec :: Int -> G c -> ShowS #

show :: G c -> String #

showList :: [G c] -> ShowS #

ToJSON (G c) Source # 
Instance details

Defined in Voting.Protocol.FFC

Methods

toJSON :: G c -> Value #

toEncoding :: G c -> Encoding #

toJSONList :: [G c] -> Value #

toEncodingList :: [G c] -> Encoding #

Reifies c FFC => FromJSON (G c) Source # 
Instance details

Defined in Voting.Protocol.FFC

Methods

parseJSON :: Value -> Parser (G c) #

parseJSONList :: Value -> Parser [G c] #

NFData (G c) Source # 
Instance details

Defined in Voting.Protocol.FFC

Methods

rnf :: G c -> () #

ToNatural (G c) Source # 
Instance details

Defined in Voting.Protocol.FFC

Methods

nat :: G c -> Natural Source #

Reifies c FFC => FromNatural (G c) Source # 
Instance details

Defined in Voting.Protocol.FFC

Methods

fromNatural :: Natural -> G c Source #

Reifies c FFC => Invertible (G c) Source # 
Instance details

Defined in Voting.Protocol.FFC

Methods

inv :: G c -> G c Source #

(/) :: G c -> G c -> G c Source #

Reifies c FFC => Multiplicative (G c) Source # 
Instance details

Defined in Voting.Protocol.FFC

Methods

one :: G c Source #

(*) :: G c -> G c -> G c Source #

class Multiplicative a => Invertible a where Source #

Minimal complete definition

inv

Methods

inv :: a -> a Source #

(/) :: a -> a -> a infixl 7 Source #

Instances
Reifies c FFC => Invertible (G c) Source # 
Instance details

Defined in Voting.Protocol.FFC

Methods

inv :: G c -> G c Source #

(/) :: G c -> G c -> G c Source #

class Multiplicative a where Source #

Methods

one :: a Source #

(*) :: a -> a -> a infixl 7 Source #

Instances
Multiplicative Int Source # 
Instance details

Defined in Voting.Protocol.FFC

Methods

one :: Int Source #

(*) :: Int -> Int -> Int Source #

Multiplicative Integer Source # 
Instance details

Defined in Voting.Protocol.FFC

Multiplicative Natural Source # 
Instance details

Defined in Voting.Protocol.FFC

Reifies c FFC => Multiplicative (E c) Source # 
Instance details

Defined in Voting.Protocol.FFC

Methods

one :: E c Source #

(*) :: E c -> E c -> E c Source #

Reifies c FFC => Multiplicative (G c) Source # 
Instance details

Defined in Voting.Protocol.FFC

Methods

one :: G c Source #

(*) :: G c -> G c -> G c Source #

Reifies c FFC => Multiplicative (F c) Source # 
Instance details

Defined in Voting.Protocol.FFC

Methods

one :: F c Source #

(*) :: F c -> F c -> F c Source #

class Additive a => Negable a where Source #

Minimal complete definition

neg

Methods

neg :: a -> a Source #

(-) :: a -> a -> a infixl 6 Source #

Instances
Negable Int Source # 
Instance details

Defined in Voting.Protocol.FFC

Methods

neg :: Int -> Int Source #

(-) :: Int -> Int -> Int Source #

Negable Integer Source # 
Instance details

Defined in Voting.Protocol.FFC

Reifies c FFC => Negable (E c) Source # 
Instance details

Defined in Voting.Protocol.FFC

Methods

neg :: E c -> E c Source #

(-) :: E c -> E c -> E c Source #

Reifies c FFC => Negable (F c) Source # 
Instance details

Defined in Voting.Protocol.FFC

Methods

neg :: F c -> F c Source #

(-) :: F c -> F c -> F c Source #

class Additive a where Source #

Minimal complete definition

zero, (+)

Methods

zero :: a Source #

(+) :: a -> a -> a infixl 6 Source #

sum :: Foldable f => f a -> a Source #

Instances
Additive Int Source # 
Instance details

Defined in Voting.Protocol.FFC

Methods

zero :: Int Source #

(+) :: Int -> Int -> Int Source #

sum :: Foldable f => f Int -> Int Source #

Additive Integer Source # 
Instance details

Defined in Voting.Protocol.FFC

Additive Natural Source # 
Instance details

Defined in Voting.Protocol.FFC

Reifies c FFC => Additive (E c) Source # 
Instance details

Defined in Voting.Protocol.FFC

Methods

zero :: E c Source #

(+) :: E c -> E c -> E c Source #

sum :: Foldable f => f (E c) -> E c Source #

Reifies c FFC => Additive (F c) Source # 
Instance details

Defined in Voting.Protocol.FFC

Methods

zero :: F c Source #

(+) :: F c -> F c -> F c Source #

sum :: Foldable f => f (F c) -> F c Source #

Reifies c FFC => Additive (Encryption c) Source #

Additive homomorphism. Using the fact that: groupGen ^x * groupGen ^y == groupGen ^(x+y).

Instance details

Defined in Voting.Protocol.Election

newtype F c Source #

The type of the elements of a Finite Prime Field.

A field must satisfy the following properties:

  • (f, (+), zero) forms an abelian group, called the Additive group of f.
  • (NonNull f, (*), one) forms an abelian group, called the Multiplicative group of f.
  • (*) is associative: (a*b)*c == a*(b*c) and a*(b*c) == (a*b)*c.
  • (*) and (+) are both commutative: a*b == b*a and a+b == b+a
  • (*) and (+) are both left and right distributive: a*(b+c) == (a*b) + (a*c) and (a+b)*c == (a*c) + (b*c)

The Natural is always within [0..fieldCharac-1].

Constructors

F 

Fields

Instances
Eq (F c) Source # 
Instance details

Defined in Voting.Protocol.FFC

Methods

(==) :: F c -> F c -> Bool #

(/=) :: F c -> F c -> Bool #

Ord (F c) Source # 
Instance details

Defined in Voting.Protocol.FFC

Methods

compare :: F c -> F c -> Ordering #

(<) :: F c -> F c -> Bool #

(<=) :: F c -> F c -> Bool #

(>) :: F c -> F c -> Bool #

(>=) :: F c -> F c -> Bool #

max :: F c -> F c -> F c #

min :: F c -> F c -> F c #

Show (F c) Source # 
Instance details

Defined in Voting.Protocol.FFC

Methods

showsPrec :: Int -> F c -> ShowS #

show :: F c -> String #

showList :: [F c] -> ShowS #

ToJSON (F c) Source # 
Instance details

Defined in Voting.Protocol.FFC

Methods

toJSON :: F c -> Value #

toEncoding :: F c -> Encoding #

toJSONList :: [F c] -> Value #

toEncodingList :: [F c] -> Encoding #

Reifies c FFC => FromJSON (F c) Source # 
Instance details

Defined in Voting.Protocol.FFC

Methods

parseJSON :: Value -> Parser (F c) #

parseJSONList :: Value -> Parser [F c] #

NFData (F c) Source # 
Instance details

Defined in Voting.Protocol.FFC

Methods

rnf :: F c -> () #

Reifies c FFC => Random (F c) Source # 
Instance details

Defined in Voting.Protocol.FFC

Methods

randomR :: RandomGen g => (F c, F c) -> g -> (F c, g) #

random :: RandomGen g => g -> (F c, g) #

randomRs :: RandomGen g => (F c, F c) -> g -> [F c] #

randoms :: RandomGen g => g -> [F c] #

randomRIO :: (F c, F c) -> IO (F c) #

randomIO :: IO (F c) #

ToNatural (F c) Source # 
Instance details

Defined in Voting.Protocol.FFC

Methods

nat :: F c -> Natural Source #

Reifies c FFC => FromNatural (F c) Source # 
Instance details

Defined in Voting.Protocol.FFC

Methods

fromNatural :: Natural -> F c Source #

Reifies c FFC => Multiplicative (F c) Source # 
Instance details

Defined in Voting.Protocol.FFC

Methods

one :: F c Source #

(*) :: F c -> F c -> F c Source #

Reifies c FFC => Negable (F c) Source # 
Instance details

Defined in Voting.Protocol.FFC

Methods

neg :: F c -> F c Source #

(-) :: F c -> F c -> F c Source #

Reifies c FFC => Additive (F c) Source # 
Instance details

Defined in Voting.Protocol.FFC

Methods

zero :: F c Source #

(+) :: F c -> F c -> F c Source #

sum :: Foldable f => f (F c) -> F c Source #

data FFC Source #

Mutiplicative Sub-Group of a Finite Prime Field.

NOTE: an FFC term-value is brought into the context of many functions through a type-variable c whose Reifies constraint enables to reflect that FFC at the term-level (a surprising technique but a very useful one). Doing like this is simpler than working in a Monad (like a Reader), and enables that FFC term to be used simply in instances' methods not supporting an inner Monad, like parseJSON, randomR, fromEnum or arbitrary. Aside from that, the sharing of FFC amongst several types is encoded at the type-level by including c as a phantom type of F, G and E.

Constructors

FFC 

Fields

Instances
Eq FFC Source # 
Instance details

Defined in Voting.Protocol.FFC

Methods

(==) :: FFC -> FFC -> Bool #

(/=) :: FFC -> FFC -> Bool #

Show FFC Source # 
Instance details

Defined in Voting.Protocol.FFC

Methods

showsPrec :: Int -> FFC -> ShowS #

show :: FFC -> String #

showList :: [FFC] -> ShowS #

Generic FFC Source # 
Instance details

Defined in Voting.Protocol.FFC

Associated Types

type Rep FFC :: Type -> Type #

Methods

from :: FFC -> Rep FFC x #

to :: Rep FFC x -> FFC #

ToJSON FFC Source # 
Instance details

Defined in Voting.Protocol.FFC

FromJSON FFC Source # 
Instance details

Defined in Voting.Protocol.FFC

NFData FFC Source # 
Instance details

Defined in Voting.Protocol.FFC

Methods

rnf :: FFC -> () #

type Rep FFC Source # 
Instance details

Defined in Voting.Protocol.FFC

type Rep FFC = D1 (MetaData "FFC" "Voting.Protocol.FFC" "hjugement-protocol-0.0.4.20190711-9XKUqaKqeIWGSUJTM0D5D" False) (C1 (MetaCons "FFC" PrefixI True) ((S1 (MetaSel (Just "ffc_name") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Text) :*: S1 (MetaSel (Just "ffc_fieldCharac") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Natural)) :*: (S1 (MetaSel (Just "ffc_groupGen") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Natural) :*: S1 (MetaSel (Just "ffc_groupOrder") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Natural))))

groupGen :: forall c. Reifies c FFC => G c Source #

groupOrder :: forall c. Reifies c FFC => Natural Source #

weakFFC :: FFC Source #

Weak parameters for debugging purposes only.

beleniosFFC :: FFC Source #

Parameters used in Belenios. A 2048-bit fieldCharac of a Finite Prime Field, with a 256-bit groupOrder for a Multiplicative subgroup generated by groupGen.

groupGenInverses :: forall c. Reifies c FFC => [G c] Source #

groupGenInverses returns the infinite list of inverse powers of groupGen: [groupGen ^ neg i | i <- [0..]], but by computing each value from the previous one.

Used by intervalDisjunctions.

groupGenPowers :: forall c. Reifies c FFC => [G c] Source #

hash :: Reifies c FFC => ByteString -> [G c] -> E c Source #

(hash bs gs) returns as a number in E the SHA256 hash of the given ByteString bs prefixing the decimal representation of given subgroup elements gs, with a comma (",") intercalated between them.

NOTE: to avoid any collision when the hash function is used in different contexts, a message gs is actually prefixed by a bs indicating the context.

Used by proveEncryption and verifyEncryption, where the bs usually contains the statement to be proven, and the gs contains the commitments.

hexHash :: ByteString -> Text Source #

(hexHash bs) returns the SHA256 hash of the given ByteString bs, escaped in hexadecimal into a Text of 32 lowercase characters.

Used (in retro-dependencies of this library) to hash the PublicKey of a voter or a trustee.

decodeBigEndian :: ByteString -> Natural Source #

(decodeBigEndian bs) interpret bs as big-endian number.

(^) :: Reifies c FFC => G c -> E c -> G c infixr 8 Source #

(b ^ e) returns the modular exponentiation of base b by exponent e.

randomR :: Monad m => RandomGen r => Random i => Negable i => Multiplicative i => i -> StateT r m i Source #

(randomR i) returns a random integer in [0..i-1].

random :: Monad m => RandomGen r => Random i => Negable i => Multiplicative i => StateT r m i Source #

(random) returns a random integer in the range determined by its type.

bytesNat :: ToNatural n => n -> ByteString Source #

(bytesNat x) returns the serialization of x.

data Natural #

Type representing arbitrary-precision non-negative integers.

>>> 2^100 :: Natural
1267650600228229401496703205376

Operations whose result would be negative throw (Underflow :: ArithException),

>>> -1 :: Natural
*** Exception: arithmetic underflow

Since: base-4.8.0.0

Instances
Enum Natural

Since: base-4.8.0.0

Instance details

Defined in GHC.Enum

Eq Natural

Since: base-4.8.0.0

Instance details

Defined in GHC.Natural

Methods

(==) :: Natural -> Natural -> Bool #

(/=) :: Natural -> Natural -> Bool #

Integral Natural

Since: base-4.8.0.0

Instance details

Defined in GHC.Real

Num Natural

Note that Natural's Num instance isn't a ring: no element but 0 has an additive inverse. It is a semiring though.

Since: base-4.8.0.0

Instance details

Defined in GHC.Num

Ord Natural

Since: base-4.8.0.0

Instance details

Defined in GHC.Natural

Read Natural

Since: base-4.8.0.0

Instance details

Defined in GHC.Read

Real Natural

Since: base-4.8.0.0

Instance details

Defined in GHC.Real

Show Natural

Since: base-4.8.0.0

Instance details

Defined in GHC.Show

Lift Natural 
Instance details

Defined in Language.Haskell.TH.Syntax

Methods

lift :: Natural -> Q Exp #

Hashable Natural 
Instance details

Defined in Data.Hashable.Class

Methods

hashWithSalt :: Int -> Natural -> Int #

hash :: Natural -> Int #

ToJSON Natural 
Instance details

Defined in Data.Aeson.Types.ToJSON

ToJSONKey Natural 
Instance details

Defined in Data.Aeson.Types.ToJSON

FromJSON Natural 
Instance details

Defined in Data.Aeson.Types.FromJSON

FromJSONKey Natural 
Instance details

Defined in Data.Aeson.Types.FromJSON

Bits Natural

Since: base-4.8.0

Instance details

Defined in Data.Bits

Subtractive Natural 
Instance details

Defined in Basement.Numerical.Subtractive

Associated Types

type Difference Natural :: Type #

NFData Natural

Since: deepseq-1.4.0.0

Instance details

Defined in Control.DeepSeq

Methods

rnf :: Natural -> () #

Random Natural Source # 
Instance details

Defined in Voting.Protocol.FFC

Methods

randomR :: RandomGen g => (Natural, Natural) -> g -> (Natural, g) #

random :: RandomGen g => g -> (Natural, g) #

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

randoms :: RandomGen g => g -> [Natural] #

randomRIO :: (Natural, Natural) -> IO Natural #

randomIO :: IO Natural #

ToNatural Natural Source # 
Instance details

Defined in Voting.Protocol.FFC

Methods

nat :: Natural -> Natural Source #

Multiplicative Natural Source # 
Instance details

Defined in Voting.Protocol.FFC

Additive Natural Source # 
Instance details

Defined in Voting.Protocol.FFC

type Difference Natural 
Instance details

Defined in Basement.Numerical.Subtractive

class RandomGen g #

The class RandomGen provides a common interface to random number generators.

Minimal complete definition

next, split

Instances
RandomGen StdGen 
Instance details

Defined in System.Random

Methods

next :: StdGen -> (Int, StdGen) #

genRange :: StdGen -> (Int, Int) #

split :: StdGen -> (StdGen, StdGen) #

class Reifies (s :: k) a | s -> a where #

Methods

reflect :: proxy s -> a #

Recover a value inside a reify context, given a proxy for its reified type.

Instances
KnownNat n => Reifies (n :: Nat) Integer 
Instance details

Defined in Data.Reflection

Methods

reflect :: proxy n -> Integer #

KnownSymbol n => Reifies (n :: Symbol) String 
Instance details

Defined in Data.Reflection

Methods

reflect :: proxy n -> String #

Reifies Z Int 
Instance details

Defined in Data.Reflection

Methods

reflect :: proxy Z -> Int #

Reifies n Int => Reifies (D n :: Type) Int 
Instance details

Defined in Data.Reflection

Methods

reflect :: proxy (D n) -> Int #

Reifies n Int => Reifies (SD n :: Type) Int 
Instance details

Defined in Data.Reflection

Methods

reflect :: proxy (SD n) -> Int #

Reifies n Int => Reifies (PD n :: Type) Int 
Instance details

Defined in Data.Reflection

Methods

reflect :: proxy (PD n) -> Int #

(B b0, B b1, B b2, B b3, B b4, B b5, B b6, B b7, w0 ~ W b0 b1 b2 b3, w1 ~ W b4 b5 b6 b7) => Reifies (Stable w0 w1 a :: Type) a 
Instance details

Defined in Data.Reflection

Methods

reflect :: proxy (Stable w0 w1 a) -> a #

reify :: a -> (forall s. Reifies s a => Proxy s -> r) -> r #

Reify a value at the type level, to be recovered with reflect.

data Proxy (t :: k) :: forall k. k -> Type #

Proxy is a type that holds no data, but has a phantom parameter of arbitrary type (or even kind). Its use is to provide type information, even though there is no value available of that type (or it may be too costly to create one).

Historically, Proxy :: Proxy a is a safer alternative to the 'undefined :: a' idiom.

>>> Proxy :: Proxy (Void, Int -> Int)
Proxy

Proxy can even hold types of higher kinds,

>>> Proxy :: Proxy Either
Proxy
>>> Proxy :: Proxy Functor
Proxy
>>> Proxy :: Proxy complicatedStructure
Proxy

Constructors

Proxy 
Instances
Generic1 (Proxy :: k -> Type) 
Instance details

Defined in GHC.Generics

Associated Types

type Rep1 Proxy :: k -> Type #

Methods

from1 :: Proxy a -> Rep1 Proxy a #

to1 :: Rep1 Proxy a -> Proxy a #

Monad (Proxy :: Type -> Type)

Since: base-4.7.0.0

Instance details

Defined in Data.Proxy

Methods

(>>=) :: Proxy a -> (a -> Proxy b) -> Proxy b #

(>>) :: Proxy a -> Proxy b -> Proxy b #

return :: a -> Proxy a #

fail :: String -> Proxy a #

Functor (Proxy :: Type -> Type)

Since: base-4.7.0.0

Instance details

Defined in Data.Proxy

Methods

fmap :: (a -> b) -> Proxy a -> Proxy b #

(<$) :: a -> Proxy b -> Proxy a #

Applicative (Proxy :: Type -> Type)

Since: base-4.7.0.0

Instance details

Defined in Data.Proxy

Methods

pure :: a -> Proxy a #

(<*>) :: Proxy (a -> b) -> Proxy a -> Proxy b #

liftA2 :: (a -> b -> c) -> Proxy a -> Proxy b -> Proxy c #

(*>) :: Proxy a -> Proxy b -> Proxy b #

(<*) :: Proxy a -> Proxy b -> Proxy a #

Foldable (Proxy :: Type -> Type)

Since: base-4.7.0.0

Instance details

Defined in Data.Foldable

Methods

fold :: Monoid m => Proxy m -> m #

foldMap :: Monoid m => (a -> m) -> Proxy a -> m #

foldr :: (a -> b -> b) -> b -> Proxy a -> b #

foldr' :: (a -> b -> b) -> b -> Proxy a -> b #

foldl :: (b -> a -> b) -> b -> Proxy a -> b #

foldl' :: (b -> a -> b) -> b -> Proxy a -> b #

foldr1 :: (a -> a -> a) -> Proxy a -> a #

foldl1 :: (a -> a -> a) -> Proxy a -> a #

toList :: Proxy a -> [a] #

null :: Proxy a -> Bool #

length :: Proxy a -> Int #

elem :: Eq a => a -> Proxy a -> Bool #

maximum :: Ord a => Proxy a -> a #

minimum :: Ord a => Proxy a -> a #

sum :: Num a => Proxy a -> a #

product :: Num a => Proxy a -> a #

Traversable (Proxy :: Type -> Type)

Since: base-4.7.0.0

Instance details

Defined in Data.Traversable

Methods

traverse :: Applicative f => (a -> f b) -> Proxy a -> f (Proxy b) #

sequenceA :: Applicative f => Proxy (f a) -> f (Proxy a) #

mapM :: Monad m => (a -> m b) -> Proxy a -> m (Proxy b) #

sequence :: Monad m => Proxy (m a) -> m (Proxy a) #

ToJSON1 (Proxy :: Type -> Type) 
Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

liftToJSON :: (a -> Value) -> ([a] -> Value) -> Proxy a -> Value #

liftToJSONList :: (a -> Value) -> ([a] -> Value) -> [Proxy a] -> Value #

liftToEncoding :: (a -> Encoding) -> ([a] -> Encoding) -> Proxy a -> Encoding #

liftToEncodingList :: (a -> Encoding) -> ([a] -> Encoding) -> [Proxy a] -> Encoding #

FromJSON1 (Proxy :: Type -> Type) 
Instance details

Defined in Data.Aeson.Types.FromJSON

Methods

liftParseJSON :: (Value -> Parser a) -> (Value -> Parser [a]) -> Value -> Parser (Proxy a) #

liftParseJSONList :: (Value -> Parser a) -> (Value -> Parser [a]) -> Value -> Parser [Proxy a] #

Alternative (Proxy :: Type -> Type)

Since: base-4.9.0.0

Instance details

Defined in Data.Proxy

Methods

empty :: Proxy a #

(<|>) :: Proxy a -> Proxy a -> Proxy a #

some :: Proxy a -> Proxy [a] #

many :: Proxy a -> Proxy [a] #

MonadPlus (Proxy :: Type -> Type)

Since: base-4.9.0.0

Instance details

Defined in Data.Proxy

Methods

mzero :: Proxy a #

mplus :: Proxy a -> Proxy a -> Proxy a #

NFData1 (Proxy :: Type -> Type)

Since: deepseq-1.4.3.0

Instance details

Defined in Control.DeepSeq

Methods

liftRnf :: (a -> ()) -> Proxy a -> () #

Hashable1 (Proxy :: Type -> Type) 
Instance details

Defined in Data.Hashable.Class

Methods

liftHashWithSalt :: (Int -> a -> Int) -> Int -> Proxy a -> Int #

Bounded (Proxy t)

Since: base-4.7.0.0

Instance details

Defined in Data.Proxy

Methods

minBound :: Proxy t #

maxBound :: Proxy t #

Enum (Proxy s)

Since: base-4.7.0.0

Instance details

Defined in Data.Proxy

Methods

succ :: Proxy s -> Proxy s #

pred :: Proxy s -> Proxy s #

toEnum :: Int -> Proxy s #

fromEnum :: Proxy s -> Int #

enumFrom :: Proxy s -> [Proxy s] #

enumFromThen :: Proxy s -> Proxy s -> [Proxy s] #

enumFromTo :: Proxy s -> Proxy s -> [Proxy s] #

enumFromThenTo :: Proxy s -> Proxy s -> Proxy s -> [Proxy s] #

Eq (Proxy s)

Since: base-4.7.0.0

Instance details

Defined in Data.Proxy

Methods

(==) :: Proxy s -> Proxy s -> Bool #

(/=) :: Proxy s -> Proxy s -> Bool #

Ord (Proxy s)

Since: base-4.7.0.0

Instance details

Defined in Data.Proxy

Methods

compare :: Proxy s -> Proxy s -> Ordering #

(<) :: Proxy s -> Proxy s -> Bool #

(<=) :: Proxy s -> Proxy s -> Bool #

(>) :: Proxy s -> Proxy s -> Bool #

(>=) :: Proxy s -> Proxy s -> Bool #

max :: Proxy s -> Proxy s -> Proxy s #

min :: Proxy s -> Proxy s -> Proxy s #

Read (Proxy t)

Since: base-4.7.0.0

Instance details

Defined in Data.Proxy

Show (Proxy s)

Since: base-4.7.0.0

Instance details

Defined in Data.Proxy

Methods

showsPrec :: Int -> Proxy s -> ShowS #

show :: Proxy s -> String #

showList :: [Proxy s] -> ShowS #

Ix (Proxy s)

Since: base-4.7.0.0

Instance details

Defined in Data.Proxy

Methods

range :: (Proxy s, Proxy s) -> [Proxy s] #

index :: (Proxy s, Proxy s) -> Proxy s -> Int #

unsafeIndex :: (Proxy s, Proxy s) -> Proxy s -> Int

inRange :: (Proxy s, Proxy s) -> Proxy s -> Bool #

rangeSize :: (Proxy s, Proxy s) -> Int #

unsafeRangeSize :: (Proxy s, Proxy s) -> Int

Generic (Proxy t) 
Instance details

Defined in GHC.Generics

Associated Types

type Rep (Proxy t) :: Type -> Type #

Methods

from :: Proxy t -> Rep (Proxy t) x #

to :: Rep (Proxy t) x -> Proxy t #

Semigroup (Proxy s)

Since: base-4.9.0.0

Instance details

Defined in Data.Proxy

Methods

(<>) :: Proxy s -> Proxy s -> Proxy s #

sconcat :: NonEmpty (Proxy s) -> Proxy s #

stimes :: Integral b => b -> Proxy s -> Proxy s #

Monoid (Proxy s)

Since: base-4.7.0.0

Instance details

Defined in Data.Proxy

Methods

mempty :: Proxy s #

mappend :: Proxy s -> Proxy s -> Proxy s #

mconcat :: [Proxy s] -> Proxy s #

Hashable (Proxy a) 
Instance details

Defined in Data.Hashable.Class

Methods

hashWithSalt :: Int -> Proxy a -> Int #

hash :: Proxy a -> Int #

ToJSON (Proxy a) 
Instance details

Defined in Data.Aeson.Types.ToJSON

FromJSON (Proxy a) 
Instance details

Defined in Data.Aeson.Types.FromJSON

NFData (Proxy a)

Since: deepseq-1.4.0.0

Instance details

Defined in Control.DeepSeq

Methods

rnf :: Proxy a -> () #

type Rep1 (Proxy :: k -> Type)

Since: base-4.6.0.0

Instance details

Defined in GHC.Generics

type Rep1 (Proxy :: k -> Type) = D1 (MetaData "Proxy" "Data.Proxy" "base" False) (C1 (MetaCons "Proxy" PrefixI False) (U1 :: k -> Type))
type Rep (Proxy t)

Since: base-4.6.0.0

Instance details

Defined in GHC.Generics

type Rep (Proxy t) = D1 (MetaData "Proxy" "Data.Proxy" "base" False) (C1 (MetaCons "Proxy" PrefixI False) (U1 :: Type -> Type))

Orphan instances

Random Natural Source # 
Instance details

Methods

randomR :: RandomGen g => (Natural, Natural) -> g -> (Natural, g) #

random :: RandomGen g => g -> (Natural, g) #

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

randoms :: RandomGen g => g -> [Natural] #

randomRIO :: (Natural, Natural) -> IO Natural #

randomIO :: IO Natural #