trust-chain-0.1.3.0: An implementation of a trust chain
Safe HaskellNone
LanguageHaskell2010

Data.TrustChain

Synopsis

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.

Constructors

Trustless a 
TrustProxy (Signed (f (TrustChain f a))) 

Instances

Instances details
Eq a => Eq (TrustChain f a) Source # 
Instance details

Defined in Data.TrustChain

Methods

(==) :: TrustChain f a -> TrustChain f a -> Bool #

(/=) :: TrustChain f a -> TrustChain f a -> Bool #

Ord a => Ord (TrustChain f a) Source # 
Instance details

Defined in Data.TrustChain

Methods

compare :: TrustChain f a -> TrustChain f a -> Ordering #

(<) :: TrustChain f a -> TrustChain f a -> Bool #

(<=) :: TrustChain f a -> TrustChain f a -> Bool #

(>) :: TrustChain f a -> TrustChain f a -> Bool #

(>=) :: TrustChain f a -> TrustChain f a -> Bool #

max :: TrustChain f a -> TrustChain f a -> TrustChain f a #

min :: TrustChain f a -> TrustChain f a -> TrustChain f a #

(Read a, Read (f (TrustChain f a))) => Read (TrustChain f a) Source # 
Instance details

Defined in Data.TrustChain

(Show a, Show (f (TrustChain f a))) => Show (TrustChain f a) Source # 
Instance details

Defined in Data.TrustChain

Methods

showsPrec :: Int -> TrustChain f a -> ShowS #

show :: TrustChain f a -> String #

showList :: [TrustChain f a] -> ShowS #

Generic (TrustChain f a) Source # 
Instance details

Defined in Data.TrustChain

Associated Types

type Rep (TrustChain f a) :: Type -> Type #

Methods

from :: TrustChain f a -> Rep (TrustChain f a) x #

to :: Rep (TrustChain f a) x -> TrustChain f a #

(Binary a, Binary (f (TrustChain f a))) => Binary (TrustChain f a) Source # 
Instance details

Defined in Data.TrustChain

Methods

put :: TrustChain f a -> Put #

get :: Get (TrustChain f a) #

putList :: [TrustChain f a] -> Put #

type Rep (TrustChain f a) Source # 
Instance details

Defined in Data.TrustChain

type Rep (TrustChain f a) = D1 ('MetaData "TrustChain" "Data.TrustChain" "trust-chain-0.1.3.0-53O0opn2jsN9Fvl2Mku0Bl" 'False) (C1 ('MetaCons "Trustless" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a)) :+: C1 ('MetaCons "TrustProxy" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Signed (f (TrustChain f a))))))

validTrustChain :: (Binary a, Binary (f (TrustChain f a)), Foldable f) => TrustChain f a -> Bool Source #

Check that the trust chain has been legitimately signed. Once you receive True from this function, you can be certain that all of the Signed types within are truly correct.

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

newtype Whitelist Source #

A set of PublicKeys we accept information from.

Constructors

Whitelist 

Instances

Instances details
Eq Whitelist Source # 
Instance details

Defined in Data.TrustChain

Ord Whitelist Source # 
Instance details

Defined in Data.TrustChain

Read Whitelist Source # 
Instance details

Defined in Data.TrustChain

Show Whitelist Source # 
Instance details

Defined in Data.TrustChain

Generic Whitelist Source # 
Instance details

Defined in Data.TrustChain

Associated Types

type Rep Whitelist :: Type -> Type #

Binary Whitelist Source # 
Instance details

Defined in Data.TrustChain

type Rep Whitelist Source # 
Instance details

Defined in Data.TrustChain

