Safe Haskell | None |
---|---|
Language | Haskell2010 |
Synopsis
- data TrustChain f a
- = Trustless a
- | TrustProxy (Signed (f (TrustChain f a)))
- validTrustChain :: (Binary a, Binary (f (TrustChain f a)), Foldable f) => TrustChain f a -> Bool
- mkTrustProxy :: (Traversable f, Binary (f (TrustChain f a))) => PrivateKey -> f (TrustChain f a) -> IO (TrustChain f a)
- mkTrustless :: a -> TrustChain f a
- newtype Whitelist = Whitelist {}
- filterByWhitelist :: Foldable f => Whitelist -> TrustChain f a -> [TrustChain f a]
- data Claim a = Claim [PublicKey] a
- claims :: Foldable f => TrustChain f a -> [Claim a]
- claimants :: (Ord k, Ord a) => (a -> k) -> [Claim a] -> Map k (Map a (Set [PublicKey]))
- assignments :: Ord k => (a -> k) -> Merge e a a -> [Claim a] -> Either (Inconsistency e a) (Map k a)
- data Inconsistency e a = IncompatibleClaim e (Claim a) [Claim a]
- data PublicKey
- data PrivateKey
- data Signed a
- data Merge e x a
Trust Chains
data TrustChain f a Source #
A tree of trust of the given shape, where each internal node of the
tree is signed by potentially different keys. TrustChain Identity a
is a linear signature chain, whereas TrustChain NonEmpty a
is a tree
shaped trust chain. We can keep track of metadata at each internal
node of any structure using TrustChain (Compose ((,) metadata) f) a
.
For those who are familiar with the free monad, you can think of this as a free monad where the internal nodes are signed by differing parties.
Trustless a | |
TrustProxy (Signed (f (TrustChain f a))) |
Instances
validTrustChain :: (Binary a, Binary (f (TrustChain f a)), Foldable f) => TrustChain f a -> Bool Source #
mkTrustProxy :: (Traversable f, Binary (f (TrustChain f a))) => PrivateKey -> f (TrustChain f a) -> IO (TrustChain f a) Source #
Extend the trust chain with new subchains and new items.
mkTrustless :: a -> TrustChain f a Source #
Make a basic, trustless trust chain.
White Lists
A set of PublicKey
s we accept information from.
filterByWhitelist :: Foldable f => Whitelist -> TrustChain f a -> [TrustChain f a] Source #
Strips out all elements of the chain which aren't rooted by someone in
our whitelist, creating a forest of TrustChain
s instead of a single one.
Claims
A path through the trust chain.
Instances
Eq a => Eq (Claim a) Source # | |
Ord a => Ord (Claim a) Source # | |
Read a => Read (Claim a) Source # | |
Show a => Show (Claim a) Source # | |
Generic (Claim a) Source # | |
Binary a => Binary (Claim a) Source # | |
type Rep (Claim a) Source # | |
Defined in Data.TrustChain type Rep (Claim a) = D1 ('MetaData "Claim" "Data.TrustChain" "trust-chain-0.1.3.0-53O0opn2jsN9Fvl2Mku0Bl" 'False) (C1 ('MetaCons "Claim" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [PublicKey]) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a))) |
claims :: Foldable f => TrustChain f a -> [Claim a] Source #
Extract all of the claims from the trust chain.
claimants :: (Ord k, Ord a) => (a -> k) -> [Claim a] -> Map k (Map a (Set [PublicKey])) Source #
Index the claimants by what they're claiming, using the given indexing function.
The mental model here should something like k = PublicKey
and a = Person
. What
we're doing is figuring out, for every different PublicKey
contained in the Trustless
node in our TrustChain
, all of the different variations and series of signatures which lead up to those variations (along with who assented to those accounts).
There is no Merge
ing here, in particular. This is the way to splay out all of the different realities and the sequences of
PublicKey
which signed that particular variation (at one time or another).
Index and Merge
assignments :: Ord k => (a -> k) -> Merge e a a -> [Claim a] -> Either (Inconsistency e a) (Map k a) Source #
Extract all of the assignments from the trust chain, unifying information contained within them. This is where we might find potential inconsistencies.
Inconsistencies
data Inconsistency e a Source #
An inconsistency with the various accounts in the trust chain
IncompatibleClaim e (Claim a) [Claim a] |
Instances
Re-Exports from Cropty
A public identity which corresponds to your secret one, allowing
you to tell other people how to encrypt
things for you. If you sign
something with the PrivateKey
associated with this public one,
someone will be able to verify it was you with your public key.
data PrivateKey #
A secret identity which one should be very careful about storing and sharing. If others get it, they will be able to read messages intended for you.
Instances
Eq PrivateKey | |
Defined in Cropty (==) :: PrivateKey -> PrivateKey -> Bool # (/=) :: PrivateKey -> PrivateKey -> Bool # | |
Ord PrivateKey | |
Defined in Cropty compare :: PrivateKey -> PrivateKey -> Ordering # (<) :: PrivateKey -> PrivateKey -> Bool # (<=) :: PrivateKey -> PrivateKey -> Bool # (>) :: PrivateKey -> PrivateKey -> Bool # (>=) :: PrivateKey -> PrivateKey -> Bool # max :: PrivateKey -> PrivateKey -> PrivateKey # min :: PrivateKey -> PrivateKey -> PrivateKey # | |
Read PrivateKey | |
Defined in Cropty readsPrec :: Int -> ReadS PrivateKey # readList :: ReadS [PrivateKey] # readPrec :: ReadPrec PrivateKey # readListPrec :: ReadPrec [PrivateKey] # | |
Show PrivateKey | |
Defined in Cropty showsPrec :: Int -> PrivateKey -> ShowS # show :: PrivateKey -> String # showList :: [PrivateKey] -> ShowS # | |
Binary PrivateKey | |
Defined in Cropty |
A convenient type in which to wrap signed things.
Instances
Eq (Signed a) | |
Ord (Signed a) | |
Read a => Read (Signed a) | |
Show a => Show (Signed a) | |
Generic (Signed a) | |
Binary a => Binary (Signed a) | |
type Rep (Signed a) | |
Defined in Cropty type Rep (Signed a) = D1 ('MetaData "Signed" "Cropty" "cropty-0.3.1.0-F6WpvUb2apZ5YjlIyofnDX" 'False) (C1 ('MetaCons "Signed" 'PrefixI 'True) ((S1 ('MetaSel ('Just "signed") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: S1 ('MetaSel ('Just "signedEncoded") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ByteString)) :*: (S1 ('MetaSel ('Just "signature") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Signature) :*: S1 ('MetaSel ('Just "signedBy") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 PublicKey)))) |
Re-Exports from Data.Merge
Describes the merging of two values of the same type
into some other type. Represented as a Maybe
valued
function, one can also think of this as a predicate
showing which pairs of values can be merged in this way.
data Example = Whatever { a :: Int, b :: Maybe Bool } mergeExamples :: Merge Example Example mergeExamples = Example <$> required a <*> optional b
Instances
Profunctor (Merge e) | |
Defined in Data.Merge dimap :: (a -> b) -> (c -> d) -> Merge e b c -> Merge e a d # lmap :: (a -> b) -> Merge e b c -> Merge e a c # rmap :: (b -> c) -> Merge e a b -> Merge e a c # (#.) :: forall a b c q. Coercible c b => q b c -> Merge e a b -> Merge e a c # (.#) :: forall a b c q. Coercible b a => Merge e b c -> q a b -> Merge e a c # | |
Functor (Merge e x) | |
Semigroup e => Applicative (Merge e x) | |
Monoid e => Alternative (Merge e x) | |
(Semigroup e, Semigroup a) => Semigroup (Merge e x a) | |
(Monoid e, Semigroup a) => Monoid (Merge e x a) | |