ipfs-1.3.0.1: Access IPFS locally and remotely
Safe HaskellNone
LanguageHaskell2010

Network.IPFS.Types

Description

Types related to IPFS

Synopsis

Documentation

newtype BinPath Source #

Path to the IPFS binary

Constructors

BinPath 

Fields

Instances

Instances details
Eq BinPath Source # 
Instance details

Defined in Network.IPFS.BinPath.Types

Methods

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

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

Show BinPath Source # 
Instance details

Defined in Network.IPFS.BinPath.Types

IsString BinPath Source # 
Instance details

Defined in Network.IPFS.BinPath.Types

Methods

fromString :: String -> BinPath #

Generic BinPath Source # 
Instance details

Defined in Network.IPFS.BinPath.Types

Associated Types

type Rep BinPath :: Type -> Type #

Methods

from :: BinPath -> Rep BinPath x #

to :: Rep BinPath x -> BinPath #

FromJSON BinPath Source # 
Instance details

Defined in Network.IPFS.BinPath.Types

FromEnv BinPath Source # 
Instance details

Defined in Network.IPFS.BinPath.Types

Display BinPath Source # 
Instance details

Defined in Network.IPFS.BinPath.Types

type Rep BinPath Source # 
Instance details

Defined in Network.IPFS.BinPath.Types

