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

Safe HaskellNone
LanguageHaskell2010

Voting.Protocol.Version

Contents

Synopsis

Type Version

data Version Source #

Version of the Helios-C protocol.

Constructors

Version 
Instances
Eq Version Source # 
Instance details

Defined in Voting.Protocol.Version

Methods

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

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

Ord Version Source # 
Instance details

Defined in Voting.Protocol.Version

Show Version Source # 
Instance details

Defined in Voting.Protocol.Version

IsString Version Source # 
Instance details

Defined in Voting.Protocol.Version

Methods

fromString :: String -> Version #

Generic Version Source # 
Instance details

Defined in Voting.Protocol.Version

Associated Types

type Rep Version :: Type -> Type #

Methods

from :: Version -> Rep Version x #

to :: Rep Version x -> Version #

ToJSON Version Source # 
Instance details

Defined in Voting.Protocol.Version

FromJSON Version Source # 
Instance details

Defined in Voting.Protocol.Version

NFData Version Source # 
Instance details

Defined in Voting.Protocol.Version

Methods

rnf :: Version -> () #

(VersionBranchVal branch, VersionTagsVal tags) => Reifies (V branch tags :: Type) Version Source #

Like a normal reflect but this one takes its Version from a type-level Version instead of a term-level Version.

Instance details

Defined in Voting.Protocol.Version

Methods

reflect :: proxy (V branch tags) -> Version #

type Rep Version Source # 
Instance details

Defined in Voting.Protocol.Version

type Rep Version = D1 (MetaData "Version" "Voting.Protocol.Version" "hjugement-protocol-0.0.10.20191104-EAw7qkvTkg3AkEmPDQjrRv" False) (C1 (MetaCons "Version" PrefixI True) (S1 (MetaSel (Just "version_branch") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Natural]) :*: S1 (MetaSel (Just "version_tags") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [(Text, Natural)])))

Type ExperimentalVersion

Type StableVersion

type StableVersion = V [1, 6] '[] Source #

Type VersionTagQuicker

type VersionTagQuicker = "quicker" Source #

Type V

data V (branch :: [Nat]) (tags :: [(Symbol, Nat)]) Source #

Type-level representation of a specific Version.

Instances
(VersionBranchVal branch, VersionTagsVal tags) => Reifies (V branch tags :: Type) Version Source #

Like a normal reflect but this one takes its Version from a type-level Version instead of a term-level Version.

Instance details

Defined in Voting.Protocol.Version

Methods

reflect :: proxy (V branch tags) -> Version #

Class VersionBranchVal

class VersionBranchVal a where Source #

Methods

versionBranchVal :: proxy a -> [Natural] Source #

Instances
(KnownNat h, KnownNat hh, VersionBranchVal (hh ': t)) => VersionBranchVal (h ': (hh ': t) :: [Nat]) Source # 
Instance details

Defined in Voting.Protocol.Version

Methods

versionBranchVal :: proxy (h ': (hh ': t)) -> [Natural] Source #

KnownNat h => VersionBranchVal (h ': ([] :: [Nat]) :: [Nat]) Source # 
Instance details

Defined in Voting.Protocol.Version

Methods

versionBranchVal :: proxy (h ': []) -> [Natural] Source #

Class VersionTagsVal

class VersionTagsVal a where Source #

Methods

versionTagsVal :: proxy a -> [(Text, Natural)] Source #

Instances
VersionTagsVal ([] :: [k]) Source # 
Instance details

Defined in Voting.Protocol.Version

Methods

versionTagsVal :: proxy [] -> [(Text, Natural)] Source #

(KnownSymbol s, KnownNat n, VersionTagsVal t) => VersionTagsVal ((,) s n ': t :: [(Symbol, Nat)]) Source # 
Instance details

Defined in Voting.Protocol.Version

Methods

versionTagsVal :: proxy ((s, n) ': t) -> [(Text, Natural)] Source #