ipld-cid-0.1.0.0: IPLD Content-IDentifiers <https://github.com/ipld/cid>

Copyright2018 Monadic GmbH
LicenseBSD3
Maintainerkim@monadic.xyz, team@monadic.xyz
Stabilityprovisional
Portabilitynon-portable (GHC extensions)
Safe HaskellNone
LanguageHaskell2010

Data.IPLD.CID

Description

Content IDentifiers

"CID is a format for referencing content in distributed information systems, like IPFS. It leverages content addressing, cryptographic hashing, and self-describing formats. It is the core identifier used by IPFS and IPLD."

Synopsis

Documentation

data Version Source #

Specification version.

Constructors

V0 
V1 
Instances
Bounded Version Source # 
Instance details

Defined in Data.IPLD.CID

Enum Version Source # 
Instance details

Defined in Data.IPLD.CID

Eq Version Source # 
Instance details

Defined in Data.IPLD.CID

Methods

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

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

Ord Version Source # 
Instance details

Defined in Data.IPLD.CID

Show Version Source # 
Instance details

Defined in Data.IPLD.CID

Generic Version Source # 
Instance details

Defined in Data.IPLD.CID

Associated Types

type Rep Version :: Type -> Type #

Methods

from :: Version -> Rep Version x #

to :: Rep Version x -> Version #

Hashable Version Source # 
Instance details

Defined in Data.IPLD.CID

Methods

hashWithSalt :: Int -> Version -> Int #

hash :: Version -> Int #

NFData Version Source # 
Instance details

Defined in Data.IPLD.CID

Methods

rnf :: Version -> () #

type Rep Version Source # 
Instance details

Defined in Data.IPLD.CID

type Rep Version = D1 (MetaData "Version" "Data.IPLD.CID" "ipld-cid-0.1.0.0-8NZ9ygnopa7DbdvMJP5n9H" False) (C1 (MetaCons "V0" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "V1" PrefixI False) (U1 :: Type -> Type))

data Codec Source #

The content type or format of the data being addressed, specified as a multicodec.

Note that we do not currently have a full multicodec implementation, as it is overly complicated for our purposes. We also only support Codecs on an as-needed basis. Future versions may utilise a separate library.

Constructors

Raw 
DagProtobuf 
DagCbor 
GitRaw 
Instances
Eq Codec Source # 
Instance details

Defined in Data.IPLD.CID

Methods

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

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

Ord Codec Source # 
Instance details

Defined in Data.IPLD.CID

Methods

compare :: Codec -> Codec -> Ordering #

(<) :: Codec -> Codec -> Bool #

(<=) :: Codec -> Codec -> Bool #

(>) :: Codec -> Codec -> Bool #

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

max :: Codec -> Codec -> Codec #

min :: Codec -> Codec -> Codec #

Show Codec Source # 
Instance details

Defined in Data.IPLD.CID

Methods

showsPrec :: Int -> Codec -> ShowS #

show :: Codec -> String #

showList :: [Codec] -> ShowS #

Generic Codec Source # 
Instance details

Defined in Data.IPLD.CID

Associated Types

type Rep Codec :: Type -> Type #

Methods

from :: Codec -> Rep Codec x #

to :: Rep Codec x -> Codec #

Hashable Codec Source # 
Instance details

Defined in Data.IPLD.CID

Methods

hashWithSalt :: Int -> Codec -> Int #

hash :: Codec -> Int #

NFData Codec Source # 
Instance details

Defined in Data.IPLD.CID

Methods

rnf :: Codec -> () #

type Rep Codec Source # 
Instance details

Defined in Data.IPLD.CID

type Rep Codec = D1 (MetaData "Codec" "Data.IPLD.CID" "ipld-cid-0.1.0.0-8NZ9ygnopa7DbdvMJP5n9H" False) ((C1 (MetaCons "Raw" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "DagProtobuf" PrefixI False) (U1 :: Type -> Type)) :+: (C1 (MetaCons "DagCbor" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "GitRaw" PrefixI False) (U1 :: Type -> Type)))

data CID Source #

A Content IDentifier.

Instances
Eq CID Source # 
Instance details

Defined in Data.IPLD.CID

Methods

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

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

Ord CID Source # 
Instance details

Defined in Data.IPLD.CID

Methods

compare :: CID -> CID -> Ordering #

(<) :: CID -> CID -> Bool #

(<=) :: CID -> CID -> Bool #

(>) :: CID -> CID -> Bool #

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

max :: CID -> CID -> CID #

min :: CID -> CID -> CID #

Read CID Source # 
Instance details

Defined in Data.IPLD.CID

Show CID Source # 
Instance details

Defined in Data.IPLD.CID

Methods

showsPrec :: Int -> CID -> ShowS #

show :: CID -> String #

showList :: [CID] -> ShowS #

Generic CID Source # 
Instance details

Defined in Data.IPLD.CID

Associated Types

type Rep CID :: Type -> Type #

Methods

from :: CID -> Rep CID x #

to :: Rep CID x -> CID #

Hashable CID Source # 
Instance details

Defined in Data.IPLD.CID

Methods

hashWithSalt :: Int -> CID -> Int #

hash :: CID -> Int #

NFData CID Source # 
Instance details

Defined in Data.IPLD.CID

Methods

rnf :: CID -> () #

type Rep CID Source # 
Instance details

Defined in Data.IPLD.CID

newCidV1 :: Multihashable a => Codec -> Digest a -> CID Source #

Create a V1 CID.

buildCid :: CID -> Builder Source #

Serialise a CID.

decodeCid :: ByteString -> Either String CID Source #

Decode a CID from a strict ByteString.

   decodeCid . buildCid ≡ Right

getCid :: Get CID Source #

Deserialise a CID in the Get monad.

Note that this does not support V0 CIDs.

cidFromText :: Text -> Either String CID Source #

Decode a CID from a textual representation.

The Text value is expected to be base58 (bitcoin) encoded (for V0 CIDs), or a valid Multibase.

   cidFromText . cidToText ≡ id

cidToText :: CID -> Text Source #

Encode a CID to a textual representation.

The result is either a base58 (bitcoin) encoded string of just the cidHash value for V0 CIDs, or otherwise a Multibase value at base Base58btc of the binary representation of the CID (as produced by buildCid).

codecToCode :: Codec -> Word8 Source #

multicodec numerical code of the given Codec.

codecFromCode :: Word8 -> Maybe Codec Source #

Attempt to convert from a multicodec numerical code to a Codec.