{-# LANGUAGE DataKinds #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE TypeOperators #-}
module Network.Ipfs.Api.Types where
import Control.Arrow (left)
import Control.Monad
import Data.Aeson
import Data.ByteString.Lazy (toStrict)
import qualified Data.ByteString.Lazy.Char8 ()
import qualified Data.HashMap.Strict as H
import Data.Int
import Data.Text (Text)
import qualified Data.Text.Encoding as TextS
import Data.Typeable
import Network.HTTP.Client ()
import qualified Network.HTTP.Media as M ((//))
import Servant.API
type CatReturnType = Text
type ReprovideReturnType = Text
type GetReturnType = Text
type BlockReturnType = Text
type DagReturnType = Text
type ObjectReturnType = Text
type FilesReadType = Text
data DirLink = DirLink
{ DirLink -> Text
dlName :: Text
, DirLink -> Text
dlHash :: Text
, DirLink -> Int64
dlSize :: Int64
, DirLink -> Int
dlContentType :: Int
, DirLink -> Text
dlTarget :: Text
}
deriving (Int -> DirLink -> ShowS
[DirLink] -> ShowS
DirLink -> String
(Int -> DirLink -> ShowS)
-> (DirLink -> String) -> ([DirLink] -> ShowS) -> Show DirLink
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DirLink] -> ShowS
$cshowList :: [DirLink] -> ShowS
show :: DirLink -> String
$cshow :: DirLink -> String
showsPrec :: Int -> DirLink -> ShowS
$cshowsPrec :: Int -> DirLink -> ShowS
Show, DirLink -> DirLink -> Bool
(DirLink -> DirLink -> Bool)
-> (DirLink -> DirLink -> Bool) -> Eq DirLink
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DirLink -> DirLink -> Bool
$c/= :: DirLink -> DirLink -> Bool
== :: DirLink -> DirLink -> Bool
$c== :: DirLink -> DirLink -> Bool
Eq)
data DirObj = DirObj
{ DirObj -> Text
dirHash :: Text
, DirObj -> [DirLink]
links :: [DirLink]
}
deriving (Int -> DirObj -> ShowS
[DirObj] -> ShowS
DirObj -> String
(Int -> DirObj -> ShowS)
-> (DirObj -> String) -> ([DirObj] -> ShowS) -> Show DirObj
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DirObj] -> ShowS
$cshowList :: [DirObj] -> ShowS
show :: DirObj -> String
$cshow :: DirObj -> String
showsPrec :: Int -> DirObj -> ShowS
$cshowsPrec :: Int -> DirObj -> ShowS
Show, DirObj -> DirObj -> Bool
(DirObj -> DirObj -> Bool)
-> (DirObj -> DirObj -> Bool) -> Eq DirObj
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DirObj -> DirObj -> Bool
$c/= :: DirObj -> DirObj -> Bool
== :: DirObj -> DirObj -> Bool
$c== :: DirObj -> DirObj -> Bool
Eq)
data AddObj = AddObj
{ AddObj -> Text
name :: Text
, AddObj -> Text
hash :: Text
, AddObj -> Text
size :: Text
}
deriving (Int -> AddObj -> ShowS
[AddObj] -> ShowS
AddObj -> String
(Int -> AddObj -> ShowS)
-> (AddObj -> String) -> ([AddObj] -> ShowS) -> Show AddObj
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [AddObj] -> ShowS
$cshowList :: [AddObj] -> ShowS
show :: AddObj -> String
$cshow :: AddObj -> String
showsPrec :: Int -> AddObj -> ShowS
$cshowsPrec :: Int -> AddObj -> ShowS
Show, AddObj -> AddObj -> Bool
(AddObj -> AddObj -> Bool)
-> (AddObj -> AddObj -> Bool) -> Eq AddObj
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: AddObj -> AddObj -> Bool
$c/= :: AddObj -> AddObj -> Bool
== :: AddObj -> AddObj -> Bool
$c== :: AddObj -> AddObj -> Bool
Eq)
instance FromJSON AddObj where
parseJSON :: Value -> Parser AddObj
parseJSON (Object Object
o) =
Text -> Text -> Text -> AddObj
AddObj (Text -> Text -> Text -> AddObj)
-> Parser Text -> Parser (Text -> Text -> AddObj)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
o Object -> Text -> Parser Text
forall a. FromJSON a => Object -> Text -> Parser a
.: Text
"Name"
Parser (Text -> Text -> AddObj)
-> Parser Text -> Parser (Text -> AddObj)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object -> Text -> Parser Text
forall a. FromJSON a => Object -> Text -> Parser a
.: Text
"Hash"
Parser (Text -> AddObj) -> Parser Text -> Parser AddObj
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object -> Text -> Parser Text
forall a. FromJSON a => Object -> Text -> Parser a
.: Text
"Size"
parseJSON Value
_ = Parser AddObj
forall (m :: * -> *) a. MonadPlus m => m a
mzero
data LsObj = LsObj
{ LsObj -> [DirObj]
objs :: [DirObj]
}
deriving (Int -> LsObj -> ShowS
[LsObj] -> ShowS
LsObj -> String
(Int -> LsObj -> ShowS)
-> (LsObj -> String) -> ([LsObj] -> ShowS) -> Show LsObj
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [LsObj] -> ShowS
$cshowList :: [LsObj] -> ShowS
show :: LsObj -> String
$cshow :: LsObj -> String
showsPrec :: Int -> LsObj -> ShowS
$cshowsPrec :: Int -> LsObj -> ShowS
Show, LsObj -> LsObj -> Bool
(LsObj -> LsObj -> Bool) -> (LsObj -> LsObj -> Bool) -> Eq LsObj
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: LsObj -> LsObj -> Bool
$c/= :: LsObj -> LsObj -> Bool
== :: LsObj -> LsObj -> Bool
$c== :: LsObj -> LsObj -> Bool
Eq)
data SwarmStreamObj = SwarmStreamObj
{ SwarmStreamObj -> Text
protocol :: Text
}
deriving (Int -> SwarmStreamObj -> ShowS
[SwarmStreamObj] -> ShowS
SwarmStreamObj -> String
(Int -> SwarmStreamObj -> ShowS)
-> (SwarmStreamObj -> String)
-> ([SwarmStreamObj] -> ShowS)
-> Show SwarmStreamObj
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [SwarmStreamObj] -> ShowS
$cshowList :: [SwarmStreamObj] -> ShowS
show :: SwarmStreamObj -> String
$cshow :: SwarmStreamObj -> String
showsPrec :: Int -> SwarmStreamObj -> ShowS
$cshowsPrec :: Int -> SwarmStreamObj -> ShowS
Show, SwarmStreamObj -> SwarmStreamObj -> Bool
(SwarmStreamObj -> SwarmStreamObj -> Bool)
-> (SwarmStreamObj -> SwarmStreamObj -> Bool) -> Eq SwarmStreamObj
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SwarmStreamObj -> SwarmStreamObj -> Bool
$c/= :: SwarmStreamObj -> SwarmStreamObj -> Bool
== :: SwarmStreamObj -> SwarmStreamObj -> Bool
$c== :: SwarmStreamObj -> SwarmStreamObj -> Bool
Eq)
data SwarmPeerObj = SwarmPeerObj
{ SwarmPeerObj -> Text
address :: Text
, SwarmPeerObj -> Int
direction :: Int
, SwarmPeerObj -> Text
latency :: Text
, SwarmPeerObj -> Text
muxer :: Text
, SwarmPeerObj -> Text
peer :: Text
, SwarmPeerObj -> Maybe [SwarmStreamObj]
streams :: Maybe [SwarmStreamObj]
}
deriving (Int -> SwarmPeerObj -> ShowS
[SwarmPeerObj] -> ShowS
SwarmPeerObj -> String
(Int -> SwarmPeerObj -> ShowS)
-> (SwarmPeerObj -> String)
-> ([SwarmPeerObj] -> ShowS)
-> Show SwarmPeerObj
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [SwarmPeerObj] -> ShowS
$cshowList :: [SwarmPeerObj] -> ShowS
show :: SwarmPeerObj -> String
$cshow :: SwarmPeerObj -> String
showsPrec :: Int -> SwarmPeerObj -> ShowS
$cshowsPrec :: Int -> SwarmPeerObj -> ShowS
Show, SwarmPeerObj -> SwarmPeerObj -> Bool
(SwarmPeerObj -> SwarmPeerObj -> Bool)
-> (SwarmPeerObj -> SwarmPeerObj -> Bool) -> Eq SwarmPeerObj
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SwarmPeerObj -> SwarmPeerObj -> Bool
$c/= :: SwarmPeerObj -> SwarmPeerObj -> Bool
== :: SwarmPeerObj -> SwarmPeerObj -> Bool
$c== :: SwarmPeerObj -> SwarmPeerObj -> Bool
Eq)
data SwarmPeersObj = SwarmPeersObj
{ SwarmPeersObj -> [SwarmPeerObj]
peers :: [SwarmPeerObj]
}
deriving (Int -> SwarmPeersObj -> ShowS
[SwarmPeersObj] -> ShowS
SwarmPeersObj -> String
(Int -> SwarmPeersObj -> ShowS)
-> (SwarmPeersObj -> String)
-> ([SwarmPeersObj] -> ShowS)
-> Show SwarmPeersObj
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [SwarmPeersObj] -> ShowS
$cshowList :: [SwarmPeersObj] -> ShowS
show :: SwarmPeersObj -> String
$cshow :: SwarmPeersObj -> String
showsPrec :: Int -> SwarmPeersObj -> ShowS
$cshowsPrec :: Int -> SwarmPeersObj -> ShowS
Show, SwarmPeersObj -> SwarmPeersObj -> Bool
(SwarmPeersObj -> SwarmPeersObj -> Bool)
-> (SwarmPeersObj -> SwarmPeersObj -> Bool) -> Eq SwarmPeersObj
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SwarmPeersObj -> SwarmPeersObj -> Bool
$c/= :: SwarmPeersObj -> SwarmPeersObj -> Bool
== :: SwarmPeersObj -> SwarmPeersObj -> Bool
$c== :: SwarmPeersObj -> SwarmPeersObj -> Bool
Eq)
data SwarmObj = SwarmObj
{ SwarmObj -> [Text]
strings :: [Text]
}
deriving (Int -> SwarmObj -> ShowS
[SwarmObj] -> ShowS
SwarmObj -> String
(Int -> SwarmObj -> ShowS)
-> (SwarmObj -> String) -> ([SwarmObj] -> ShowS) -> Show SwarmObj
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [SwarmObj] -> ShowS
$cshowList :: [SwarmObj] -> ShowS
show :: SwarmObj -> String
$cshow :: SwarmObj -> String
showsPrec :: Int -> SwarmObj -> ShowS
$cshowsPrec :: Int -> SwarmObj -> ShowS
Show, SwarmObj -> SwarmObj -> Bool
(SwarmObj -> SwarmObj -> Bool)
-> (SwarmObj -> SwarmObj -> Bool) -> Eq SwarmObj
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SwarmObj -> SwarmObj -> Bool
$c/= :: SwarmObj -> SwarmObj -> Bool
== :: SwarmObj -> SwarmObj -> Bool
$c== :: SwarmObj -> SwarmObj -> Bool
Eq)
data WantlistObj = WantlistObj
{ WantlistObj -> Text
forSlash :: Text
}
deriving (Int -> WantlistObj -> ShowS
[WantlistObj] -> ShowS
WantlistObj -> String
(Int -> WantlistObj -> ShowS)
-> (WantlistObj -> String)
-> ([WantlistObj] -> ShowS)
-> Show WantlistObj
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [WantlistObj] -> ShowS
$cshowList :: [WantlistObj] -> ShowS
show :: WantlistObj -> String
$cshow :: WantlistObj -> String
showsPrec :: Int -> WantlistObj -> ShowS
$cshowsPrec :: Int -> WantlistObj -> ShowS
Show, WantlistObj -> WantlistObj -> Bool
(WantlistObj -> WantlistObj -> Bool)
-> (WantlistObj -> WantlistObj -> Bool) -> Eq WantlistObj
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: WantlistObj -> WantlistObj -> Bool
$c/= :: WantlistObj -> WantlistObj -> Bool
== :: WantlistObj -> WantlistObj -> Bool
$c== :: WantlistObj -> WantlistObj -> Bool
Eq)
data BitswapStatObj = BitswapStatObj
{ BitswapStatObj -> Int64
blocksReceived :: Int64
, BitswapStatObj -> Int64
blocksSent :: Int64
, BitswapStatObj -> Int64
dataReceived :: Int64
, BitswapStatObj -> Int64
dataSent :: Int64
, BitswapStatObj -> Int64
dupBlksReceived :: Int64
, BitswapStatObj -> Int64
dupDataReceived :: Int64
, BitswapStatObj -> Int64
messagesReceived :: Int64
, BitswapStatObj -> [Text]
bitswapPeers :: [Text]
, BitswapStatObj -> Int
provideBufLen :: Int
, BitswapStatObj -> [WantlistObj]
wantlist :: [WantlistObj]
}
deriving (Int -> BitswapStatObj -> ShowS
[BitswapStatObj] -> ShowS
BitswapStatObj -> String
(Int -> BitswapStatObj -> ShowS)
-> (BitswapStatObj -> String)
-> ([BitswapStatObj] -> ShowS)
-> Show BitswapStatObj
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [BitswapStatObj] -> ShowS
$cshowList :: [BitswapStatObj] -> ShowS
show :: BitswapStatObj -> String
$cshow :: BitswapStatObj -> String
showsPrec :: Int -> BitswapStatObj -> ShowS
$cshowsPrec :: Int -> BitswapStatObj -> ShowS
Show, BitswapStatObj -> BitswapStatObj -> Bool
(BitswapStatObj -> BitswapStatObj -> Bool)
-> (BitswapStatObj -> BitswapStatObj -> Bool) -> Eq BitswapStatObj
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: BitswapStatObj -> BitswapStatObj -> Bool
$c/= :: BitswapStatObj -> BitswapStatObj -> Bool
== :: BitswapStatObj -> BitswapStatObj -> Bool
$c== :: BitswapStatObj -> BitswapStatObj -> Bool
Eq)
data BitswapWLObj = BitswapWLObj
{ BitswapWLObj -> [WantlistObj]
bitswapKeys :: [WantlistObj]
}
deriving (Int -> BitswapWLObj -> ShowS
[BitswapWLObj] -> ShowS
BitswapWLObj -> String
(Int -> BitswapWLObj -> ShowS)
-> (BitswapWLObj -> String)
-> ([BitswapWLObj] -> ShowS)
-> Show BitswapWLObj
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [BitswapWLObj] -> ShowS
$cshowList :: [BitswapWLObj] -> ShowS
show :: BitswapWLObj -> String
$cshow :: BitswapWLObj -> String
showsPrec :: Int -> BitswapWLObj -> ShowS
$cshowsPrec :: Int -> BitswapWLObj -> ShowS
Show, BitswapWLObj -> BitswapWLObj -> Bool
(BitswapWLObj -> BitswapWLObj -> Bool)
-> (BitswapWLObj -> BitswapWLObj -> Bool) -> Eq BitswapWLObj
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: BitswapWLObj -> BitswapWLObj -> Bool
$c/= :: BitswapWLObj -> BitswapWLObj -> Bool
== :: BitswapWLObj -> BitswapWLObj -> Bool
$c== :: BitswapWLObj -> BitswapWLObj -> Bool
Eq)
data BitswapLedgerObj = BitswapLedgerObj
{ BitswapLedgerObj -> Int64
exchanged :: Int64
, BitswapLedgerObj -> Text
ledgerPeer :: Text
, BitswapLedgerObj -> Int64
recv :: Int64
, BitswapLedgerObj -> Int64
sent :: Int64
, BitswapLedgerObj -> Double
value :: Double
}
deriving (Int -> BitswapLedgerObj -> ShowS
[BitswapLedgerObj] -> ShowS
BitswapLedgerObj -> String
(Int -> BitswapLedgerObj -> ShowS)
-> (BitswapLedgerObj -> String)
-> ([BitswapLedgerObj] -> ShowS)
-> Show BitswapLedgerObj
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [BitswapLedgerObj] -> ShowS
$cshowList :: [BitswapLedgerObj] -> ShowS
show :: BitswapLedgerObj -> String
$cshow :: BitswapLedgerObj -> String
showsPrec :: Int -> BitswapLedgerObj -> ShowS
$cshowsPrec :: Int -> BitswapLedgerObj -> ShowS
Show, BitswapLedgerObj -> BitswapLedgerObj -> Bool
(BitswapLedgerObj -> BitswapLedgerObj -> Bool)
-> (BitswapLedgerObj -> BitswapLedgerObj -> Bool)
-> Eq BitswapLedgerObj
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: BitswapLedgerObj -> BitswapLedgerObj -> Bool
$c/= :: BitswapLedgerObj -> BitswapLedgerObj -> Bool
== :: BitswapLedgerObj -> BitswapLedgerObj -> Bool
$c== :: BitswapLedgerObj -> BitswapLedgerObj -> Bool
Eq)
data CidBasesObj = CidBasesObj
{ CidBasesObj -> Int
baseCode :: Int
, CidBasesObj -> Text
baseName :: Text
}
deriving (Int -> CidBasesObj -> ShowS
[CidBasesObj] -> ShowS
CidBasesObj -> String
(Int -> CidBasesObj -> ShowS)
-> (CidBasesObj -> String)
-> ([CidBasesObj] -> ShowS)
-> Show CidBasesObj
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CidBasesObj] -> ShowS
$cshowList :: [CidBasesObj] -> ShowS
show :: CidBasesObj -> String
$cshow :: CidBasesObj -> String
showsPrec :: Int -> CidBasesObj -> ShowS
$cshowsPrec :: Int -> CidBasesObj -> ShowS
Show, CidBasesObj -> CidBasesObj -> Bool
(CidBasesObj -> CidBasesObj -> Bool)
-> (CidBasesObj -> CidBasesObj -> Bool) -> Eq CidBasesObj
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CidBasesObj -> CidBasesObj -> Bool
$c/= :: CidBasesObj -> CidBasesObj -> Bool
== :: CidBasesObj -> CidBasesObj -> Bool
$c== :: CidBasesObj -> CidBasesObj -> Bool
Eq)
data CidCodecsObj = CidCodecsObj
{ CidCodecsObj -> Int
codecCode :: Int
, CidCodecsObj -> Text
codecName :: Text
}
deriving (Int -> CidCodecsObj -> ShowS
[CidCodecsObj] -> ShowS
CidCodecsObj -> String
(Int -> CidCodecsObj -> ShowS)
-> (CidCodecsObj -> String)
-> ([CidCodecsObj] -> ShowS)
-> Show CidCodecsObj
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CidCodecsObj] -> ShowS
$cshowList :: [CidCodecsObj] -> ShowS
show :: CidCodecsObj -> String
$cshow :: CidCodecsObj -> String
showsPrec :: Int -> CidCodecsObj -> ShowS
$cshowsPrec :: Int -> CidCodecsObj -> ShowS
Show, CidCodecsObj -> CidCodecsObj -> Bool
(CidCodecsObj -> CidCodecsObj -> Bool)
-> (CidCodecsObj -> CidCodecsObj -> Bool) -> Eq CidCodecsObj
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CidCodecsObj -> CidCodecsObj -> Bool
$c/= :: CidCodecsObj -> CidCodecsObj -> Bool
== :: CidCodecsObj -> CidCodecsObj -> Bool
$c== :: CidCodecsObj -> CidCodecsObj -> Bool
Eq)
data CidHashesObj = CidHashesObj
{ CidHashesObj -> Int
multihashCode :: Int
, CidHashesObj -> Text
multihashName :: Text
}
deriving (Int -> CidHashesObj -> ShowS
[CidHashesObj] -> ShowS
CidHashesObj -> String
(Int -> CidHashesObj -> ShowS)
-> (CidHashesObj -> String)
-> ([CidHashesObj] -> ShowS)
-> Show CidHashesObj
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CidHashesObj] -> ShowS
$cshowList :: [CidHashesObj] -> ShowS
show :: CidHashesObj -> String
$cshow :: CidHashesObj -> String
showsPrec :: Int -> CidHashesObj -> ShowS
$cshowsPrec :: Int -> CidHashesObj -> ShowS
Show, CidHashesObj -> CidHashesObj -> Bool
(CidHashesObj -> CidHashesObj -> Bool)
-> (CidHashesObj -> CidHashesObj -> Bool) -> Eq CidHashesObj
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CidHashesObj -> CidHashesObj -> Bool
$c/= :: CidHashesObj -> CidHashesObj -> Bool
== :: CidHashesObj -> CidHashesObj -> Bool
$c== :: CidHashesObj -> CidHashesObj -> Bool
Eq)
data CidObj = CidObj
{ CidObj -> Text
cidStr :: Text
, CidObj -> Text
errorMsg :: Text
, CidObj -> Text
formatted :: Text
}
deriving (Int -> CidObj -> ShowS
[CidObj] -> ShowS
CidObj -> String
(Int -> CidObj -> ShowS)
-> (CidObj -> String) -> ([CidObj] -> ShowS) -> Show CidObj
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CidObj] -> ShowS
$cshowList :: [CidObj] -> ShowS
show :: CidObj -> String
$cshow :: CidObj -> String
showsPrec :: Int -> CidObj -> ShowS
$cshowsPrec :: Int -> CidObj -> ShowS
Show, CidObj -> CidObj -> Bool
(CidObj -> CidObj -> Bool)
-> (CidObj -> CidObj -> Bool) -> Eq CidObj
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CidObj -> CidObj -> Bool
$c/= :: CidObj -> CidObj -> Bool
== :: CidObj -> CidObj -> Bool
$c== :: CidObj -> CidObj -> Bool
Eq)
data BlockObj = BlockObj
{ BlockObj -> Text
key :: Text
, BlockObj -> Int
blockSize :: Int
}
deriving (Int -> BlockObj -> ShowS
[BlockObj] -> ShowS
BlockObj -> String
(Int -> BlockObj -> ShowS)
-> (BlockObj -> String) -> ([BlockObj] -> ShowS) -> Show BlockObj
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [BlockObj] -> ShowS
$cshowList :: [BlockObj] -> ShowS
show :: BlockObj -> String
$cshow :: BlockObj -> String
showsPrec :: Int -> BlockObj -> ShowS
$cshowsPrec :: Int -> BlockObj -> ShowS
Show, BlockObj -> BlockObj -> Bool
(BlockObj -> BlockObj -> Bool)
-> (BlockObj -> BlockObj -> Bool) -> Eq BlockObj
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: BlockObj -> BlockObj -> Bool
$c/= :: BlockObj -> BlockObj -> Bool
== :: BlockObj -> BlockObj -> Bool
$c== :: BlockObj -> BlockObj -> Bool
Eq)
data DagCidObj = DagCidObj
{ DagCidObj -> Text
cidSlash :: Text
}
deriving (Int -> DagCidObj -> ShowS
[DagCidObj] -> ShowS
DagCidObj -> String
(Int -> DagCidObj -> ShowS)
-> (DagCidObj -> String)
-> ([DagCidObj] -> ShowS)
-> Show DagCidObj
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DagCidObj] -> ShowS
$cshowList :: [DagCidObj] -> ShowS
show :: DagCidObj -> String
$cshow :: DagCidObj -> String
showsPrec :: Int -> DagCidObj -> ShowS
$cshowsPrec :: Int -> DagCidObj -> ShowS
Show, DagCidObj -> DagCidObj -> Bool
(DagCidObj -> DagCidObj -> Bool)
-> (DagCidObj -> DagCidObj -> Bool) -> Eq DagCidObj
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DagCidObj -> DagCidObj -> Bool
$c/= :: DagCidObj -> DagCidObj -> Bool
== :: DagCidObj -> DagCidObj -> Bool
$c== :: DagCidObj -> DagCidObj -> Bool
Eq)
data DagResolveObj = DagResolveObj
{ DagResolveObj -> DagCidObj
cid :: DagCidObj
, DagResolveObj -> Text
remPath :: Text
}
deriving (Int -> DagResolveObj -> ShowS
[DagResolveObj] -> ShowS
DagResolveObj -> String
(Int -> DagResolveObj -> ShowS)
-> (DagResolveObj -> String)
-> ([DagResolveObj] -> ShowS)
-> Show DagResolveObj
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DagResolveObj] -> ShowS
$cshowList :: [DagResolveObj] -> ShowS
show :: DagResolveObj -> String
$cshow :: DagResolveObj -> String
showsPrec :: Int -> DagResolveObj -> ShowS
$cshowsPrec :: Int -> DagResolveObj -> ShowS
Show, DagResolveObj -> DagResolveObj -> Bool
(DagResolveObj -> DagResolveObj -> Bool)
-> (DagResolveObj -> DagResolveObj -> Bool) -> Eq DagResolveObj
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DagResolveObj -> DagResolveObj -> Bool
$c/= :: DagResolveObj -> DagResolveObj -> Bool
== :: DagResolveObj -> DagResolveObj -> Bool
$c== :: DagResolveObj -> DagResolveObj -> Bool
Eq)
data DagPutObj = DagPutObj
{ DagPutObj -> DagCidObj
putCid :: DagCidObj
}
deriving (Int -> DagPutObj -> ShowS
[DagPutObj] -> ShowS
DagPutObj -> String
(Int -> DagPutObj -> ShowS)
-> (DagPutObj -> String)
-> ([DagPutObj] -> ShowS)
-> Show DagPutObj
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DagPutObj] -> ShowS
$cshowList :: [DagPutObj] -> ShowS
show :: DagPutObj -> String
$cshow :: DagPutObj -> String
showsPrec :: Int -> DagPutObj -> ShowS
$cshowsPrec :: Int -> DagPutObj -> ShowS
Show, DagPutObj -> DagPutObj -> Bool
(DagPutObj -> DagPutObj -> Bool)
-> (DagPutObj -> DagPutObj -> Bool) -> Eq DagPutObj
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DagPutObj -> DagPutObj -> Bool
$c/= :: DagPutObj -> DagPutObj -> Bool
== :: DagPutObj -> DagPutObj -> Bool
$c== :: DagPutObj -> DagPutObj -> Bool
Eq)
data ConfigObj = ConfigObj
{ ConfigObj -> Text
configKey :: Text
, ConfigObj -> Text
configValue :: Text
}
deriving (Int -> ConfigObj -> ShowS
[ConfigObj] -> ShowS
ConfigObj -> String
(Int -> ConfigObj -> ShowS)
-> (ConfigObj -> String)
-> ([ConfigObj] -> ShowS)
-> Show ConfigObj
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ConfigObj] -> ShowS
$cshowList :: [ConfigObj] -> ShowS
show :: ConfigObj -> String
$cshow :: ConfigObj -> String
showsPrec :: Int -> ConfigObj -> ShowS
$cshowsPrec :: Int -> ConfigObj -> ShowS
Show, ConfigObj -> ConfigObj -> Bool
(ConfigObj -> ConfigObj -> Bool)
-> (ConfigObj -> ConfigObj -> Bool) -> Eq ConfigObj
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ConfigObj -> ConfigObj -> Bool
$c/= :: ConfigObj -> ConfigObj -> Bool
== :: ConfigObj -> ConfigObj -> Bool
$c== :: ConfigObj -> ConfigObj -> Bool
Eq)
data ObjectLinkObj = ObjectLinkObj
{ ObjectLinkObj -> Text
linkHash :: Text
, ObjectLinkObj -> Text
linkName :: Text
, ObjectLinkObj -> Int64
linkSize :: Int64
}
deriving (Int -> ObjectLinkObj -> ShowS
[ObjectLinkObj] -> ShowS
ObjectLinkObj -> String
(Int -> ObjectLinkObj -> ShowS)
-> (ObjectLinkObj -> String)
-> ([ObjectLinkObj] -> ShowS)
-> Show ObjectLinkObj
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ObjectLinkObj] -> ShowS
$cshowList :: [ObjectLinkObj] -> ShowS
show :: ObjectLinkObj -> String
$cshow :: ObjectLinkObj -> String
showsPrec :: Int -> ObjectLinkObj -> ShowS
$cshowsPrec :: Int -> ObjectLinkObj -> ShowS
Show, ObjectLinkObj -> ObjectLinkObj -> Bool
(ObjectLinkObj -> ObjectLinkObj -> Bool)
-> (ObjectLinkObj -> ObjectLinkObj -> Bool) -> Eq ObjectLinkObj
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ObjectLinkObj -> ObjectLinkObj -> Bool
$c/= :: ObjectLinkObj -> ObjectLinkObj -> Bool
== :: ObjectLinkObj -> ObjectLinkObj -> Bool
$c== :: ObjectLinkObj -> ObjectLinkObj -> Bool
Eq)
data ObjectObj = ObjectObj
{ ObjectObj -> Text
newObjectHash :: Text
}
deriving (Int -> ObjectObj -> ShowS
[ObjectObj] -> ShowS
ObjectObj -> String
(Int -> ObjectObj -> ShowS)
-> (ObjectObj -> String)
-> ([ObjectObj] -> ShowS)
-> Show ObjectObj
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ObjectObj] -> ShowS
$cshowList :: [ObjectObj] -> ShowS
show :: ObjectObj -> String
$cshow :: ObjectObj -> String
showsPrec :: Int -> ObjectObj -> ShowS
$cshowsPrec :: Int -> ObjectObj -> ShowS
Show, ObjectObj -> ObjectObj -> Bool
(ObjectObj -> ObjectObj -> Bool)
-> (ObjectObj -> ObjectObj -> Bool) -> Eq ObjectObj
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ObjectObj -> ObjectObj -> Bool
$c/= :: ObjectObj -> ObjectObj -> Bool
== :: ObjectObj -> ObjectObj -> Bool
$c== :: ObjectObj -> ObjectObj -> Bool
Eq)
data ObjectLinksObj = WithLinks
{ ObjectLinksObj -> Text
objectHash :: Text
, ObjectLinksObj -> [ObjectLinkObj]
objectLinks :: [ObjectLinkObj]
}
| WithoutLinks
{ objectHash :: Text
}
deriving (Int -> ObjectLinksObj -> ShowS
[ObjectLinksObj] -> ShowS
ObjectLinksObj -> String
(Int -> ObjectLinksObj -> ShowS)
-> (ObjectLinksObj -> String)
-> ([ObjectLinksObj] -> ShowS)
-> Show ObjectLinksObj
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ObjectLinksObj] -> ShowS
$cshowList :: [ObjectLinksObj] -> ShowS
show :: ObjectLinksObj -> String
$cshow :: ObjectLinksObj -> String
showsPrec :: Int -> ObjectLinksObj -> ShowS
$cshowsPrec :: Int -> ObjectLinksObj -> ShowS
Show, ObjectLinksObj -> ObjectLinksObj -> Bool
(ObjectLinksObj -> ObjectLinksObj -> Bool)
-> (ObjectLinksObj -> ObjectLinksObj -> Bool) -> Eq ObjectLinksObj
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ObjectLinksObj -> ObjectLinksObj -> Bool
$c/= :: ObjectLinksObj -> ObjectLinksObj -> Bool
== :: ObjectLinksObj -> ObjectLinksObj -> Bool
$c== :: ObjectLinksObj -> ObjectLinksObj -> Bool
Eq)
data ObjectGetObj = ObjectGetObj
{ ObjectGetObj -> Text
objectName :: Text
, ObjectGetObj -> [ObjectLinkObj]
objectGetLinks :: [ObjectLinkObj]
}
deriving (Int -> ObjectGetObj -> ShowS
[ObjectGetObj] -> ShowS
ObjectGetObj -> String
(Int -> ObjectGetObj -> ShowS)
-> (ObjectGetObj -> String)
-> ([ObjectGetObj] -> ShowS)
-> Show ObjectGetObj
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ObjectGetObj] -> ShowS
$cshowList :: [ObjectGetObj] -> ShowS
show :: ObjectGetObj -> String
$cshow :: ObjectGetObj -> String
showsPrec :: Int -> ObjectGetObj -> ShowS
$cshowsPrec :: Int -> ObjectGetObj -> ShowS
Show, ObjectGetObj -> ObjectGetObj -> Bool
(ObjectGetObj -> ObjectGetObj -> Bool)
-> (ObjectGetObj -> ObjectGetObj -> Bool) -> Eq ObjectGetObj
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ObjectGetObj -> ObjectGetObj -> Bool
$c/= :: ObjectGetObj -> ObjectGetObj -> Bool
== :: ObjectGetObj -> ObjectGetObj -> Bool
$c== :: ObjectGetObj -> ObjectGetObj -> Bool
Eq)
data ObjectStatObj = ObjectStatObj
{ ObjectStatObj -> Int
objBlockSize :: Int
, ObjectStatObj -> Int
cumulativeSize :: Int
, ObjectStatObj -> Int
dataSize :: Int
, ObjectStatObj -> Text
objHash :: Text
, ObjectStatObj -> Int
linksSize :: Int
, ObjectStatObj -> Int
numLinks :: Int
}
deriving (Int -> ObjectStatObj -> ShowS
[ObjectStatObj] -> ShowS
ObjectStatObj -> String
(Int -> ObjectStatObj -> ShowS)
-> (ObjectStatObj -> String)
-> ([ObjectStatObj] -> ShowS)
-> Show ObjectStatObj
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ObjectStatObj] -> ShowS
$cshowList :: [ObjectStatObj] -> ShowS
show :: ObjectStatObj -> String
$cshow :: ObjectStatObj -> String
showsPrec :: Int -> ObjectStatObj -> ShowS
$cshowsPrec :: Int -> ObjectStatObj -> ShowS
Show, ObjectStatObj -> ObjectStatObj -> Bool
(ObjectStatObj -> ObjectStatObj -> Bool)
-> (ObjectStatObj -> ObjectStatObj -> Bool) -> Eq ObjectStatObj
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ObjectStatObj -> ObjectStatObj -> Bool
$c/= :: ObjectStatObj -> ObjectStatObj -> Bool
== :: ObjectStatObj -> ObjectStatObj -> Bool
$c== :: ObjectStatObj -> ObjectStatObj -> Bool
Eq)
data DiffObj = DiffObj
{ DiffObj -> Text
diffSlash :: Text
}
deriving (Int -> DiffObj -> ShowS
[DiffObj] -> ShowS
DiffObj -> String
(Int -> DiffObj -> ShowS)
-> (DiffObj -> String) -> ([DiffObj] -> ShowS) -> Show DiffObj
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DiffObj] -> ShowS
$cshowList :: [DiffObj] -> ShowS
show :: DiffObj -> String
$cshow :: DiffObj -> String
showsPrec :: Int -> DiffObj -> ShowS
$cshowsPrec :: Int -> DiffObj -> ShowS
Show, DiffObj -> DiffObj -> Bool
(DiffObj -> DiffObj -> Bool)
-> (DiffObj -> DiffObj -> Bool) -> Eq DiffObj
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DiffObj -> DiffObj -> Bool
$c/= :: DiffObj -> DiffObj -> Bool
== :: DiffObj -> DiffObj -> Bool
$c== :: DiffObj -> DiffObj -> Bool
Eq)
data ObjectChangeObj = ObjectChangeObj
{ ObjectChangeObj -> Maybe DiffObj
after :: Maybe DiffObj
, ObjectChangeObj -> DiffObj
before :: DiffObj
, ObjectChangeObj -> Text
path :: Text
, ObjectChangeObj -> Int
diffType :: Int
}
deriving (Int -> ObjectChangeObj -> ShowS
[ObjectChangeObj] -> ShowS
ObjectChangeObj -> String
(Int -> ObjectChangeObj -> ShowS)
-> (ObjectChangeObj -> String)
-> ([ObjectChangeObj] -> ShowS)
-> Show ObjectChangeObj
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ObjectChangeObj] -> ShowS
$cshowList :: [ObjectChangeObj] -> ShowS
show :: ObjectChangeObj -> String
$cshow :: ObjectChangeObj -> String
showsPrec :: Int -> ObjectChangeObj -> ShowS
$cshowsPrec :: Int -> ObjectChangeObj -> ShowS
Show, ObjectChangeObj -> ObjectChangeObj -> Bool
(ObjectChangeObj -> ObjectChangeObj -> Bool)
-> (ObjectChangeObj -> ObjectChangeObj -> Bool)
-> Eq ObjectChangeObj
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ObjectChangeObj -> ObjectChangeObj -> Bool
$c/= :: ObjectChangeObj -> ObjectChangeObj -> Bool
== :: ObjectChangeObj -> ObjectChangeObj -> Bool
$c== :: ObjectChangeObj -> ObjectChangeObj -> Bool
Eq)
data ObjectDiffObj = ObjectDiffObj
{ ObjectDiffObj -> [ObjectChangeObj]
changes :: [ObjectChangeObj]
}
deriving (Int -> ObjectDiffObj -> ShowS
[ObjectDiffObj] -> ShowS
ObjectDiffObj -> String
(Int -> ObjectDiffObj -> ShowS)
-> (ObjectDiffObj -> String)
-> ([ObjectDiffObj] -> ShowS)
-> Show ObjectDiffObj
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ObjectDiffObj] -> ShowS
$cshowList :: [ObjectDiffObj] -> ShowS
show :: ObjectDiffObj -> String
$cshow :: ObjectDiffObj -> String
showsPrec :: Int -> ObjectDiffObj -> ShowS
$cshowsPrec :: Int -> ObjectDiffObj -> ShowS
Show, ObjectDiffObj -> ObjectDiffObj -> Bool
(ObjectDiffObj -> ObjectDiffObj -> Bool)
-> (ObjectDiffObj -> ObjectDiffObj -> Bool) -> Eq ObjectDiffObj
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ObjectDiffObj -> ObjectDiffObj -> Bool
$c/= :: ObjectDiffObj -> ObjectDiffObj -> Bool
== :: ObjectDiffObj -> ObjectDiffObj -> Bool
$c== :: ObjectDiffObj -> ObjectDiffObj -> Bool
Eq)
data PinObj = WithoutProgress
{ PinObj -> [Text]
pins :: [Text]
}
| WithProgress
{ pins :: [Text]
, PinObj -> Int
progress :: Int
}
deriving (Int -> PinObj -> ShowS
[PinObj] -> ShowS
PinObj -> String
(Int -> PinObj -> ShowS)
-> (PinObj -> String) -> ([PinObj] -> ShowS) -> Show PinObj
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [PinObj] -> ShowS
$cshowList :: [PinObj] -> ShowS
show :: PinObj -> String
$cshow :: PinObj -> String
showsPrec :: Int -> PinObj -> ShowS
$cshowsPrec :: Int -> PinObj -> ShowS
Show, PinObj -> PinObj -> Bool
(PinObj -> PinObj -> Bool)
-> (PinObj -> PinObj -> Bool) -> Eq PinObj
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PinObj -> PinObj -> Bool
$c/= :: PinObj -> PinObj -> Bool
== :: PinObj -> PinObj -> Bool
$c== :: PinObj -> PinObj -> Bool
Eq)
data BootstrapObj = BootstrapObj
{ BootstrapObj -> [Text]
bootstrapPeers :: [Text]
}
deriving (Int -> BootstrapObj -> ShowS
[BootstrapObj] -> ShowS
BootstrapObj -> String
(Int -> BootstrapObj -> ShowS)
-> (BootstrapObj -> String)
-> ([BootstrapObj] -> ShowS)
-> Show BootstrapObj
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [BootstrapObj] -> ShowS
$cshowList :: [BootstrapObj] -> ShowS
show :: BootstrapObj -> String
$cshow :: BootstrapObj -> String
showsPrec :: Int -> BootstrapObj -> ShowS
$cshowsPrec :: Int -> BootstrapObj -> ShowS
Show, BootstrapObj -> BootstrapObj -> Bool
(BootstrapObj -> BootstrapObj -> Bool)
-> (BootstrapObj -> BootstrapObj -> Bool) -> Eq BootstrapObj
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: BootstrapObj -> BootstrapObj -> Bool
$c/= :: BootstrapObj -> BootstrapObj -> Bool
== :: BootstrapObj -> BootstrapObj -> Bool
$c== :: BootstrapObj -> BootstrapObj -> Bool
Eq)
data StatsBwObj = StatsBwObj
{ StatsBwObj -> Double
rateIn :: Double
, StatsBwObj -> Double
rateOut :: Double
, StatsBwObj -> Int64
totalIn :: Int64
, StatsBwObj -> Int64
totalOut :: Int64
}
deriving (Int -> StatsBwObj -> ShowS
[StatsBwObj] -> ShowS
StatsBwObj -> String
(Int -> StatsBwObj -> ShowS)
-> (StatsBwObj -> String)
-> ([StatsBwObj] -> ShowS)
-> Show StatsBwObj
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [StatsBwObj] -> ShowS
$cshowList :: [StatsBwObj] -> ShowS
show :: StatsBwObj -> String
$cshow :: StatsBwObj -> String
showsPrec :: Int -> StatsBwObj -> ShowS
$cshowsPrec :: Int -> StatsBwObj -> ShowS
Show, StatsBwObj -> StatsBwObj -> Bool
(StatsBwObj -> StatsBwObj -> Bool)
-> (StatsBwObj -> StatsBwObj -> Bool) -> Eq StatsBwObj
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: StatsBwObj -> StatsBwObj -> Bool
$c/= :: StatsBwObj -> StatsBwObj -> Bool
== :: StatsBwObj -> StatsBwObj -> Bool
$c== :: StatsBwObj -> StatsBwObj -> Bool
Eq)
data StatsRepoObj = StatsRepoObj
{ StatsRepoObj -> Int64
numObjects :: Int64
, StatsRepoObj -> Text
repoPath :: Text
, StatsRepoObj -> Int64
repoSize :: Int64
, StatsRepoObj -> Int64
storageMax :: Int64
, StatsRepoObj -> Text
repoVersion :: Text
}
deriving (Int -> StatsRepoObj -> ShowS
[StatsRepoObj] -> ShowS
StatsRepoObj -> String
(Int -> StatsRepoObj -> ShowS)
-> (StatsRepoObj -> String)
-> ([StatsRepoObj] -> ShowS)
-> Show StatsRepoObj
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [StatsRepoObj] -> ShowS
$cshowList :: [StatsRepoObj] -> ShowS
show :: StatsRepoObj -> String
$cshow :: StatsRepoObj -> String
showsPrec :: Int -> StatsRepoObj -> ShowS
$cshowsPrec :: Int -> StatsRepoObj -> ShowS
Show, StatsRepoObj -> StatsRepoObj -> Bool
(StatsRepoObj -> StatsRepoObj -> Bool)
-> (StatsRepoObj -> StatsRepoObj -> Bool) -> Eq StatsRepoObj
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: StatsRepoObj -> StatsRepoObj -> Bool
$c/= :: StatsRepoObj -> StatsRepoObj -> Bool
== :: StatsRepoObj -> StatsRepoObj -> Bool
$c== :: StatsRepoObj -> StatsRepoObj -> Bool
Eq)
data VersionObj = VersionObj
{ VersionObj -> Text
commit :: Text
, VersionObj -> Text
golang :: Text
, VersionObj -> Text
repo :: Text
, VersionObj -> Text
system :: Text
, VersionObj -> Text
version :: Text
}
deriving (Int -> VersionObj -> ShowS
[VersionObj] -> ShowS
VersionObj -> String
(Int -> VersionObj -> ShowS)
-> (VersionObj -> String)
-> ([VersionObj] -> ShowS)
-> Show VersionObj
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [VersionObj] -> ShowS
$cshowList :: [VersionObj] -> ShowS
show :: VersionObj -> String
$cshow :: VersionObj -> String
showsPrec :: Int -> VersionObj -> ShowS
$cshowsPrec :: Int -> VersionObj -> ShowS
Show, VersionObj -> VersionObj -> Bool
(VersionObj -> VersionObj -> Bool)
-> (VersionObj -> VersionObj -> Bool) -> Eq VersionObj
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: VersionObj -> VersionObj -> Bool
$c/= :: VersionObj -> VersionObj -> Bool
== :: VersionObj -> VersionObj -> Bool
$c== :: VersionObj -> VersionObj -> Bool
Eq)
data IdObj = IdObj
{ IdObj -> [Text]
addresses :: [Text]
, IdObj -> Text
agentVersion :: Text
, IdObj -> Text
id :: Text
, IdObj -> Text
protocolVersion :: Text
, IdObj -> Text
publicKey :: Text
}
deriving (Int -> IdObj -> ShowS
[IdObj] -> ShowS
IdObj -> String
(Int -> IdObj -> ShowS)
-> (IdObj -> String) -> ([IdObj] -> ShowS) -> Show IdObj
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [IdObj] -> ShowS
$cshowList :: [IdObj] -> ShowS
show :: IdObj -> String
$cshow :: IdObj -> String
showsPrec :: Int -> IdObj -> ShowS
$cshowsPrec :: Int -> IdObj -> ShowS
Show, IdObj -> IdObj -> Bool
(IdObj -> IdObj -> Bool) -> (IdObj -> IdObj -> Bool) -> Eq IdObj
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: IdObj -> IdObj -> Bool
$c/= :: IdObj -> IdObj -> Bool
== :: IdObj -> IdObj -> Bool
$c== :: IdObj -> IdObj -> Bool
Eq)
data DnsObj = DnsObj
{ DnsObj -> Text
dnsPath :: Text
}
deriving (Int -> DnsObj -> ShowS
[DnsObj] -> ShowS
DnsObj -> String
(Int -> DnsObj -> ShowS)
-> (DnsObj -> String) -> ([DnsObj] -> ShowS) -> Show DnsObj
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DnsObj] -> ShowS
$cshowList :: [DnsObj] -> ShowS
show :: DnsObj -> String
$cshow :: DnsObj -> String
showsPrec :: Int -> DnsObj -> ShowS
$cshowsPrec :: Int -> DnsObj -> ShowS
Show, DnsObj -> DnsObj -> Bool
(DnsObj -> DnsObj -> Bool)
-> (DnsObj -> DnsObj -> Bool) -> Eq DnsObj
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DnsObj -> DnsObj -> Bool
$c/= :: DnsObj -> DnsObj -> Bool
== :: DnsObj -> DnsObj -> Bool
$c== :: DnsObj -> DnsObj -> Bool
Eq)
data PubsubObj = PubsubObj
{ PubsubObj -> [Text]
pubsubStrings :: [Text]
}
deriving (Int -> PubsubObj -> ShowS
[PubsubObj] -> ShowS
PubsubObj -> String
(Int -> PubsubObj -> ShowS)
-> (PubsubObj -> String)
-> ([PubsubObj] -> ShowS)
-> Show PubsubObj
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [PubsubObj] -> ShowS
$cshowList :: [PubsubObj] -> ShowS
show :: PubsubObj -> String
$cshow :: PubsubObj -> String
showsPrec :: Int -> PubsubObj -> ShowS
$cshowsPrec :: Int -> PubsubObj -> ShowS
Show, PubsubObj -> PubsubObj -> Bool
(PubsubObj -> PubsubObj -> Bool)
-> (PubsubObj -> PubsubObj -> Bool) -> Eq PubsubObj
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PubsubObj -> PubsubObj -> Bool
$c/= :: PubsubObj -> PubsubObj -> Bool
== :: PubsubObj -> PubsubObj -> Bool
$c== :: PubsubObj -> PubsubObj -> Bool
Eq)
data LogLsObj = LogLsObj
{ LogLsObj -> [Text]
logLsStrings :: [Text]
}
deriving (Int -> LogLsObj -> ShowS
[LogLsObj] -> ShowS
LogLsObj -> String
(Int -> LogLsObj -> ShowS)
-> (LogLsObj -> String) -> ([LogLsObj] -> ShowS) -> Show LogLsObj
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [LogLsObj] -> ShowS
$cshowList :: [LogLsObj] -> ShowS
show :: LogLsObj -> String
$cshow :: LogLsObj -> String
showsPrec :: Int -> LogLsObj -> ShowS
$cshowsPrec :: Int -> LogLsObj -> ShowS
Show, LogLsObj -> LogLsObj -> Bool
(LogLsObj -> LogLsObj -> Bool)
-> (LogLsObj -> LogLsObj -> Bool) -> Eq LogLsObj
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: LogLsObj -> LogLsObj -> Bool
$c/= :: LogLsObj -> LogLsObj -> Bool
== :: LogLsObj -> LogLsObj -> Bool
$c== :: LogLsObj -> LogLsObj -> Bool
Eq)
data LogLevelObj = LogLevelObj
{ LogLevelObj -> Text
message :: Text
}
deriving (Int -> LogLevelObj -> ShowS
[LogLevelObj] -> ShowS
LogLevelObj -> String
(Int -> LogLevelObj -> ShowS)
-> (LogLevelObj -> String)
-> ([LogLevelObj] -> ShowS)
-> Show LogLevelObj
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [LogLevelObj] -> ShowS
$cshowList :: [LogLevelObj] -> ShowS
show :: LogLevelObj -> String
$cshow :: LogLevelObj -> String
showsPrec :: Int -> LogLevelObj -> ShowS
$cshowsPrec :: Int -> LogLevelObj -> ShowS
Show, LogLevelObj -> LogLevelObj -> Bool
(LogLevelObj -> LogLevelObj -> Bool)
-> (LogLevelObj -> LogLevelObj -> Bool) -> Eq LogLevelObj
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: LogLevelObj -> LogLevelObj -> Bool
$c/= :: LogLevelObj -> LogLevelObj -> Bool
== :: LogLevelObj -> LogLevelObj -> Bool
$c== :: LogLevelObj -> LogLevelObj -> Bool
Eq)
data RepoVersionObj = RepoVersionObj
{ RepoVersionObj -> Text
repoVer :: Text
}
deriving (Int -> RepoVersionObj -> ShowS
[RepoVersionObj] -> ShowS
RepoVersionObj -> String
(Int -> RepoVersionObj -> ShowS)
-> (RepoVersionObj -> String)
-> ([RepoVersionObj] -> ShowS)
-> Show RepoVersionObj
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [RepoVersionObj] -> ShowS
$cshowList :: [RepoVersionObj] -> ShowS
show :: RepoVersionObj -> String
$cshow :: RepoVersionObj -> String
showsPrec :: Int -> RepoVersionObj -> ShowS
$cshowsPrec :: Int -> RepoVersionObj -> ShowS
Show, RepoVersionObj -> RepoVersionObj -> Bool
(RepoVersionObj -> RepoVersionObj -> Bool)
-> (RepoVersionObj -> RepoVersionObj -> Bool) -> Eq RepoVersionObj
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: RepoVersionObj -> RepoVersionObj -> Bool
$c/= :: RepoVersionObj -> RepoVersionObj -> Bool
== :: RepoVersionObj -> RepoVersionObj -> Bool
$c== :: RepoVersionObj -> RepoVersionObj -> Bool
Eq)
data RepoFsckObj = RepoFsckObj
{ RepoFsckObj -> Text
repoMessage :: Text
}
deriving (Int -> RepoFsckObj -> ShowS
[RepoFsckObj] -> ShowS
RepoFsckObj -> String
(Int -> RepoFsckObj -> ShowS)
-> (RepoFsckObj -> String)
-> ([RepoFsckObj] -> ShowS)
-> Show RepoFsckObj
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [RepoFsckObj] -> ShowS
$cshowList :: [RepoFsckObj] -> ShowS
show :: RepoFsckObj -> String
$cshow :: RepoFsckObj -> String
showsPrec :: Int -> RepoFsckObj -> ShowS
$cshowsPrec :: Int -> RepoFsckObj -> ShowS
Show, RepoFsckObj -> RepoFsckObj -> Bool
(RepoFsckObj -> RepoFsckObj -> Bool)
-> (RepoFsckObj -> RepoFsckObj -> Bool) -> Eq RepoFsckObj
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: RepoFsckObj -> RepoFsckObj -> Bool
$c/= :: RepoFsckObj -> RepoFsckObj -> Bool
== :: RepoFsckObj -> RepoFsckObj -> Bool
$c== :: RepoFsckObj -> RepoFsckObj -> Bool
Eq)
data KeyDetailsObj = KeyDetailsObj
{ KeyDetailsObj -> Text
keyId :: Text
, KeyDetailsObj -> Text
keyName :: Text
}
deriving (Int -> KeyDetailsObj -> ShowS
[KeyDetailsObj] -> ShowS
KeyDetailsObj -> String
(Int -> KeyDetailsObj -> ShowS)
-> (KeyDetailsObj -> String)
-> ([KeyDetailsObj] -> ShowS)
-> Show KeyDetailsObj
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [KeyDetailsObj] -> ShowS
$cshowList :: [KeyDetailsObj] -> ShowS
show :: KeyDetailsObj -> String
$cshow :: KeyDetailsObj -> String
showsPrec :: Int -> KeyDetailsObj -> ShowS
$cshowsPrec :: Int -> KeyDetailsObj -> ShowS
Show, KeyDetailsObj -> KeyDetailsObj -> Bool
(KeyDetailsObj -> KeyDetailsObj -> Bool)
-> (KeyDetailsObj -> KeyDetailsObj -> Bool) -> Eq KeyDetailsObj
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: KeyDetailsObj -> KeyDetailsObj -> Bool
$c/= :: KeyDetailsObj -> KeyDetailsObj -> Bool
== :: KeyDetailsObj -> KeyDetailsObj -> Bool
$c== :: KeyDetailsObj -> KeyDetailsObj -> Bool
Eq)
data KeyObj = KeyObj
{ KeyObj -> [KeyDetailsObj]
keys :: [KeyDetailsObj]
}
deriving (Int -> KeyObj -> ShowS
[KeyObj] -> ShowS
KeyObj -> String
(Int -> KeyObj -> ShowS)
-> (KeyObj -> String) -> ([KeyObj] -> ShowS) -> Show KeyObj
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [KeyObj] -> ShowS
$cshowList :: [KeyObj] -> ShowS
show :: KeyObj -> String
$cshow :: KeyObj -> String
showsPrec :: Int -> KeyObj -> ShowS
$cshowsPrec :: Int -> KeyObj -> ShowS
Show, KeyObj -> KeyObj -> Bool
(KeyObj -> KeyObj -> Bool)
-> (KeyObj -> KeyObj -> Bool) -> Eq KeyObj
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: KeyObj -> KeyObj -> Bool
$c/= :: KeyObj -> KeyObj -> Bool
== :: KeyObj -> KeyObj -> Bool
$c== :: KeyObj -> KeyObj -> Bool
Eq)
data KeyRenameObj = KeyRenameObj
{ KeyRenameObj -> Text
peerId :: Text
, KeyRenameObj -> Text
now :: Text
, KeyRenameObj -> Bool
overwrite :: Bool
, KeyRenameObj -> Text
was :: Text
}
deriving (Int -> KeyRenameObj -> ShowS
[KeyRenameObj] -> ShowS
KeyRenameObj -> String
(Int -> KeyRenameObj -> ShowS)
-> (KeyRenameObj -> String)
-> ([KeyRenameObj] -> ShowS)
-> Show KeyRenameObj
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [KeyRenameObj] -> ShowS
$cshowList :: [KeyRenameObj] -> ShowS
show :: KeyRenameObj -> String
$cshow :: KeyRenameObj -> String
showsPrec :: Int -> KeyRenameObj -> ShowS
$cshowsPrec :: Int -> KeyRenameObj -> ShowS
Show, KeyRenameObj -> KeyRenameObj -> Bool
(KeyRenameObj -> KeyRenameObj -> Bool)
-> (KeyRenameObj -> KeyRenameObj -> Bool) -> Eq KeyRenameObj
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: KeyRenameObj -> KeyRenameObj -> Bool
$c/= :: KeyRenameObj -> KeyRenameObj -> Bool
== :: KeyRenameObj -> KeyRenameObj -> Bool
$c== :: KeyRenameObj -> KeyRenameObj -> Bool
Eq)
data FilesStatObj = FilesStatObj
{ FilesStatObj -> Text
fileObjectHash :: Text
, FilesStatObj -> Int
objectSize :: Int
, FilesStatObj -> Int
cumulativeObjectSize :: Int
, FilesStatObj -> Int
blocks :: Int
, FilesStatObj -> Text
objectType :: Text
}
deriving (Int -> FilesStatObj -> ShowS
[FilesStatObj] -> ShowS
FilesStatObj -> String
(Int -> FilesStatObj -> ShowS)
-> (FilesStatObj -> String)
-> ([FilesStatObj] -> ShowS)
-> Show FilesStatObj
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [FilesStatObj] -> ShowS
$cshowList :: [FilesStatObj] -> ShowS
show :: FilesStatObj -> String
$cshow :: FilesStatObj -> String
showsPrec :: Int -> FilesStatObj -> ShowS
$cshowsPrec :: Int -> FilesStatObj -> ShowS
Show, FilesStatObj -> FilesStatObj -> Bool
(FilesStatObj -> FilesStatObj -> Bool)
-> (FilesStatObj -> FilesStatObj -> Bool) -> Eq FilesStatObj
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: FilesStatObj -> FilesStatObj -> Bool
$c/= :: FilesStatObj -> FilesStatObj -> Bool
== :: FilesStatObj -> FilesStatObj -> Bool
$c== :: FilesStatObj -> FilesStatObj -> Bool
Eq)
data FilesEntryObj = FilesEntryObj
{ FilesEntryObj -> Text
entryName :: Text
, FilesEntryObj -> Int
entryType :: Int
, FilesEntryObj -> Int
entrySize :: Int
, FilesEntryObj -> Text
entryHash :: Text
}
deriving (Int -> FilesEntryObj -> ShowS
[FilesEntryObj] -> ShowS
FilesEntryObj -> String
(Int -> FilesEntryObj -> ShowS)
-> (FilesEntryObj -> String)
-> ([FilesEntryObj] -> ShowS)
-> Show FilesEntryObj
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [FilesEntryObj] -> ShowS
$cshowList :: [FilesEntryObj] -> ShowS
show :: FilesEntryObj -> String
$cshow :: FilesEntryObj -> String
showsPrec :: Int -> FilesEntryObj -> ShowS
$cshowsPrec :: Int -> FilesEntryObj -> ShowS
Show, FilesEntryObj -> FilesEntryObj -> Bool
(FilesEntryObj -> FilesEntryObj -> Bool)
-> (FilesEntryObj -> FilesEntryObj -> Bool) -> Eq FilesEntryObj
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: FilesEntryObj -> FilesEntryObj -> Bool
$c/= :: FilesEntryObj -> FilesEntryObj -> Bool
== :: FilesEntryObj -> FilesEntryObj -> Bool
$c== :: FilesEntryObj -> FilesEntryObj -> Bool
Eq)
data FilesLsObj = FilesLsObj
{ FilesLsObj -> [FilesEntryObj]
enteries :: [FilesEntryObj]
}
deriving (Int -> FilesLsObj -> ShowS
[FilesLsObj] -> ShowS
FilesLsObj -> String
(Int -> FilesLsObj -> ShowS)
-> (FilesLsObj -> String)
-> ([FilesLsObj] -> ShowS)
-> Show FilesLsObj
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [FilesLsObj] -> ShowS
$cshowList :: [FilesLsObj] -> ShowS
show :: FilesLsObj -> String
$cshow :: FilesLsObj -> String
showsPrec :: Int -> FilesLsObj -> ShowS
$cshowsPrec :: Int -> FilesLsObj -> ShowS
Show, FilesLsObj -> FilesLsObj -> Bool
(FilesLsObj -> FilesLsObj -> Bool)
-> (FilesLsObj -> FilesLsObj -> Bool) -> Eq FilesLsObj
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: FilesLsObj -> FilesLsObj -> Bool
$c/= :: FilesLsObj -> FilesLsObj -> Bool
== :: FilesLsObj -> FilesLsObj -> Bool
$c== :: FilesLsObj -> FilesLsObj -> Bool
Eq)
data FilesFlushObj = FilesFlushObj
{ FilesFlushObj -> Text
fileCid :: Text
}
deriving (Int -> FilesFlushObj -> ShowS
[FilesFlushObj] -> ShowS
FilesFlushObj -> String
(Int -> FilesFlushObj -> ShowS)
-> (FilesFlushObj -> String)
-> ([FilesFlushObj] -> ShowS)
-> Show FilesFlushObj
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [FilesFlushObj] -> ShowS
$cshowList :: [FilesFlushObj] -> ShowS
show :: FilesFlushObj -> String
$cshow :: FilesFlushObj -> String
showsPrec :: Int -> FilesFlushObj -> ShowS
$cshowsPrec :: Int -> FilesFlushObj -> ShowS
Show, FilesFlushObj -> FilesFlushObj -> Bool
(FilesFlushObj -> FilesFlushObj -> Bool)
-> (FilesFlushObj -> FilesFlushObj -> Bool) -> Eq FilesFlushObj
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: FilesFlushObj -> FilesFlushObj -> Bool
$c/= :: FilesFlushObj -> FilesFlushObj -> Bool
== :: FilesFlushObj -> FilesFlushObj -> Bool
$c== :: FilesFlushObj -> FilesFlushObj -> Bool
Eq)
instance FromJSON DirLink where
parseJSON :: Value -> Parser DirLink
parseJSON (Object Object
o) =
Text -> Text -> Int64 -> Int -> Text -> DirLink
DirLink (Text -> Text -> Int64 -> Int -> Text -> DirLink)
-> Parser Text -> Parser (Text -> Int64 -> Int -> Text -> DirLink)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
o Object -> Text -> Parser Text
forall a. FromJSON a => Object -> Text -> Parser a
.: Text
"Name"
Parser (Text -> Int64 -> Int -> Text -> DirLink)
-> Parser Text -> Parser (Int64 -> Int -> Text -> DirLink)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object -> Text -> Parser Text
forall a. FromJSON a => Object -> Text -> Parser a
.: Text
"Hash"
Parser (Int64 -> Int -> Text -> DirLink)
-> Parser Int64 -> Parser (Int -> Text -> DirLink)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object -> Text -> Parser Int64
forall a. FromJSON a => Object -> Text -> Parser a
.: Text
"Size"
Parser (Int -> Text -> DirLink)
-> Parser Int -> Parser (Text -> DirLink)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object -> Text -> Parser Int
forall a. FromJSON a => Object -> Text -> Parser a
.: Text
"Type"
Parser (Text -> DirLink) -> Parser Text -> Parser DirLink
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object -> Text -> Parser Text
forall a. FromJSON a => Object -> Text -> Parser a
.: Text
"Target"
parseJSON Value
_ = Parser DirLink
forall (m :: * -> *) a. MonadPlus m => m a
mzero
instance FromJSON DirObj where
parseJSON :: Value -> Parser DirObj
parseJSON (Object Object
o) =
Text -> [DirLink] -> DirObj
DirObj (Text -> [DirLink] -> DirObj)
-> Parser Text -> Parser ([DirLink] -> DirObj)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
o Object -> Text -> Parser Text
forall a. FromJSON a => Object -> Text -> Parser a
.: Text
"Hash"
Parser ([DirLink] -> DirObj) -> Parser [DirLink] -> Parser DirObj
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object -> Text -> Parser [DirLink]
forall a. FromJSON a => Object -> Text -> Parser a
.: Text
"Links"
parseJSON Value
_ = Parser DirObj
forall (m :: * -> *) a. MonadPlus m => m a
mzero
instance FromJSON LsObj where
parseJSON :: Value -> Parser LsObj
parseJSON (Object Object
o) =
[DirObj] -> LsObj
LsObj ([DirObj] -> LsObj) -> Parser [DirObj] -> Parser LsObj
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
o Object -> Text -> Parser [DirObj]
forall a. FromJSON a => Object -> Text -> Parser a
.: Text
"Objects"
parseJSON Value
_ = Parser LsObj
forall (m :: * -> *) a. MonadPlus m => m a
mzero
instance FromJSON SwarmStreamObj where
parseJSON :: Value -> Parser SwarmStreamObj
parseJSON (Object Object
o) =
Text -> SwarmStreamObj
SwarmStreamObj (Text -> SwarmStreamObj) -> Parser Text -> Parser SwarmStreamObj
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
o Object -> Text -> Parser Text
forall a. FromJSON a => Object -> Text -> Parser a
.: Text
"Protocol"
parseJSON Value
_ = Parser SwarmStreamObj
forall (m :: * -> *) a. MonadPlus m => m a
mzero
instance FromJSON SwarmPeerObj where
parseJSON :: Value -> Parser SwarmPeerObj
parseJSON (Object Object
o) =
Text
-> Int
-> Text
-> Text
-> Text
-> Maybe [SwarmStreamObj]
-> SwarmPeerObj
SwarmPeerObj (Text
-> Int
-> Text
-> Text
-> Text
-> Maybe [SwarmStreamObj]
-> SwarmPeerObj)
-> Parser Text
-> Parser
(Int
-> Text -> Text -> Text -> Maybe [SwarmStreamObj] -> SwarmPeerObj)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
o Object -> Text -> Parser Text
forall a. FromJSON a => Object -> Text -> Parser a
.: Text
"Addr"
Parser
(Int
-> Text -> Text -> Text -> Maybe [SwarmStreamObj] -> SwarmPeerObj)
-> Parser Int
-> Parser
(Text -> Text -> Text -> Maybe [SwarmStreamObj] -> SwarmPeerObj)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object -> Text -> Parser Int
forall a. FromJSON a => Object -> Text -> Parser a
.: Text
"Direction"
Parser
(Text -> Text -> Text -> Maybe [SwarmStreamObj] -> SwarmPeerObj)
-> Parser Text
-> Parser (Text -> Text -> Maybe [SwarmStreamObj] -> SwarmPeerObj)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object -> Text -> Parser Text
forall a. FromJSON a => Object -> Text -> Parser a
.: Text
"Latency"
Parser (Text -> Text -> Maybe [SwarmStreamObj] -> SwarmPeerObj)
-> Parser Text
-> Parser (Text -> Maybe [SwarmStreamObj] -> SwarmPeerObj)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object -> Text -> Parser Text
forall a. FromJSON a => Object -> Text -> Parser a
.: Text
"Muxer"
Parser (Text -> Maybe [SwarmStreamObj] -> SwarmPeerObj)
-> Parser Text -> Parser (Maybe [SwarmStreamObj] -> SwarmPeerObj)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object -> Text -> Parser Text
forall a. FromJSON a => Object -> Text -> Parser a
.: Text
"Peer"
Parser (Maybe [SwarmStreamObj] -> SwarmPeerObj)
-> Parser (Maybe [SwarmStreamObj]) -> Parser SwarmPeerObj
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object -> Text -> Parser (Maybe [SwarmStreamObj])
forall a. FromJSON a => Object -> Text -> Parser a
.: Text
"Streams"
parseJSON Value
_ = Parser SwarmPeerObj
forall (m :: * -> *) a. MonadPlus m => m a
mzero
instance FromJSON SwarmPeersObj where
parseJSON :: Value -> Parser SwarmPeersObj
parseJSON (Object Object
o) =
[SwarmPeerObj] -> SwarmPeersObj
SwarmPeersObj ([SwarmPeerObj] -> SwarmPeersObj)
-> Parser [SwarmPeerObj] -> Parser SwarmPeersObj
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
o Object -> Text -> Parser [SwarmPeerObj]
forall a. FromJSON a => Object -> Text -> Parser a
.: Text
"Peers"
parseJSON Value
_ = Parser SwarmPeersObj
forall (m :: * -> *) a. MonadPlus m => m a
mzero
instance FromJSON SwarmObj where
parseJSON :: Value -> Parser SwarmObj
parseJSON (Object Object
o) =
[Text] -> SwarmObj
SwarmObj ([Text] -> SwarmObj) -> Parser [Text] -> Parser SwarmObj
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
o Object -> Text -> Parser [Text]
forall a. FromJSON a => Object -> Text -> Parser a
.: Text
"Strings"
parseJSON Value
_ = Parser SwarmObj
forall (m :: * -> *) a. MonadPlus m => m a
mzero
instance FromJSON WantlistObj where
parseJSON :: Value -> Parser WantlistObj
parseJSON (Object Object
o) =
Text -> WantlistObj
WantlistObj (Text -> WantlistObj) -> Parser Text -> Parser WantlistObj
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
o Object -> Text -> Parser Text
forall a. FromJSON a => Object -> Text -> Parser a
.: Text
"/"
parseJSON Value
_ = Parser WantlistObj
forall (m :: * -> *) a. MonadPlus m => m a
mzero
instance FromJSON BitswapStatObj where
parseJSON :: Value -> Parser BitswapStatObj
parseJSON (Object Object
o) =
Int64
-> Int64
-> Int64
-> Int64
-> Int64
-> Int64
-> Int64
-> [Text]
-> Int
-> [WantlistObj]
-> BitswapStatObj
BitswapStatObj (Int64
-> Int64
-> Int64
-> Int64
-> Int64
-> Int64
-> Int64
-> [Text]
-> Int
-> [WantlistObj]
-> BitswapStatObj)
-> Parser Int64
-> Parser
(Int64
-> Int64
-> Int64
-> Int64
-> Int64
-> Int64
-> [Text]
-> Int
-> [WantlistObj]
-> BitswapStatObj)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
o Object -> Text -> Parser Int64
forall a. FromJSON a => Object -> Text -> Parser a
.: Text
"BlocksReceived"
Parser
(Int64
-> Int64
-> Int64
-> Int64
-> Int64
-> Int64
-> [Text]
-> Int
-> [WantlistObj]
-> BitswapStatObj)
-> Parser Int64
-> Parser
(Int64
-> Int64
-> Int64
-> Int64
-> Int64
-> [Text]
-> Int
-> [WantlistObj]
-> BitswapStatObj)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object -> Text -> Parser Int64
forall a. FromJSON a => Object -> Text -> Parser a
.: Text
"BlocksSent"
Parser
(Int64
-> Int64
-> Int64
-> Int64
-> Int64
-> [Text]
-> Int
-> [WantlistObj]
-> BitswapStatObj)
-> Parser Int64
-> Parser
(Int64
-> Int64
-> Int64
-> Int64
-> [Text]
-> Int
-> [WantlistObj]
-> BitswapStatObj)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object -> Text -> Parser Int64
forall a. FromJSON a => Object -> Text -> Parser a
.: Text
"DataReceived"
Parser
(Int64
-> Int64
-> Int64
-> Int64
-> [Text]
-> Int
-> [WantlistObj]
-> BitswapStatObj)
-> Parser Int64
-> Parser
(Int64
-> Int64
-> Int64
-> [Text]
-> Int
-> [WantlistObj]
-> BitswapStatObj)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object -> Text -> Parser Int64
forall a. FromJSON a => Object -> Text -> Parser a
.: Text
"DataSent"
Parser
(Int64
-> Int64
-> Int64
-> [Text]
-> Int
-> [WantlistObj]
-> BitswapStatObj)
-> Parser Int64
-> Parser
(Int64
-> Int64 -> [Text] -> Int -> [WantlistObj] -> BitswapStatObj)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object -> Text -> Parser Int64
forall a. FromJSON a => Object -> Text -> Parser a
.: Text
"DupBlksReceived"
Parser
(Int64
-> Int64 -> [Text] -> Int -> [WantlistObj] -> BitswapStatObj)
-> Parser Int64
-> Parser
(Int64 -> [Text] -> Int -> [WantlistObj] -> BitswapStatObj)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object -> Text -> Parser Int64
forall a. FromJSON a => Object -> Text -> Parser a
.: Text
"DupDataReceived"
Parser (Int64 -> [Text] -> Int -> [WantlistObj] -> BitswapStatObj)
-> Parser Int64
-> Parser ([Text] -> Int -> [WantlistObj] -> BitswapStatObj)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object -> Text -> Parser Int64
forall a. FromJSON a => Object -> Text -> Parser a
.: Text
"MessagesReceived"
Parser ([Text] -> Int -> [WantlistObj] -> BitswapStatObj)
-> Parser [Text] -> Parser (Int -> [WantlistObj] -> BitswapStatObj)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object -> Text -> Parser [Text]
forall a. FromJSON a => Object -> Text -> Parser a
.: Text
"Peers"
Parser (Int -> [WantlistObj] -> BitswapStatObj)
-> Parser Int -> Parser ([WantlistObj] -> BitswapStatObj)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object -> Text -> Parser Int
forall a. FromJSON a => Object -> Text -> Parser a
.: Text
"ProvideBufLen"
Parser ([WantlistObj] -> BitswapStatObj)
-> Parser [WantlistObj] -> Parser BitswapStatObj
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object -> Text -> Parser [WantlistObj]
forall a. FromJSON a => Object -> Text -> Parser a
.: Text
"Wantlist"
parseJSON Value
_ = Parser BitswapStatObj
forall (m :: * -> *) a. MonadPlus m => m a
mzero
instance FromJSON BitswapWLObj where
parseJSON :: Value -> Parser BitswapWLObj
parseJSON (Object Object
o) =
[WantlistObj] -> BitswapWLObj
BitswapWLObj ([WantlistObj] -> BitswapWLObj)
-> Parser [WantlistObj] -> Parser BitswapWLObj
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
o Object -> Text -> Parser [WantlistObj]
forall a. FromJSON a => Object -> Text -> Parser a
.: Text
"Keys"
parseJSON Value
_ = Parser BitswapWLObj
forall (m :: * -> *) a. MonadPlus m => m a
mzero
instance FromJSON BitswapLedgerObj where
parseJSON :: Value -> Parser BitswapLedgerObj
parseJSON (Object Object
o) =
Int64 -> Text -> Int64 -> Int64 -> Double -> BitswapLedgerObj
BitswapLedgerObj (Int64 -> Text -> Int64 -> Int64 -> Double -> BitswapLedgerObj)
-> Parser Int64
-> Parser (Text -> Int64 -> Int64 -> Double -> BitswapLedgerObj)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
o Object -> Text -> Parser Int64
forall a. FromJSON a => Object -> Text -> Parser a
.: Text
"Exchanged"
Parser (Text -> Int64 -> Int64 -> Double -> BitswapLedgerObj)
-> Parser Text
-> Parser (Int64 -> Int64 -> Double -> BitswapLedgerObj)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object -> Text -> Parser Text
forall a. FromJSON a => Object -> Text -> Parser a
.: Text
"Peer"
Parser (Int64 -> Int64 -> Double -> BitswapLedgerObj)
-> Parser Int64 -> Parser (Int64 -> Double -> BitswapLedgerObj)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object -> Text -> Parser Int64
forall a. FromJSON a => Object -> Text -> Parser a
.: Text
"Recv"
Parser (Int64 -> Double -> BitswapLedgerObj)
-> Parser Int64 -> Parser (Double -> BitswapLedgerObj)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object -> Text -> Parser Int64
forall a. FromJSON a => Object -> Text -> Parser a
.: Text
"Sent"
Parser (Double -> BitswapLedgerObj)
-> Parser Double -> Parser BitswapLedgerObj
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object -> Text -> Parser Double
forall a. FromJSON a => Object -> Text -> Parser a
.: Text
"Value"
parseJSON Value
_ = Parser BitswapLedgerObj
forall (m :: * -> *) a. MonadPlus m => m a
mzero
instance FromJSON CidBasesObj where
parseJSON :: Value -> Parser CidBasesObj
parseJSON (Object Object
o) =
Int -> Text -> CidBasesObj
CidBasesObj (Int -> Text -> CidBasesObj)
-> Parser Int -> Parser (Text -> CidBasesObj)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
o Object -> Text -> Parser Int
forall a. FromJSON a => Object -> Text -> Parser a
.: Text
"Code"
Parser (Text -> CidBasesObj) -> Parser Text -> Parser CidBasesObj
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object -> Text -> Parser Text
forall a. FromJSON a => Object -> Text -> Parser a
.: Text
"Name"
parseJSON Value
_ = Parser CidBasesObj
forall (m :: * -> *) a. MonadPlus m => m a
mzero
instance FromJSON CidCodecsObj where
parseJSON :: Value -> Parser CidCodecsObj
parseJSON (Object Object
o) =
Int -> Text -> CidCodecsObj
CidCodecsObj (Int -> Text -> CidCodecsObj)
-> Parser Int -> Parser (Text -> CidCodecsObj)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
o Object -> Text -> Parser Int
forall a. FromJSON a => Object -> Text -> Parser a
.: Text
"Code"
Parser (Text -> CidCodecsObj) -> Parser Text -> Parser CidCodecsObj
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object -> Text -> Parser Text
forall a. FromJSON a => Object -> Text -> Parser a
.: Text
"Name"
parseJSON Value
_ = Parser CidCodecsObj
forall (m :: * -> *) a. MonadPlus m => m a
mzero
instance FromJSON CidHashesObj where
parseJSON :: Value -> Parser CidHashesObj
parseJSON (Object Object
o) =
Int -> Text -> CidHashesObj
CidHashesObj (Int -> Text -> CidHashesObj)
-> Parser Int -> Parser (Text -> CidHashesObj)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
o Object -> Text -> Parser Int
forall a. FromJSON a => Object -> Text -> Parser a
.: Text
"Code"
Parser (Text -> CidHashesObj) -> Parser Text -> Parser CidHashesObj
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object -> Text -> Parser Text
forall a. FromJSON a => Object -> Text -> Parser a
.: Text
"Name"
parseJSON Value
_ = Parser CidHashesObj
forall (m :: * -> *) a. MonadPlus m => m a
mzero
instance FromJSON CidObj where
parseJSON :: Value -> Parser CidObj
parseJSON (Object Object
o) =
Text -> Text -> Text -> CidObj
CidObj (Text -> Text -> Text -> CidObj)
-> Parser Text -> Parser (Text -> Text -> CidObj)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
o Object -> Text -> Parser Text
forall a. FromJSON a => Object -> Text -> Parser a
.: Text
"CidStr"
Parser (Text -> Text -> CidObj)
-> Parser Text -> Parser (Text -> CidObj)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object -> Text -> Parser Text
forall a. FromJSON a => Object -> Text -> Parser a
.: Text
"ErrorMsg"
Parser (Text -> CidObj) -> Parser Text -> Parser CidObj
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object -> Text -> Parser Text
forall a. FromJSON a => Object -> Text -> Parser a
.: Text
"Formatted"
parseJSON Value
_ = Parser CidObj
forall (m :: * -> *) a. MonadPlus m => m a
mzero
instance FromJSON BlockObj where
parseJSON :: Value -> Parser BlockObj
parseJSON (Object Object
o) =
Text -> Int -> BlockObj
BlockObj (Text -> Int -> BlockObj)
-> Parser Text -> Parser (Int -> BlockObj)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
o Object -> Text -> Parser Text
forall a. FromJSON a => Object -> Text -> Parser a
.: Text
"Key"
Parser (Int -> BlockObj) -> Parser Int -> Parser BlockObj
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object -> Text -> Parser Int
forall a. FromJSON a => Object -> Text -> Parser a
.: Text
"Size"
parseJSON Value
_ = Parser BlockObj
forall (m :: * -> *) a. MonadPlus m => m a
mzero
instance FromJSON DagCidObj where
parseJSON :: Value -> Parser DagCidObj
parseJSON (Object Object
o) =
Text -> DagCidObj
DagCidObj (Text -> DagCidObj) -> Parser Text -> Parser DagCidObj
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
o Object -> Text -> Parser Text
forall a. FromJSON a => Object -> Text -> Parser a
.: Text
"/"
parseJSON Value
_ = Parser DagCidObj
forall (m :: * -> *) a. MonadPlus m => m a
mzero
instance FromJSON DagResolveObj where
parseJSON :: Value -> Parser DagResolveObj
parseJSON (Object Object
o) =
DagCidObj -> Text -> DagResolveObj
DagResolveObj (DagCidObj -> Text -> DagResolveObj)
-> Parser DagCidObj -> Parser (Text -> DagResolveObj)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
o Object -> Text -> Parser DagCidObj
forall a. FromJSON a => Object -> Text -> Parser a
.: Text
"Cid"
Parser (Text -> DagResolveObj)
-> Parser Text -> Parser DagResolveObj
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object -> Text -> Parser Text
forall a. FromJSON a => Object -> Text -> Parser a
.: Text
"RemPath"
parseJSON Value
_ = Parser DagResolveObj
forall (m :: * -> *) a. MonadPlus m => m a
mzero
instance FromJSON DagPutObj where
parseJSON :: Value -> Parser DagPutObj
parseJSON (Object Object
o) =
DagCidObj -> DagPutObj
DagPutObj (DagCidObj -> DagPutObj) -> Parser DagCidObj -> Parser DagPutObj
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
o Object -> Text -> Parser DagCidObj
forall a. FromJSON a => Object -> Text -> Parser a
.: Text
"Cid"
parseJSON Value
_ = Parser DagPutObj
forall (m :: * -> *) a. MonadPlus m => m a
mzero
instance FromJSON ConfigObj where
parseJSON :: Value -> Parser ConfigObj
parseJSON (Object Object
o) =
Text -> Text -> ConfigObj
ConfigObj (Text -> Text -> ConfigObj)
-> Parser Text -> Parser (Text -> ConfigObj)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
o Object -> Text -> Parser Text
forall a. FromJSON a => Object -> Text -> Parser a
.: Text
"Key"
Parser (Text -> ConfigObj) -> Parser Text -> Parser ConfigObj
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object -> Text -> Parser Text
forall a. FromJSON a => Object -> Text -> Parser a
.: Text
"Value"
parseJSON Value
_ = Parser ConfigObj
forall (m :: * -> *) a. MonadPlus m => m a
mzero
instance FromJSON ObjectLinkObj where
parseJSON :: Value -> Parser ObjectLinkObj
parseJSON (Object Object
o) =
Text -> Text -> Int64 -> ObjectLinkObj
ObjectLinkObj (Text -> Text -> Int64 -> ObjectLinkObj)
-> Parser Text -> Parser (Text -> Int64 -> ObjectLinkObj)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
o Object -> Text -> Parser Text
forall a. FromJSON a => Object -> Text -> Parser a
.: Text
"Hash"
Parser (Text -> Int64 -> ObjectLinkObj)
-> Parser Text -> Parser (Int64 -> ObjectLinkObj)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object -> Text -> Parser Text
forall a. FromJSON a => Object -> Text -> Parser a
.: Text
"Name"
Parser (Int64 -> ObjectLinkObj)
-> Parser Int64 -> Parser ObjectLinkObj
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object -> Text -> Parser Int64
forall a. FromJSON a => Object -> Text -> Parser a
.: Text
"Size"
parseJSON Value
_ = Parser ObjectLinkObj
forall (m :: * -> *) a. MonadPlus m => m a
mzero
instance FromJSON ObjectObj where
parseJSON :: Value -> Parser ObjectObj
parseJSON (Object Object
o) =
Text -> ObjectObj
ObjectObj (Text -> ObjectObj) -> Parser Text -> Parser ObjectObj
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
o Object -> Text -> Parser Text
forall a. FromJSON a => Object -> Text -> Parser a
.: Text
"Hash"
parseJSON Value
_ = Parser ObjectObj
forall (m :: * -> *) a. MonadPlus m => m a
mzero
instance FromJSON ObjectLinksObj where
parseJSON :: Value -> Parser ObjectLinksObj
parseJSON (Object Object
v) =
case Text -> Object -> Maybe Value
forall k v. (Eq k, Hashable k) => k -> HashMap k v -> Maybe v
H.lookup Text
"Links" Object
v of
Just (Value
_) -> Text -> [ObjectLinkObj] -> ObjectLinksObj
WithLinks (Text -> [ObjectLinkObj] -> ObjectLinksObj)
-> Parser Text -> Parser ([ObjectLinkObj] -> ObjectLinksObj)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
v Object -> Text -> Parser Text
forall a. FromJSON a => Object -> Text -> Parser a
.: Text
"Hash"
Parser ([ObjectLinkObj] -> ObjectLinksObj)
-> Parser [ObjectLinkObj] -> Parser ObjectLinksObj
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
v Object -> Text -> Parser [ObjectLinkObj]
forall a. FromJSON a => Object -> Text -> Parser a
.: Text
"Links"
Maybe Value
Nothing ->
case Text -> Object -> Maybe Value
forall k v. (Eq k, Hashable k) => k -> HashMap k v -> Maybe v
H.lookup Text
"Hash" Object
v of
Just (Value
_) -> Text -> ObjectLinksObj
WithoutLinks (Text -> ObjectLinksObj) -> Parser Text -> Parser ObjectLinksObj
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
v Object -> Text -> Parser Text
forall a. FromJSON a => Object -> Text -> Parser a
.: Text
"Hash"
Maybe Value
Nothing -> Parser ObjectLinksObj
forall (m :: * -> *) a. MonadPlus m => m a
mzero
parseJSON Value
_ = Parser ObjectLinksObj
forall (m :: * -> *) a. MonadPlus m => m a
mzero
instance FromJSON ObjectGetObj where
parseJSON :: Value -> Parser ObjectGetObj
parseJSON (Object Object
o) =
Text -> [ObjectLinkObj] -> ObjectGetObj
ObjectGetObj (Text -> [ObjectLinkObj] -> ObjectGetObj)
-> Parser Text -> Parser ([ObjectLinkObj] -> ObjectGetObj)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
o Object -> Text -> Parser Text
forall a. FromJSON a => Object -> Text -> Parser a
.: Text
"Data"
Parser ([ObjectLinkObj] -> ObjectGetObj)
-> Parser [ObjectLinkObj] -> Parser ObjectGetObj
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object -> Text -> Parser [ObjectLinkObj]
forall a. FromJSON a => Object -> Text -> Parser a
.: Text
"Links"
parseJSON Value
_ = Parser ObjectGetObj
forall (m :: * -> *) a. MonadPlus m => m a
mzero
instance FromJSON ObjectStatObj where
parseJSON :: Value -> Parser ObjectStatObj
parseJSON (Object Object
o) =
Int -> Int -> Int -> Text -> Int -> Int -> ObjectStatObj
ObjectStatObj (Int -> Int -> Int -> Text -> Int -> Int -> ObjectStatObj)
-> Parser Int
-> Parser (Int -> Int -> Text -> Int -> Int -> ObjectStatObj)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
o Object -> Text -> Parser Int
forall a. FromJSON a => Object -> Text -> Parser a
.: Text
"BlockSize"
Parser (Int -> Int -> Text -> Int -> Int -> ObjectStatObj)
-> Parser Int
-> Parser (Int -> Text -> Int -> Int -> ObjectStatObj)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object -> Text -> Parser Int
forall a. FromJSON a => Object -> Text -> Parser a
.: Text
"CumulativeSize"
Parser (Int -> Text -> Int -> Int -> ObjectStatObj)
-> Parser Int -> Parser (Text -> Int -> Int -> ObjectStatObj)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object -> Text -> Parser Int
forall a. FromJSON a => Object -> Text -> Parser a
.: Text
"DataSize"
Parser (Text -> Int -> Int -> ObjectStatObj)
-> Parser Text -> Parser (Int -> Int -> ObjectStatObj)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object -> Text -> Parser Text
forall a. FromJSON a => Object -> Text -> Parser a
.: Text
"Hash"
Parser (Int -> Int -> ObjectStatObj)
-> Parser Int -> Parser (Int -> ObjectStatObj)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object -> Text -> Parser Int
forall a. FromJSON a => Object -> Text -> Parser a
.: Text
"LinksSize"
Parser (Int -> ObjectStatObj) -> Parser Int -> Parser ObjectStatObj
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object -> Text -> Parser Int
forall a. FromJSON a => Object -> Text -> Parser a
.: Text
"NumLinks"
parseJSON Value
_ = Parser ObjectStatObj
forall (m :: * -> *) a. MonadPlus m => m a
mzero
instance FromJSON ObjectChangeObj where
parseJSON :: Value -> Parser ObjectChangeObj
parseJSON (Object Object
o) =
Maybe DiffObj -> DiffObj -> Text -> Int -> ObjectChangeObj
ObjectChangeObj (Maybe DiffObj -> DiffObj -> Text -> Int -> ObjectChangeObj)
-> Parser (Maybe DiffObj)
-> Parser (DiffObj -> Text -> Int -> ObjectChangeObj)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
o Object -> Text -> Parser (Maybe DiffObj)
forall a. FromJSON a => Object -> Text -> Parser a
.: Text
"After"
Parser (DiffObj -> Text -> Int -> ObjectChangeObj)
-> Parser DiffObj -> Parser (Text -> Int -> ObjectChangeObj)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object -> Text -> Parser DiffObj
forall a. FromJSON a => Object -> Text -> Parser a
.: Text
"Before"
Parser (Text -> Int -> ObjectChangeObj)
-> Parser Text -> Parser (Int -> ObjectChangeObj)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object -> Text -> Parser Text
forall a. FromJSON a => Object -> Text -> Parser a
.: Text
"Path"
Parser (Int -> ObjectChangeObj)
-> Parser Int -> Parser ObjectChangeObj
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object -> Text -> Parser Int
forall a. FromJSON a => Object -> Text -> Parser a
.: Text
"Type"
parseJSON Value
_ = Parser ObjectChangeObj
forall (m :: * -> *) a. MonadPlus m => m a
mzero
instance FromJSON DiffObj where
parseJSON :: Value -> Parser DiffObj
parseJSON (Object Object
o) =
Text -> DiffObj
DiffObj (Text -> DiffObj) -> Parser Text -> Parser DiffObj
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
o Object -> Text -> Parser Text
forall a. FromJSON a => Object -> Text -> Parser a
.: Text
"/"
parseJSON Value
_ = Parser DiffObj
forall (m :: * -> *) a. MonadPlus m => m a
mzero
instance FromJSON ObjectDiffObj where
parseJSON :: Value -> Parser ObjectDiffObj
parseJSON (Object Object
o) =
[ObjectChangeObj] -> ObjectDiffObj
ObjectDiffObj ([ObjectChangeObj] -> ObjectDiffObj)
-> Parser [ObjectChangeObj] -> Parser ObjectDiffObj
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
o Object -> Text -> Parser [ObjectChangeObj]
forall a. FromJSON a => Object -> Text -> Parser a
.: Text
"Changes"
parseJSON Value
_ = Parser ObjectDiffObj
forall (m :: * -> *) a. MonadPlus m => m a
mzero
instance FromJSON PinObj where
parseJSON :: Value -> Parser PinObj
parseJSON (Object Object
v) =
case Text -> Object -> Maybe Value
forall k v. (Eq k, Hashable k) => k -> HashMap k v -> Maybe v
H.lookup Text
"Progress" Object
v of
Just (Value
_) -> [Text] -> Int -> PinObj
WithProgress ([Text] -> Int -> PinObj)
-> Parser [Text] -> Parser (Int -> PinObj)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
v Object -> Text -> Parser [Text]
forall a. FromJSON a => Object -> Text -> Parser a
.: Text
"Pins"
Parser (Int -> PinObj) -> Parser Int -> Parser PinObj
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
v Object -> Text -> Parser Int
forall a. FromJSON a => Object -> Text -> Parser a
.: Text
"Progress"
Maybe Value
Nothing ->
case Text -> Object -> Maybe Value
forall k v. (Eq k, Hashable k) => k -> HashMap k v -> Maybe v
H.lookup Text
"Pins" Object
v of
Just (Value
_) -> [Text] -> PinObj
WithoutProgress ([Text] -> PinObj) -> Parser [Text] -> Parser PinObj
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
v Object -> Text -> Parser [Text]
forall a. FromJSON a => Object -> Text -> Parser a
.: Text
"Pins"
Maybe Value
Nothing -> Parser PinObj
forall (m :: * -> *) a. MonadPlus m => m a
mzero
parseJSON Value
_ = Parser PinObj
forall (m :: * -> *) a. MonadPlus m => m a
mzero
instance FromJSON BootstrapObj where
parseJSON :: Value -> Parser BootstrapObj
parseJSON (Object Object
o) =
[Text] -> BootstrapObj
BootstrapObj ([Text] -> BootstrapObj) -> Parser [Text] -> Parser BootstrapObj
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
o Object -> Text -> Parser [Text]
forall a. FromJSON a => Object -> Text -> Parser a
.: Text
"Peers"
parseJSON Value
_ = Parser BootstrapObj
forall (m :: * -> *) a. MonadPlus m => m a
mzero
instance FromJSON StatsBwObj where
parseJSON :: Value -> Parser StatsBwObj
parseJSON (Object Object
o) =
Double -> Double -> Int64 -> Int64 -> StatsBwObj
StatsBwObj (Double -> Double -> Int64 -> Int64 -> StatsBwObj)
-> Parser Double -> Parser (Double -> Int64 -> Int64 -> StatsBwObj)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
o Object -> Text -> Parser Double
forall a. FromJSON a => Object -> Text -> Parser a
.: Text
"RateIn"
Parser (Double -> Int64 -> Int64 -> StatsBwObj)
-> Parser Double -> Parser (Int64 -> Int64 -> StatsBwObj)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object -> Text -> Parser Double
forall a. FromJSON a => Object -> Text -> Parser a
.: Text
"RateOut"
Parser (Int64 -> Int64 -> StatsBwObj)
-> Parser Int64 -> Parser (Int64 -> StatsBwObj)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object -> Text -> Parser Int64
forall a. FromJSON a => Object -> Text -> Parser a
.: Text
"TotalIn"
Parser (Int64 -> StatsBwObj) -> Parser Int64 -> Parser StatsBwObj
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object -> Text -> Parser Int64
forall a. FromJSON a => Object -> Text -> Parser a
.: Text
"TotalOut"
parseJSON Value
_ = Parser StatsBwObj
forall (m :: * -> *) a. MonadPlus m => m a
mzero
instance FromJSON StatsRepoObj where
parseJSON :: Value -> Parser StatsRepoObj
parseJSON (Object Object
o) =
Int64 -> Text -> Int64 -> Int64 -> Text -> StatsRepoObj
StatsRepoObj (Int64 -> Text -> Int64 -> Int64 -> Text -> StatsRepoObj)
-> Parser Int64
-> Parser (Text -> Int64 -> Int64 -> Text -> StatsRepoObj)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
o Object -> Text -> Parser Int64
forall a. FromJSON a => Object -> Text -> Parser a
.: Text
"NumObjects"
Parser (Text -> Int64 -> Int64 -> Text -> StatsRepoObj)
-> Parser Text -> Parser (Int64 -> Int64 -> Text -> StatsRepoObj)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object -> Text -> Parser Text
forall a. FromJSON a => Object -> Text -> Parser a
.: Text
"RepoPath"
Parser (Int64 -> Int64 -> Text -> StatsRepoObj)
-> Parser Int64 -> Parser (Int64 -> Text -> StatsRepoObj)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object -> Text -> Parser Int64
forall a. FromJSON a => Object -> Text -> Parser a
.: Text
"RepoSize"
Parser (Int64 -> Text -> StatsRepoObj)
-> Parser Int64 -> Parser (Text -> StatsRepoObj)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object -> Text -> Parser Int64
forall a. FromJSON a => Object -> Text -> Parser a
.: Text
"StorageMax"
Parser (Text -> StatsRepoObj) -> Parser Text -> Parser StatsRepoObj
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object -> Text -> Parser Text
forall a. FromJSON a => Object -> Text -> Parser a
.: Text
"Version"
parseJSON Value
_ = Parser StatsRepoObj
forall (m :: * -> *) a. MonadPlus m => m a
mzero
instance FromJSON VersionObj where
parseJSON :: Value -> Parser VersionObj
parseJSON (Object Object
o) =
Text -> Text -> Text -> Text -> Text -> VersionObj
VersionObj (Text -> Text -> Text -> Text -> Text -> VersionObj)
-> Parser Text
-> Parser (Text -> Text -> Text -> Text -> VersionObj)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
o Object -> Text -> Parser Text
forall a. FromJSON a => Object -> Text -> Parser a
.: Text
"Commit"
Parser (Text -> Text -> Text -> Text -> VersionObj)
-> Parser Text -> Parser (Text -> Text -> Text -> VersionObj)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object -> Text -> Parser Text
forall a. FromJSON a => Object -> Text -> Parser a
.: Text
"Golang"
Parser (Text -> Text -> Text -> VersionObj)
-> Parser Text -> Parser (Text -> Text -> VersionObj)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object -> Text -> Parser Text
forall a. FromJSON a => Object -> Text -> Parser a
.: Text
"Repo"
Parser (Text -> Text -> VersionObj)
-> Parser Text -> Parser (Text -> VersionObj)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object -> Text -> Parser Text
forall a. FromJSON a => Object -> Text -> Parser a
.: Text
"System"
Parser (Text -> VersionObj) -> Parser Text -> Parser VersionObj
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object -> Text -> Parser Text
forall a. FromJSON a => Object -> Text -> Parser a
.: Text
"Version"
parseJSON Value
_ = Parser VersionObj
forall (m :: * -> *) a. MonadPlus m => m a
mzero
instance FromJSON IdObj where
parseJSON :: Value -> Parser IdObj
parseJSON (Object Object
o) =
[Text] -> Text -> Text -> Text -> Text -> IdObj
IdObj ([Text] -> Text -> Text -> Text -> Text -> IdObj)
-> Parser [Text] -> Parser (Text -> Text -> Text -> Text -> IdObj)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
o Object -> Text -> Parser [Text]
forall a. FromJSON a => Object -> Text -> Parser a
.: Text
"Addresses"
Parser (Text -> Text -> Text -> Text -> IdObj)
-> Parser Text -> Parser (Text -> Text -> Text -> IdObj)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object -> Text -> Parser Text
forall a. FromJSON a => Object -> Text -> Parser a
.: Text
"AgentVersion"
Parser (Text -> Text -> Text -> IdObj)
-> Parser Text -> Parser (Text -> Text -> IdObj)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object -> Text -> Parser Text
forall a. FromJSON a => Object -> Text -> Parser a
.: Text
"ID"
Parser (Text -> Text -> IdObj)
-> Parser Text -> Parser (Text -> IdObj)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object -> Text -> Parser Text
forall a. FromJSON a => Object -> Text -> Parser a
.: Text
"ProtocolVersion"
Parser (Text -> IdObj) -> Parser Text -> Parser IdObj
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object -> Text -> Parser Text
forall a. FromJSON a => Object -> Text -> Parser a
.: Text
"PublicKey"
parseJSON Value
_ = Parser IdObj
forall (m :: * -> *) a. MonadPlus m => m a
mzero
instance FromJSON DnsObj where
parseJSON :: Value -> Parser DnsObj
parseJSON (Object Object
o) =
Text -> DnsObj
DnsObj (Text -> DnsObj) -> Parser Text -> Parser DnsObj
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
o Object -> Text -> Parser Text
forall a. FromJSON a => Object -> Text -> Parser a
.: Text
"Path"
parseJSON Value
_ = Parser DnsObj
forall (m :: * -> *) a. MonadPlus m => m a
mzero
instance FromJSON PubsubObj where
parseJSON :: Value -> Parser PubsubObj
parseJSON (Object Object
o) =
[Text] -> PubsubObj
PubsubObj ([Text] -> PubsubObj) -> Parser [Text] -> Parser PubsubObj
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
o Object -> Text -> Parser [Text]
forall a. FromJSON a => Object -> Text -> Parser a
.: Text
"Strings"
parseJSON Value
_ = Parser PubsubObj
forall (m :: * -> *) a. MonadPlus m => m a
mzero
instance FromJSON LogLsObj where
parseJSON :: Value -> Parser LogLsObj
parseJSON (Object Object
o) =
[Text] -> LogLsObj
LogLsObj ([Text] -> LogLsObj) -> Parser [Text] -> Parser LogLsObj
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
o Object -> Text -> Parser [Text]
forall a. FromJSON a => Object -> Text -> Parser a
.: Text
"Strings"
parseJSON Value
_ = Parser LogLsObj
forall (m :: * -> *) a. MonadPlus m => m a
mzero
instance FromJSON LogLevelObj where
parseJSON :: Value -> Parser LogLevelObj
parseJSON (Object Object
o) =
Text -> LogLevelObj
LogLevelObj (Text -> LogLevelObj) -> Parser Text -> Parser LogLevelObj
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
o Object -> Text -> Parser Text
forall a. FromJSON a => Object -> Text -> Parser a
.: Text
"Message"
parseJSON Value
_ = Parser LogLevelObj
forall (m :: * -> *) a. MonadPlus m => m a
mzero
instance FromJSON RepoVersionObj where
parseJSON :: Value -> Parser RepoVersionObj
parseJSON (Object Object
o) =
Text -> RepoVersionObj
RepoVersionObj (Text -> RepoVersionObj) -> Parser Text -> Parser RepoVersionObj
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
o Object -> Text -> Parser Text
forall a. FromJSON a => Object -> Text -> Parser a
.: Text
"Version"
parseJSON Value
_ = Parser RepoVersionObj
forall (m :: * -> *) a. MonadPlus m => m a
mzero
instance FromJSON RepoFsckObj where
parseJSON :: Value -> Parser RepoFsckObj
parseJSON (Object Object
o) =
Text -> RepoFsckObj
RepoFsckObj (Text -> RepoFsckObj) -> Parser Text -> Parser RepoFsckObj
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
o Object -> Text -> Parser Text
forall a. FromJSON a => Object -> Text -> Parser a
.: Text
"Message"
parseJSON Value
_ = Parser RepoFsckObj
forall (m :: * -> *) a. MonadPlus m => m a
mzero
instance FromJSON KeyDetailsObj where
parseJSON :: Value -> Parser KeyDetailsObj
parseJSON (Object Object
o) =
Text -> Text -> KeyDetailsObj
KeyDetailsObj (Text -> Text -> KeyDetailsObj)
-> Parser Text -> Parser (Text -> KeyDetailsObj)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
o Object -> Text -> Parser Text
forall a. FromJSON a => Object -> Text -> Parser a
.: Text
"Id"
Parser (Text -> KeyDetailsObj)
-> Parser Text -> Parser KeyDetailsObj
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object -> Text -> Parser Text
forall a. FromJSON a => Object -> Text -> Parser a
.: Text
"Name"
parseJSON Value
_ = Parser KeyDetailsObj
forall (m :: * -> *) a. MonadPlus m => m a
mzero
instance FromJSON KeyObj where
parseJSON :: Value -> Parser KeyObj
parseJSON (Object Object
o) =
[KeyDetailsObj] -> KeyObj
KeyObj ([KeyDetailsObj] -> KeyObj)
-> Parser [KeyDetailsObj] -> Parser KeyObj
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
o Object -> Text -> Parser [KeyDetailsObj]
forall a. FromJSON a => Object -> Text -> Parser a
.: Text
"Keys"
parseJSON Value
_ = Parser KeyObj
forall (m :: * -> *) a. MonadPlus m => m a
mzero
instance FromJSON KeyRenameObj where
parseJSON :: Value -> Parser KeyRenameObj
parseJSON (Object Object
o) =
Text -> Text -> Bool -> Text -> KeyRenameObj
KeyRenameObj (Text -> Text -> Bool -> Text -> KeyRenameObj)
-> Parser Text -> Parser (Text -> Bool -> Text -> KeyRenameObj)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
o Object -> Text -> Parser Text
forall a. FromJSON a => Object -> Text -> Parser a
.: Text
"Id"
Parser (Text -> Bool -> Text -> KeyRenameObj)
-> Parser Text -> Parser (Bool -> Text -> KeyRenameObj)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object -> Text -> Parser Text
forall a. FromJSON a => Object -> Text -> Parser a
.: Text
"Now"
Parser (Bool -> Text -> KeyRenameObj)
-> Parser Bool -> Parser (Text -> KeyRenameObj)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object -> Text -> Parser Bool
forall a. FromJSON a => Object -> Text -> Parser a
.: Text
"Overwrite"
Parser (Text -> KeyRenameObj) -> Parser Text -> Parser KeyRenameObj
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object -> Text -> Parser Text
forall a. FromJSON a => Object -> Text -> Parser a
.: Text
"Was"
parseJSON Value
_ = Parser KeyRenameObj
forall (m :: * -> *) a. MonadPlus m => m a
mzero
instance FromJSON FilesStatObj where
parseJSON :: Value -> Parser FilesStatObj
parseJSON (Object Object
o) =
Text -> Int -> Int -> Int -> Text -> FilesStatObj
FilesStatObj (Text -> Int -> Int -> Int -> Text -> FilesStatObj)
-> Parser Text
-> Parser (Int -> Int -> Int -> Text -> FilesStatObj)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
o Object -> Text -> Parser Text
forall a. FromJSON a => Object -> Text -> Parser a
.: Text
"Hash"
Parser (Int -> Int -> Int -> Text -> FilesStatObj)
-> Parser Int -> Parser (Int -> Int -> Text -> FilesStatObj)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object -> Text -> Parser Int
forall a. FromJSON a => Object -> Text -> Parser a
.: Text
"Size"
Parser (Int -> Int -> Text -> FilesStatObj)
-> Parser Int -> Parser (Int -> Text -> FilesStatObj)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object -> Text -> Parser Int
forall a. FromJSON a => Object -> Text -> Parser a
.: Text
"CumulativeSize"
Parser (Int -> Text -> FilesStatObj)
-> Parser Int -> Parser (Text -> FilesStatObj)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object -> Text -> Parser Int
forall a. FromJSON a => Object -> Text -> Parser a
.: Text
"Blocks"
Parser (Text -> FilesStatObj) -> Parser Text -> Parser FilesStatObj
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object -> Text -> Parser Text
forall a. FromJSON a => Object -> Text -> Parser a
.: Text
"Type"
parseJSON Value
_ = Parser FilesStatObj
forall (m :: * -> *) a. MonadPlus m => m a
mzero
instance FromJSON FilesEntryObj where
parseJSON :: Value -> Parser FilesEntryObj
parseJSON (Object Object
o) =
Text -> Int -> Int -> Text -> FilesEntryObj
FilesEntryObj (Text -> Int -> Int -> Text -> FilesEntryObj)
-> Parser Text -> Parser (Int -> Int -> Text -> FilesEntryObj)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
o Object -> Text -> Parser Text
forall a. FromJSON a => Object -> Text -> Parser a
.: Text
"Name"
Parser (Int -> Int -> Text -> FilesEntryObj)
-> Parser Int -> Parser (Int -> Text -> FilesEntryObj)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object -> Text -> Parser Int
forall a. FromJSON a => Object -> Text -> Parser a
.: Text
"Type"
Parser (Int -> Text -> FilesEntryObj)
-> Parser Int -> Parser (Text -> FilesEntryObj)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object -> Text -> Parser Int
forall a. FromJSON a => Object -> Text -> Parser a
.: Text
"Size"
Parser (Text -> FilesEntryObj)
-> Parser Text -> Parser FilesEntryObj
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object -> Text -> Parser Text
forall a. FromJSON a => Object -> Text -> Parser a
.: Text
"Hash"
parseJSON Value
_ = Parser FilesEntryObj
forall (m :: * -> *) a. MonadPlus m => m a
mzero
instance FromJSON FilesLsObj where
parseJSON :: Value -> Parser FilesLsObj
parseJSON (Object Object
o) =
[FilesEntryObj] -> FilesLsObj
FilesLsObj ([FilesEntryObj] -> FilesLsObj)
-> Parser [FilesEntryObj] -> Parser FilesLsObj
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
o Object -> Text -> Parser [FilesEntryObj]
forall a. FromJSON a => Object -> Text -> Parser a
.: Text
"Entries"
parseJSON Value
_ = Parser FilesLsObj
forall (m :: * -> *) a. MonadPlus m => m a
mzero
instance FromJSON FilesFlushObj where
parseJSON :: Value -> Parser FilesFlushObj
parseJSON (Object Object
o) =
Text -> FilesFlushObj
FilesFlushObj (Text -> FilesFlushObj) -> Parser Text -> Parser FilesFlushObj
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
o Object -> Text -> Parser Text
forall a. FromJSON a => Object -> Text -> Parser a
.: Text
"Cid"
parseJSON Value
_ = Parser FilesFlushObj
forall (m :: * -> *) a. MonadPlus m => m a
mzero
data IpfsText deriving Typeable
instance Servant.API.Accept IpfsText where
contentType :: Proxy IpfsText -> MediaType
contentType Proxy IpfsText
_ = ByteString
"text" ByteString -> ByteString -> MediaType
M.// ByteString
"plain"
instance MimeUnrender IpfsText Text where
mimeUnrender :: Proxy IpfsText -> ByteString -> Either String Text
mimeUnrender Proxy IpfsText
_ = (UnicodeException -> String)
-> Either UnicodeException Text -> Either String Text
forall (a :: * -> * -> *) b c d.
ArrowChoice a =>
a b c -> a (Either b d) (Either c d)
left UnicodeException -> String
forall a. Show a => a -> String
show (Either UnicodeException Text -> Either String Text)
-> (ByteString -> Either UnicodeException Text)
-> ByteString
-> Either String Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> Either UnicodeException Text
TextS.decodeUtf8' (ByteString -> Either UnicodeException Text)
-> (ByteString -> ByteString)
-> ByteString
-> Either UnicodeException Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> ByteString
toStrict
data IpfsJSON deriving Typeable
instance Servant.API.Accept IpfsJSON where
contentType :: Proxy IpfsJSON -> MediaType
contentType Proxy IpfsJSON
_ = ByteString
"application" ByteString -> ByteString -> MediaType
M.// ByteString
"json"
instance MimeUnrender IpfsJSON Text where
mimeUnrender :: Proxy IpfsJSON -> ByteString -> Either String Text
mimeUnrender Proxy IpfsJSON
_ = (UnicodeException -> String)
-> Either UnicodeException Text -> Either String Text
forall (a :: * -> * -> *) b c d.
ArrowChoice a =>
a b c -> a (Either b d) (Either c d)
left UnicodeException -> String
forall a. Show a => a -> String
show (Either UnicodeException Text -> Either String Text)
-> (ByteString -> Either UnicodeException Text)
-> ByteString
-> Either String Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> Either UnicodeException Text
TextS.decodeUtf8' (ByteString -> Either UnicodeException Text)
-> (ByteString -> ByteString)
-> ByteString
-> Either UnicodeException Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> ByteString
toStrict
type IpfsApi = "cat" :> Capture "arg" Text :> Get '[IpfsText] CatReturnType
:<|> "ls" :> Capture "arg" Text :> Get '[JSON] LsObj
:<|> "get" :> Capture "arg" Text :> Get '[IpfsText] GetReturnType
:<|> "swarm" :> "peers" :> Get '[JSON] SwarmPeersObj
:<|> "swarm" :> "connect" :> QueryParam "arg" Text :> Get '[JSON] SwarmObj
:<|> "swarm" :> "disconnect" :> QueryParam "arg" Text :> Get '[JSON] SwarmObj
:<|> "swarm" :> "filters" :> Get '[JSON] SwarmObj
:<|> "swarm" :> "filters" :> "add" :> QueryParam "arg" Text :> Get '[JSON] SwarmObj
:<|> "swarm" :> "filters" :> "rm" :> QueryParam "arg" Text :> Get '[JSON] SwarmObj
:<|> "bitswap" :> "stat" :> Get '[JSON] BitswapStatObj
:<|> "bitswap" :> "wantlist" :> Get '[JSON] BitswapWLObj
:<|> "bitswap" :> "ledger" :> Capture "peerId" Text :> Get '[JSON] BitswapLedgerObj
:<|> "bitswap" :> "reprovide" :> Get '[IpfsText] ReprovideReturnType
:<|> "cid" :> "bases" :> Get '[JSON] [CidBasesObj]
:<|> "cid" :> "codecs" :> Get '[JSON] [CidCodecsObj]
:<|> "cid" :> "hashes" :> Get '[JSON] [CidHashesObj]
:<|> "cid" :> "base32" :> Capture "cid" Text :> Get '[JSON] CidObj
:<|> "cid" :> "format" :> Capture "cid" Text :> Get '[JSON] CidObj
:<|> "block" :> "get" :> Capture "key" Text :> Get '[IpfsText] BlockReturnType
:<|> "block" :> "stat" :> Capture "key" Text :> Get '[JSON] BlockObj
:<|> "dag" :> "get" :> Capture "ref" Text :> Get '[IpfsJSON] DagReturnType
:<|> "dag" :> "resolve" :> Capture "ref" Text :> Get '[JSON] DagResolveObj
:<|> "config" :> Capture "ref" Text :> Get '[JSON] ConfigObj
:<|> "config" :> Capture "arg" Text :> QueryParam "arg" Text :> Get '[JSON] ConfigObj
:<|> "object" :> "data" :> Capture "ref" Text :> Get '[IpfsText] ObjectReturnType
:<|> "object" :> "new" :> Get '[JSON] ObjectObj
:<|> "object" :> "links" :> Capture "ref" Text :> Get '[JSON] ObjectLinksObj
:<|> "object" :> "patch" :> "add-link" :> Capture "arg" Text
:> QueryParam "arg" Text :> QueryParam "arg" Text :> Get '[JSON] ObjectLinksObj
:<|> "object" :> "patch" :> "rm-link" :> Capture "arg" Text
:> QueryParam "arg" Text :> Get '[JSON] ObjectLinksObj
:<|> "object" :> "get" :> Capture "arg" Text :> Get '[JSON] ObjectGetObj
:<|> "object" :> "diff" :> Capture "arg" Text :> QueryParam "arg" Text :> Get '[JSON] ObjectDiffObj
:<|> "object" :> "stat" :> Capture "arg" Text :> Get '[JSON] ObjectStatObj
:<|> "pin" :> "add" :> Capture "arg" Text :> Get '[JSON] PinObj
:<|> "pin" :> "rm" :> Capture "arg" Text :> Get '[JSON] PinObj
:<|> "bootstrap" :> "add" :> QueryParam "arg" Text :> Get '[JSON] BootstrapObj
:<|> "bootstrap" :> "list" :> Get '[JSON] BootstrapObj
:<|> "bootstrap" :> "rm" :> QueryParam "arg" Text :> Get '[JSON] BootstrapObj
:<|> "stats" :> "bw" :> Get '[JSON] StatsBwObj
:<|> "stats" :> "repo" :> Get '[JSON] StatsRepoObj
:<|> "version" :> Get '[JSON] VersionObj
:<|> "id" :> Get '[JSON] IdObj
:<|> "id" :> Capture "arg" Text :> Get '[JSON] IdObj
:<|> "dns" :> Capture "arg" Text :> Get '[JSON] DnsObj
:<|> "pubsub" :> "ls" :> Get '[JSON] PubsubObj
:<|> "pubsub" :> "peers" :> Get '[JSON] PubsubObj
:<|> "pubsub" :> "pub" :> Capture "arg" Text :> QueryParam "arg" Text :> Get '[JSON] NoContent
:<|> "log" :> "ls" :> Get '[JSON] LogLsObj
:<|> "log" :> "level" :> Capture "arg" Text :> QueryParam "arg" Text :> Get '[JSON] LogLevelObj
:<|> "repo" :> "version" :> Get '[JSON] RepoVersionObj
:<|> "repo" :> "fsck" :> Get '[JSON] RepoFsckObj
:<|> "key" :> "gen" :> Capture "arg" Text :> QueryParam "type" Text :> Get '[JSON] KeyDetailsObj
:<|> "key" :> "list" :> Get '[JSON] KeyObj
:<|> "key" :> "rename" :> Capture "arg" Text :> QueryParam "arg" Text :> Get '[JSON] KeyRenameObj
:<|> "key" :> "rm" :> Capture "arg" Text :> Get '[JSON] KeyObj
:<|> "files" :> "chcid" :> QueryParam "arg" Text :> QueryParam "cid-version" Int :> Get '[JSON] NoContent
:<|> "files" :> "cp" :> QueryParam "arg" Text :> QueryParam "arg" Text :> Get '[JSON] NoContent
:<|> "files" :> "flush" :> QueryParam "arg" Text :> Get '[JSON] FilesFlushObj
:<|> "files" :> "ls" :> QueryParam "arg" Text :> Get '[JSON] FilesLsObj
:<|> "files" :> "mkdir" :> QueryParam "arg" Text :> Get '[JSON] NoContent
:<|> "files" :> "mv" :> QueryParam "arg" Text :> QueryParam "arg" Text :> Get '[JSON] NoContent
:<|> "files" :> "read" :> QueryParam "arg" Text :> Get '[IpfsText] FilesReadType
:<|> "files" :> "rm" :> QueryParam "arg" Text :> QueryParam "recursive" Bool :> Get '[JSON] NoContent
:<|> "files" :> "stat" :> QueryParam "arg" Text :> Get '[JSON] FilesStatObj
:<|> "shutdown" :> Get '[JSON] NoContent