type Rep BinPath = D1 ('MetaData "BinPath" "Network.IPFS.BinPath.Types" "ipfs-1.3.0.1-DXC1D51H294HjfmR2x5yzm" 'True) (C1 ('MetaCons "BinPath" 'PrefixI 'True) (S1 ('MetaSel ('Just "getBinPath") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 FilePath)))

newtype CID Source #

Constructors

CID 

Fields

Instances

Instances details
Eq CID Source # 
Instance details

Defined in Network.IPFS.CID.Types

Methods

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

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

Ord CID Source # 
Instance details

Defined in Network.IPFS.CID.Types

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 Network.IPFS.CID.Types

Show CID Source # 
Instance details

Defined in Network.IPFS.CID.Types

Methods

showsPrec :: Int -> CID -> ShowS #

show :: CID -> String #

showList :: [CID] -> ShowS #

IsString CID Source # 
Instance details

Defined in Network.IPFS.CID.Types

Methods

fromString :: String -> CID #

Generic CID Source # 
Instance details

Defined in Network.IPFS.CID.Types

Associated Types

type Rep CID :: Type -> Type #

Methods

from :: CID -> Rep CID x #

to :: Rep CID x -> CID #

ToJSON CID Source # 
Instance details

Defined in Network.IPFS.CID.Types

FromJSON CID Source # 
Instance details

Defined in Network.IPFS.CID.Types

ToHttpApiData CID Source # 
Instance details

Defined in Network.IPFS.CID.Types

FromHttpApiData CID Source # 
Instance details

Defined in Network.IPFS.CID.Types

Display CID Source # 
Instance details

Defined in Network.IPFS.CID.Types

ToSchema CID Source # 
Instance details

Defined in Network.IPFS.CID.Types

ToParamSchema CID Source # 
Instance details

Defined in Network.IPFS.CID.Types

Methods

toParamSchema :: forall (t :: SwaggerKind Type). Proxy CID -> ParamSchema t #

MimeRender PlainText CID Source # 
Instance details

Defined in Network.IPFS.CID.Types

MimeRender OctetStream CID Source # 
Instance details

Defined in Network.IPFS.CID.Types

MimeUnrender PlainText CID Source # 
Instance details

Defined in Network.IPFS.CID.Types

MimeUnrender PlainText [CID] Source # 
Instance details

Defined in Network.IPFS.CID.Types

type Rep CID Source # 
Instance details

Defined in Network.IPFS.CID.Types

type Rep CID = D1 ('MetaData "CID" "Network.IPFS.CID.Types" "ipfs-1.3.0.1-DXC1D51H294HjfmR2x5yzm" 'True) (C1 ('MetaCons "CID" 'PrefixI 'True) (S1 ('MetaSel ('Just "unaddress") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text)))

mkCID :: Text -> CID Source #

Smart constructor for CID

newtype Name Source #

Constructors

Name 

Fields

Instances

Instances details
Eq Name Source # 
Instance details

Defined in Network.IPFS.Name.Types

Methods

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

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

Ord Name Source # 
Instance details

Defined in Network.IPFS.Name.Types

Methods

compare :: Name -> Name -> Ordering #

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

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

(>) :: Name -> Name -> Bool #

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

max :: Name -> Name -> Name #

min :: Name -> Name -> Name #

Show Name Source # 
Instance details

Defined in Network.IPFS.Name.Types

Methods

showsPrec :: Int -> Name -> ShowS #

show :: Name -> String #

showList :: [Name] -> ShowS #

IsString Name Source # 
Instance details

Defined in Network.IPFS.Name.Types

Methods

fromString :: String -> Name #

Generic Name Source # 
Instance details

Defined in Network.IPFS.Name.Types

Associated Types

type Rep Name :: Type -> Type #

Methods

from :: Name -> Rep Name x #

to :: Rep Name x -> Name #

ToJSON Name Source # 
Instance details

Defined in Network.IPFS.Name.Types

FromJSON Name Source # 
Instance details

Defined in Network.IPFS.Name.Types

FromHttpApiData Name Source # 
Instance details

Defined in Network.IPFS.Name.Types

Display Name Source # 
Instance details

Defined in Network.IPFS.Name.Types

ToSchema Name Source # 
Instance details

Defined in Network.IPFS.Name.Types

ToParamSchema Name Source # 
Instance details

Defined in Network.IPFS.Name.Types

Methods

toParamSchema :: forall (t :: SwaggerKind Type). Proxy Name -> ParamSchema t #

type Rep Name Source # 
Instance details

Defined in Network.IPFS.Name.Types

type Rep Name = D1 ('MetaData "Name" "Network.IPFS.Name.Types" "ipfs-1.3.0.1-DXC1D51H294HjfmR2x5yzm" 'True) (C1 ('MetaCons "Name" 'PrefixI 'True) (S1 ('MetaSel ('Just "unName") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String)))

newtype Peer Source #

Constructors

Peer 

Fields

Instances

Instances details
Eq Peer Source # 
Instance details

Defined in Network.IPFS.Peer.Types

Methods

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

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

Show Peer Source # 
Instance details

Defined in Network.IPFS.Peer.Types

Methods

showsPrec :: Int -> Peer -> ShowS #

show :: Peer -> String #

showList :: [Peer] -> ShowS #

IsString Peer Source # 
Instance details

Defined in Network.IPFS.Peer.Types

Methods

fromString :: String -> Peer #

ToJSON Peer Source # 
Instance details

Defined in Network.IPFS.Peer.Types

FromJSON Peer Source # 
Instance details

Defined in Network.IPFS.Peer.Types

Display Peer Source # 
Instance details

Defined in Network.IPFS.Peer.Types

ToSchema Peer Source # 
Instance details

Defined in Network.IPFS.Peer.Types

MimeRender PlainText Peer Source # 
Instance details

Defined in Network.IPFS.Peer.Types

MimeRender OctetStream Peer Source # 
Instance details

Defined in Network.IPFS.Peer.Types

newtype Path Source #

CID path

Exmaple

"QmcaHAFzUPRCRaUK12dC6YyhcqEEtdfg94XrPwgCxZ1ihD/myfile.txt"

Constructors

Path 

Fields

Instances

Instances details
Eq Path Source # 
Instance details

Defined in Network.IPFS.Path.Types

Methods

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

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

Ord Path Source # 
Instance details

Defined in Network.IPFS.Path.Types

Methods

compare :: Path -> Path -> Ordering #

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

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

(>) :: Path -> Path -> Bool #

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

max :: Path -> Path -> Path #

min :: Path -> Path -> Path #

Show Path Source # 
Instance details

Defined in Network.IPFS.Path.Types

Methods

showsPrec :: Int -> Path -> ShowS #

show :: Path -> String #

showList :: [Path] -> ShowS #

IsString Path Source # 
Instance details

Defined in Network.IPFS.Path.Types

Methods

fromString :: String -> Path #

Generic Path Source # 
Instance details

Defined in Network.IPFS.Path.Types

Associated Types

type Rep Path :: Type -> Type #

Methods

from :: Path -> Rep Path x #

to :: Rep Path x -> Path #

ToHttpApiData Path Source # 
Instance details

Defined in Network.IPFS.Path.Types

ToSchema Path Source # 
Instance details

Defined in Network.IPFS.Path.Types

MimeRender PlainText Path Source # 
Instance details

Defined in Network.IPFS.Path.Types

MimeRender OctetStream Path Source # 
Instance details

Defined in Network.IPFS.Path.Types

type Rep Path Source # 
Instance details

Defined in Network.IPFS.Path.Types

type Rep Path = D1 ('MetaData "Path" "Network.IPFS.Path.Types" "ipfs-1.3.0.1-DXC1D51H294HjfmR2x5yzm" 'True) (C1 ('MetaCons "Path" 'PrefixI 'True) (S1 ('MetaSel ('Just "unpath") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text)))

data SparseTree Source #

Directory structure for CIDs and other identifiers

Examples:

Content "abcdef"
show $ Directory [(Key "abcdef", Stub "myfile.txt")])]

"abcdef/myfile.txt"

Instances

Instances details
Eq SparseTree Source # 
Instance details

Defined in Network.IPFS.SparseTree.Types

Show SparseTree Source # 
Instance details

Defined in Network.IPFS.SparseTree.Types

Generic SparseTree Source # 
Instance details

Defined in Network.IPFS.SparseTree.Types

Associated Types

type Rep SparseTree :: Type -> Type #

ToJSON SparseTree Source # 
Instance details

Defined in Network.IPFS.SparseTree.Types

Display SparseTree Source # 
Instance details

Defined in Network.IPFS.SparseTree.Types

ToSchema SparseTree Source # 
Instance details

Defined in Network.IPFS.SparseTree.Types

Display (Map Tag SparseTree) Source # 
Instance details

Defined in Network.IPFS.SparseTree.Types

type Rep SparseTree Source # 
Instance details

Defined in Network.IPFS.SparseTree.Types

type Rep SparseTree = D1 ('MetaData "SparseTree" "Network.IPFS.SparseTree.Types" "ipfs-1.3.0.1-DXC1D51H294HjfmR2x5yzm" 'False) (C1 ('MetaCons "Stub" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Name)) :+: (C1 ('MetaCons "Content" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 CID)) :+: C1 ('MetaCons "Directory" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Map Tag SparseTree)))))

data Tag Source #

Constructors

Key Name 
Hash CID 

Instances

Instances details
Eq Tag Source # 
Instance details

Defined in Network.IPFS.SparseTree.Types

Methods

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

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

Ord Tag Source # 
Instance details

Defined in Network.IPFS.SparseTree.Types

Methods

compare :: Tag -> Tag -> Ordering #

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

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

(>) :: Tag -> Tag -> Bool #

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

max :: Tag -> Tag -> Tag #

min :: Tag -> Tag -> Tag #

Show Tag Source # 
Instance details

Defined in Network.IPFS.SparseTree.Types

Methods

showsPrec :: Int -> Tag -> ShowS #

show :: Tag -> String #

showList :: [Tag] -> ShowS #

Generic Tag Source # 
Instance details

Defined in Network.IPFS.SparseTree.Types

Associated Types

type Rep Tag :: Type -> Type #

Methods

from :: Tag -> Rep Tag x #

to :: Rep Tag x -> Tag #

ToJSON Tag Source # 
Instance details

Defined in Network.IPFS.SparseTree.Types

ToJSONKey Tag Source # 
Instance details

Defined in Network.IPFS.SparseTree.Types

FromJSON Tag Source # 
Instance details

Defined in Network.IPFS.SparseTree.Types

FromJSONKey Tag Source # 
Instance details

Defined in Network.IPFS.SparseTree.Types

FromHttpApiData Tag Source # 
Instance details

Defined in Network.IPFS.SparseTree.Types

Display Tag Source # 
Instance details

Defined in Network.IPFS.SparseTree.Types

ToSchema Tag Source # 
Instance details

Defined in Network.IPFS.SparseTree.Types

Display (Map Tag SparseTree) Source # 
Instance details

Defined in Network.IPFS.SparseTree.Types

type Rep Tag Source # 
Instance details

Defined in Network.IPFS.SparseTree.Types

type Rep Tag = D1 ('MetaData "Tag" "Network.IPFS.SparseTree.Types" "ipfs-1.3.0.1-DXC1D51H294HjfmR2x5yzm" 'False) (C1 ('MetaCons "Key" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Name)) :+: C1 ('MetaCons "Hash" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 CID)))

newtype Timeout Source #

Constructors

Timeout 

Fields

Instances

Instances details
Eq Timeout Source # 
Instance details

Defined in Network.IPFS.Timeout.Types

Methods

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

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

Num Timeout Source # 
Instance details

Defined in Network.IPFS.Timeout.Types

Show Timeout Source # 
Instance details

Defined in Network.IPFS.Timeout.Types

Generic Timeout Source # 
Instance details

Defined in Network.IPFS.Timeout.Types

Associated Types

type Rep Timeout :: Type -> Type #

Methods

from :: Timeout -> Rep Timeout x #

to :: Rep Timeout x -> Timeout #

FromJSON Timeout Source # 
Instance details

Defined in Network.IPFS.Timeout.Types

FromEnv Timeout Source # 
Instance details

Defined in Network.IPFS.Timeout.Types

type Rep Timeout Source # 
Instance details

Defined in Network.IPFS.Timeout.Types

type Rep Timeout = D1 ('MetaData "Timeout" "Network.IPFS.Timeout.Types" "ipfs-1.3.0.1-DXC1D51H294HjfmR2x5yzm" 'True) (C1 ('MetaCons "Timeout" 'PrefixI 'True) (S1 ('MetaSel ('Just "getSeconds") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Natural)))

newtype URL Source #

IPFS client URL

Constructors

URL 

Fields

Instances

Instances details
Eq URL Source # 
Instance details

Defined in Network.IPFS.URL.Types

Methods

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

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

Show URL Source # 
Instance details

Defined in Network.IPFS.URL.Types

Methods

showsPrec :: Int -> URL -> ShowS #

show :: URL -> String #

showList :: [URL] -> ShowS #

Generic URL Source # 
Instance details

Defined in Network.IPFS.URL.Types

Associated Types

type Rep URL :: Type -> Type #

Methods

from :: URL -> Rep URL x #

to :: Rep URL x -> URL #

FromJSON URL Source # 
Instance details

Defined in Network.IPFS.URL.Types

type Rep URL Source # 
Instance details

Defined in Network.IPFS.URL.Types

type Rep URL = D1 ('MetaData "URL" "Network.IPFS.URL.Types" "ipfs-1.3.0.1-DXC1D51H294HjfmR2x5yzm" 'True) (C1 ('MetaCons "URL" 'PrefixI 'True) (S1 ('MetaSel ('Just "getURL") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 BaseUrl)))

newtype Gateway Source #

Type safety wrapper for IPFS Gateway Used as cname value for DNS updates

Constructors

Gateway 

Fields

Instances

Instances details
Eq Gateway Source # 
Instance details

Defined in Network.IPFS.Gateway.Types

Methods

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

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

Show Gateway Source # 
Instance details

Defined in Network.IPFS.Gateway.Types

IsString Gateway Source # 
Instance details

Defined in Network.IPFS.Gateway.Types

Methods

fromString :: String -> Gateway #

Generic Gateway Source # 
Instance details

Defined in Network.IPFS.Gateway.Types

Associated Types

type Rep Gateway :: Type -> Type #

Methods

from :: Gateway -> Rep Gateway x #

to :: Rep Gateway x -> Gateway #

FromJSON Gateway Source # 
Instance details

Defined in Network.IPFS.Gateway.Types

ToSchema Gateway Source # 
Instance details

Defined in Network.IPFS.Gateway.Types

type Rep Gateway Source # 
Instance details

Defined in Network.IPFS.Gateway.Types

type Rep Gateway = D1 ('MetaData "Gateway" "Network.IPFS.Gateway.Types" "ipfs-1.3.0.1-DXC1D51H294HjfmR2x5yzm" 'True) (C1 ('MetaCons "Gateway" 'PrefixI 'True) (S1 ('MetaSel ('Just "getGateway") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text)))

data ErrorBody Source #

Constructors

ErrorBody 

Fields

Instances

Instances details
FromJSON ErrorBody Source # 
Instance details

Defined in Network.IPFS.Client.Error.Types

data Stat Source #

Instances

Instances details
FromJSON Stat Source # 
Instance details

Defined in Network.IPFS.Stat.Types

newtype Bytes Source #

Constructors

Bytes 

Fields

Instances

Instances details
Eq Bytes Source # 
Instance details

Defined in Network.IPFS.Bytes.Types

Methods

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

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

Show Bytes Source # 
Instance details

Defined in Network.IPFS.Bytes.Types

Methods

showsPrec :: Int -> Bytes -> ShowS #

show :: Bytes -> String #

showList :: [Bytes] -> ShowS #

FromJSON Bytes Source # 
Instance details

Defined in Network.IPFS.Bytes.Types