type Rep Whitelist = D1 ('MetaData "Whitelist" "Data.TrustChain" "trust-chain-0.1.3.0-53O0opn2jsN9Fvl2Mku0Bl" 'True) (C1 ('MetaCons "Whitelist" 'PrefixI 'True) (S1 ('MetaSel ('Just "unWhitelist") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Set PublicKey))))

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 TrustChains instead of a single one.

Claims

data Claim a Source #

A path through the trust chain.

Constructors

Claim [PublicKey] a 

Instances

Instances details
Eq a => Eq (Claim a) Source # 
Instance details

Defined in Data.TrustChain

Methods

(==) :: Claim a -> Claim a -> Bool #

(/=) :: Claim a -> Claim a -> Bool #

Ord a => Ord (Claim a) Source # 
Instance details

Defined in Data.TrustChain

Methods

compare :: Claim a -> Claim a -> Ordering #

(<) :: Claim a -> Claim a -> Bool #

(<=) :: Claim a -> Claim a -> Bool #

(>) :: Claim a -> Claim a -> Bool #

(>=) :: Claim a -> Claim a -> Bool #

max :: Claim a -> Claim a -> Claim a #

min :: Claim a -> Claim a -> Claim a #

Read a => Read (Claim a) Source # 
Instance details

Defined in Data.TrustChain

Show a => Show (Claim a) Source # 
Instance details

Defined in Data.TrustChain

Methods

showsPrec :: Int -> Claim a -> ShowS #

show :: Claim a -> String #

showList :: [Claim a] -> ShowS #

Generic (Claim a) Source # 
Instance details

Defined in Data.TrustChain

Associated Types

type Rep (Claim a) :: Type -> Type #

Methods

from :: Claim a -> Rep (Claim a) x #

to :: Rep (Claim a) x -> Claim a #

Binary a => Binary (Claim a) Source # 
Instance details

Defined in Data.TrustChain

Methods

put :: Claim a -> Put #

get :: Get (Claim a) #

putList :: [Claim a] -> Put #

type Rep (Claim a) Source # 
Instance details

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 Mergeing 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

Constructors

IncompatibleClaim e (Claim a) [Claim a] 

Instances

Instances details
(Eq e, Eq a) => Eq (Inconsistency e a) Source # 
Instance details

Defined in Data.TrustChain

Methods

(==) :: Inconsistency e a -> Inconsistency e a -> Bool #

(/=) :: Inconsistency e a -> Inconsistency e a -> Bool #

(Ord e, Ord a) => Ord (Inconsistency e a) Source # 
Instance details

Defined in Data.TrustChain

(Read e, Read a) => Read (Inconsistency e a) Source # 
Instance details

Defined in Data.TrustChain

(Show e, Show a) => Show (Inconsistency e a) Source # 
Instance details

Defined in Data.TrustChain

Generic (Inconsistency e a) Source # 
Instance details

Defined in Data.TrustChain

Associated Types

type Rep (Inconsistency e a) :: Type -> Type #

Methods

from :: Inconsistency e a -> Rep (Inconsistency e a) x #

to :: Rep (Inconsistency e a) x -> Inconsistency e a #

(Binary e, Binary a) => Binary (Inconsistency e a) Source # 
Instance details

Defined in Data.TrustChain

Methods

put :: Inconsistency e a -> Put #

get :: Get (Inconsistency e a) #

putList :: [Inconsistency e a] -> Put #

type Rep (Inconsistency e a) Source # 
Instance details

Defined in Data.TrustChain

type Rep (Inconsistency e a) = D1 ('MetaData "Inconsistency" "Data.TrustChain" "trust-chain-0.1.3.0-53O0opn2jsN9Fvl2Mku0Bl" 'False) (C1 ('MetaCons "IncompatibleClaim" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 e) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Claim a)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Claim a]))))

Re-Exports from Cropty

data PublicKey #

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.

Instances

Instances details
Eq PublicKey 
Instance details

Defined in Cropty

Ord PublicKey 
Instance details

Defined in Cropty

Read PublicKey 
Instance details

Defined in Cropty

Show PublicKey 
Instance details

Defined in Cropty

Binary PublicKey 
Instance details

Defined in Cropty

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

Instances details
Eq PrivateKey 
Instance details

Defined in Cropty

Ord PrivateKey 
Instance details

Defined in Cropty

Read PrivateKey 
Instance details

Defined in Cropty

Show PrivateKey 
Instance details

Defined in Cropty

Binary PrivateKey 
Instance details

Defined in Cropty

data Signed a #

A convenient type in which to wrap signed things.

Instances

Instances details
Eq (Signed a) 
Instance details

Defined in Cropty

Methods

(==) :: Signed a -> Signed a -> Bool #

(/=) :: Signed a -> Signed a -> Bool #

Ord (Signed a) 
Instance details

Defined in Cropty

Methods

compare :: Signed a -> Signed a -> Ordering #

(<) :: Signed a -> Signed a -> Bool #

(<=) :: Signed a -> Signed a -> Bool #

(>) :: Signed a -> Signed a -> Bool #

(>=) :: Signed a -> Signed a -> Bool #

max :: Signed a -> Signed a -> Signed a #

min :: Signed a -> Signed a -> Signed a #

Read a => Read (Signed a) 
Instance details

Defined in Cropty

Show a => Show (Signed a) 
Instance details

Defined in Cropty

Methods

showsPrec :: Int -> Signed a -> ShowS #

show :: Signed a -> String #

showList :: [Signed a] -> ShowS #

Generic (Signed a) 
Instance details

Defined in Cropty

Associated Types

type Rep (Signed a) :: Type -> Type #

Methods

from :: Signed a -> Rep (Signed a) x #

to :: Rep (Signed a) x -> Signed a #

Binary a => Binary (Signed a) 
Instance details

Defined in Cropty

Methods

put :: Signed a -> Put #

get :: Get (Signed a) #

putList :: [Signed a] -> Put #

type Rep (Signed a) 
Instance details

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

data Merge e x a #

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

Instances details
Profunctor (Merge e) 
Instance details

Defined in Data.Merge

Methods

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) 
Instance details

Defined in Data.Merge

Methods

fmap :: (a -> b) -> Merge e x a -> Merge e x b #

(<$) :: a -> Merge e x b -> Merge e x a #

Semigroup e => Applicative (Merge e x) 
Instance details

Defined in Data.Merge

Methods

pure :: a -> Merge e x a #

(<*>) :: Merge e x (a -> b) -> Merge e x a -> Merge e x b #

liftA2 :: (a -> b -> c) -> Merge e x a -> Merge e x b -> Merge e x c #

(*>) :: Merge e x a -> Merge e x b -> Merge e x b #

(<*) :: Merge e x a -> Merge e x b -> Merge e x a #

Monoid e => Alternative (Merge e x) 
Instance details

Defined in Data.Merge

Methods

empty :: Merge e x a #

(<|>) :: Merge e x a -> Merge e x a -> Merge e x a #

some :: Merge e x a -> Merge e x [a] #

many :: Merge e x a -> Merge e x [a] #

(Semigroup e, Semigroup a) => Semigroup (Merge e x a) 
Instance details

Defined in Data.Merge

Methods

(<>) :: Merge e x a -> Merge e x a -> Merge e x a #

sconcat :: NonEmpty (Merge e x a) -> Merge e x a #

stimes :: Integral b => b -> Merge e x a -> Merge e x a #

(Monoid e, Semigroup a) => Monoid (Merge e x a) 
Instance details

Defined in Data.Merge

Methods

mempty :: Merge e x a #

mappend :: Merge e x a -> Merge e x a -> Merge e x a #

mconcat :: [Merge e x a] -> Merge e x a #