{-# LANGUAGE DataKinds #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE TypeOperators #-}
module Network.Ipfs.Api.Types.Stream where
import Control.Monad
import Data.Aeson
import qualified Data.ByteString.Lazy.Char8 ()
import Data.Int
import Data.Text
import Network.HTTP.Client ()
import Servant.API
import Network.Ipfs.Api.Types (IpfsText)
type LogReturnType = Text
data PingObj = PingObj
{ PingObj -> Bool
success :: Bool
, PingObj -> Text
text :: Text
, PingObj -> Int64
time :: Int64
}
deriving (Int -> PingObj -> ShowS
[PingObj] -> ShowS
PingObj -> String
(Int -> PingObj -> ShowS)
-> (PingObj -> String) -> ([PingObj] -> ShowS) -> Show PingObj
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [PingObj] -> ShowS
$cshowList :: [PingObj] -> ShowS
show :: PingObj -> String
$cshow :: PingObj -> String
showsPrec :: Int -> PingObj -> ShowS
$cshowsPrec :: Int -> PingObj -> ShowS
Show, PingObj -> PingObj -> Bool
(PingObj -> PingObj -> Bool)
-> (PingObj -> PingObj -> Bool) -> Eq PingObj
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PingObj -> PingObj -> Bool
$c/= :: PingObj -> PingObj -> Bool
== :: PingObj -> PingObj -> Bool
$c== :: PingObj -> PingObj -> Bool
Eq)
data ResponseObj = ResponseObj
{ ResponseObj -> Maybe [Text]
addrs :: Maybe [Text]
, ResponseObj -> Text
id :: Text
}
deriving (Int -> ResponseObj -> ShowS
[ResponseObj] -> ShowS
ResponseObj -> String
(Int -> ResponseObj -> ShowS)
-> (ResponseObj -> String)
-> ([ResponseObj] -> ShowS)
-> Show ResponseObj
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ResponseObj] -> ShowS
$cshowList :: [ResponseObj] -> ShowS
show :: ResponseObj -> String
$cshow :: ResponseObj -> String
showsPrec :: Int -> ResponseObj -> ShowS
$cshowsPrec :: Int -> ResponseObj -> ShowS
Show, ResponseObj -> ResponseObj -> Bool
(ResponseObj -> ResponseObj -> Bool)
-> (ResponseObj -> ResponseObj -> Bool) -> Eq ResponseObj
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ResponseObj -> ResponseObj -> Bool
$c/= :: ResponseObj -> ResponseObj -> Bool
== :: ResponseObj -> ResponseObj -> Bool
$c== :: ResponseObj -> ResponseObj -> Bool
Eq)
data DhtObj = DhtObj
{ :: Text
, DhtObj -> Text
addrid :: Text
, DhtObj -> Maybe [ResponseObj]
responses :: Maybe [ResponseObj]
, DhtObj -> Int
addrType :: Int
}
deriving (Int -> DhtObj -> ShowS
[DhtObj] -> ShowS
DhtObj -> String
(Int -> DhtObj -> ShowS)
-> (DhtObj -> String) -> ([DhtObj] -> ShowS) -> Show DhtObj
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DhtObj] -> ShowS
$cshowList :: [DhtObj] -> ShowS
show :: DhtObj -> String
$cshow :: DhtObj -> String
showsPrec :: Int -> DhtObj -> ShowS
$cshowsPrec :: Int -> DhtObj -> ShowS
Show, DhtObj -> DhtObj -> Bool
(DhtObj -> DhtObj -> Bool)
-> (DhtObj -> DhtObj -> Bool) -> Eq DhtObj
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DhtObj -> DhtObj -> Bool
$c/= :: DhtObj -> DhtObj -> Bool
== :: DhtObj -> DhtObj -> Bool
$c== :: DhtObj -> DhtObj -> Bool
Eq)
data RepoKeyObj = RepoKeyObj
{ RepoKeyObj -> Text
repoSlash :: Text
}
deriving (Int -> RepoKeyObj -> ShowS
[RepoKeyObj] -> ShowS
RepoKeyObj -> String
(Int -> RepoKeyObj -> ShowS)
-> (RepoKeyObj -> String)
-> ([RepoKeyObj] -> ShowS)
-> Show RepoKeyObj
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [RepoKeyObj] -> ShowS
$cshowList :: [RepoKeyObj] -> ShowS
show :: RepoKeyObj -> String
$cshow :: RepoKeyObj -> String
showsPrec :: Int -> RepoKeyObj -> ShowS
$cshowsPrec :: Int -> RepoKeyObj -> ShowS
Show, RepoKeyObj -> RepoKeyObj -> Bool
(RepoKeyObj -> RepoKeyObj -> Bool)
-> (RepoKeyObj -> RepoKeyObj -> Bool) -> Eq RepoKeyObj
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: RepoKeyObj -> RepoKeyObj -> Bool
$c/= :: RepoKeyObj -> RepoKeyObj -> Bool
== :: RepoKeyObj -> RepoKeyObj -> Bool
$c== :: RepoKeyObj -> RepoKeyObj -> Bool
Eq)
data RepoGcObj = RepoGcObj
{ RepoGcObj -> RepoKeyObj
repoKey :: RepoKeyObj
}
deriving (Int -> RepoGcObj -> ShowS
[RepoGcObj] -> ShowS
RepoGcObj -> String
(Int -> RepoGcObj -> ShowS)
-> (RepoGcObj -> String)
-> ([RepoGcObj] -> ShowS)
-> Show RepoGcObj
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [RepoGcObj] -> ShowS
$cshowList :: [RepoGcObj] -> ShowS
show :: RepoGcObj -> String
$cshow :: RepoGcObj -> String
showsPrec :: Int -> RepoGcObj -> ShowS
$cshowsPrec :: Int -> RepoGcObj -> ShowS
Show, RepoGcObj -> RepoGcObj -> Bool
(RepoGcObj -> RepoGcObj -> Bool)
-> (RepoGcObj -> RepoGcObj -> Bool) -> Eq RepoGcObj
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: RepoGcObj -> RepoGcObj -> Bool
$c/= :: RepoGcObj -> RepoGcObj -> Bool
== :: RepoGcObj -> RepoGcObj -> Bool
$c== :: RepoGcObj -> RepoGcObj -> Bool
Eq)
data RepoVerifyObj = RepoVerifyObj
{ RepoVerifyObj -> Text
msg :: Text
, RepoVerifyObj -> Int
progress :: Int
}
deriving (Int -> RepoVerifyObj -> ShowS
[RepoVerifyObj] -> ShowS
RepoVerifyObj -> String
(Int -> RepoVerifyObj -> ShowS)
-> (RepoVerifyObj -> String)
-> ([RepoVerifyObj] -> ShowS)
-> Show RepoVerifyObj
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [RepoVerifyObj] -> ShowS
$cshowList :: [RepoVerifyObj] -> ShowS
show :: RepoVerifyObj -> String
$cshow :: RepoVerifyObj -> String
showsPrec :: Int -> RepoVerifyObj -> ShowS
$cshowsPrec :: Int -> RepoVerifyObj -> ShowS
Show, RepoVerifyObj -> RepoVerifyObj -> Bool
(RepoVerifyObj -> RepoVerifyObj -> Bool)
-> (RepoVerifyObj -> RepoVerifyObj -> Bool) -> Eq RepoVerifyObj
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: RepoVerifyObj -> RepoVerifyObj -> Bool
$c/= :: RepoVerifyObj -> RepoVerifyObj -> Bool
== :: RepoVerifyObj -> RepoVerifyObj -> Bool
$c== :: RepoVerifyObj -> RepoVerifyObj -> Bool
Eq)
data RefsObj = RefsObj
{ RefsObj -> Text
error :: Text
, RefsObj -> Text
ref :: Text
}
deriving (Int -> RefsObj -> ShowS
[RefsObj] -> ShowS
RefsObj -> String
(Int -> RefsObj -> ShowS)
-> (RefsObj -> String) -> ([RefsObj] -> ShowS) -> Show RefsObj
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [RefsObj] -> ShowS
$cshowList :: [RefsObj] -> ShowS
show :: RefsObj -> String
$cshow :: RefsObj -> String
showsPrec :: Int -> RefsObj -> ShowS
$cshowsPrec :: Int -> RefsObj -> ShowS
Show, RefsObj -> RefsObj -> Bool
(RefsObj -> RefsObj -> Bool)
-> (RefsObj -> RefsObj -> Bool) -> Eq RefsObj
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: RefsObj -> RefsObj -> Bool
$c/= :: RefsObj -> RefsObj -> Bool
== :: RefsObj -> RefsObj -> Bool
$c== :: RefsObj -> RefsObj -> Bool
Eq)
data PubsubSubObj = PubsubSubObj
{ PubsubSubObj -> Text
mssgdata :: Text
, PubsubSubObj -> Text
from :: Text
, PubsubSubObj -> Text
seqno :: Text
, PubsubSubObj -> [Text]
topicIDs :: [Text]
}
deriving (Int -> PubsubSubObj -> ShowS
[PubsubSubObj] -> ShowS
PubsubSubObj -> String
(Int -> PubsubSubObj -> ShowS)
-> (PubsubSubObj -> String)
-> ([PubsubSubObj] -> ShowS)
-> Show PubsubSubObj
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [PubsubSubObj] -> ShowS
$cshowList :: [PubsubSubObj] -> ShowS
show :: PubsubSubObj -> String
$cshow :: PubsubSubObj -> String
showsPrec :: Int -> PubsubSubObj -> ShowS
$cshowsPrec :: Int -> PubsubSubObj -> ShowS
Show, PubsubSubObj -> PubsubSubObj -> Bool
(PubsubSubObj -> PubsubSubObj -> Bool)
-> (PubsubSubObj -> PubsubSubObj -> Bool) -> Eq PubsubSubObj
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PubsubSubObj -> PubsubSubObj -> Bool
$c/= :: PubsubSubObj -> PubsubSubObj -> Bool
== :: PubsubSubObj -> PubsubSubObj -> Bool
$c== :: PubsubSubObj -> PubsubSubObj -> Bool
Eq)
instance FromJSON PingObj where
parseJSON :: Value -> Parser PingObj
parseJSON (Object Object
o) =
Bool -> Text -> Int64 -> PingObj
PingObj (Bool -> Text -> Int64 -> PingObj)
-> Parser Bool -> Parser (Text -> Int64 -> PingObj)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
o Object -> Text -> Parser Bool
forall a. FromJSON a => Object -> Text -> Parser a
.: Text
"Success"
Parser (Text -> Int64 -> PingObj)
-> Parser Text -> Parser (Int64 -> PingObj)
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
"Text"
Parser (Int64 -> PingObj) -> Parser Int64 -> Parser PingObj
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
"Time"
parseJSON Value
_ = Parser PingObj
forall (m :: * -> *) a. MonadPlus m => m a
mzero
instance FromJSON DhtObj where
parseJSON :: Value -> Parser DhtObj
parseJSON (Object Object
o) =
Text -> Text -> Maybe [ResponseObj] -> Int -> DhtObj
DhtObj (Text -> Text -> Maybe [ResponseObj] -> Int -> DhtObj)
-> Parser Text
-> Parser (Text -> Maybe [ResponseObj] -> Int -> DhtObj)
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
"Extra"
Parser (Text -> Maybe [ResponseObj] -> Int -> DhtObj)
-> Parser Text -> Parser (Maybe [ResponseObj] -> Int -> DhtObj)
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 (Maybe [ResponseObj] -> Int -> DhtObj)
-> Parser (Maybe [ResponseObj]) -> Parser (Int -> DhtObj)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object -> Text -> Parser (Maybe [ResponseObj])
forall a. FromJSON a => Object -> Text -> Parser a
.: Text
"Responses"
Parser (Int -> DhtObj) -> Parser Int -> Parser DhtObj
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 DhtObj
forall (m :: * -> *) a. MonadPlus m => m a
mzero
instance FromJSON ResponseObj where
parseJSON :: Value -> Parser ResponseObj
parseJSON (Object Object
o) =
Maybe [Text] -> Text -> ResponseObj
ResponseObj (Maybe [Text] -> Text -> ResponseObj)
-> Parser (Maybe [Text]) -> Parser (Text -> ResponseObj)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
o Object -> Text -> Parser (Maybe [Text])
forall a. FromJSON a => Object -> Text -> Parser a
.: Text
"Addrs"
Parser (Text -> ResponseObj) -> Parser Text -> Parser ResponseObj
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"
parseJSON Value
_ = Parser ResponseObj
forall (m :: * -> *) a. MonadPlus m => m a
mzero
instance FromJSON RepoKeyObj where
parseJSON :: Value -> Parser RepoKeyObj
parseJSON (Object Object
o) =
Text -> RepoKeyObj
RepoKeyObj (Text -> RepoKeyObj) -> Parser Text -> Parser RepoKeyObj
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 RepoKeyObj
forall (m :: * -> *) a. MonadPlus m => m a
mzero
instance FromJSON RepoGcObj where
parseJSON :: Value -> Parser RepoGcObj
parseJSON (Object Object
o) =
RepoKeyObj -> RepoGcObj
RepoGcObj (RepoKeyObj -> RepoGcObj) -> Parser RepoKeyObj -> Parser RepoGcObj
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
o Object -> Text -> Parser RepoKeyObj
forall a. FromJSON a => Object -> Text -> Parser a
.: Text
"Key"
parseJSON Value
_ = Parser RepoGcObj
forall (m :: * -> *) a. MonadPlus m => m a
mzero
instance FromJSON RepoVerifyObj where
parseJSON :: Value -> Parser RepoVerifyObj
parseJSON (Object Object
o) =
Text -> Int -> RepoVerifyObj
RepoVerifyObj (Text -> Int -> RepoVerifyObj)
-> Parser Text -> Parser (Int -> RepoVerifyObj)
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
"Msg"
Parser (Int -> RepoVerifyObj) -> Parser Int -> Parser RepoVerifyObj
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
"Progress"
parseJSON Value
_ = Parser RepoVerifyObj
forall (m :: * -> *) a. MonadPlus m => m a
mzero
instance FromJSON RefsObj where
parseJSON :: Value -> Parser RefsObj
parseJSON (Object Object
o) =
Text -> Text -> RefsObj
RefsObj (Text -> Text -> RefsObj)
-> Parser Text -> Parser (Text -> RefsObj)
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
"Err"
Parser (Text -> RefsObj) -> Parser Text -> Parser RefsObj
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
"Ref"
parseJSON Value
_ = Parser RefsObj
forall (m :: * -> *) a. MonadPlus m => m a
mzero
instance FromJSON PubsubSubObj where
parseJSON :: Value -> Parser PubsubSubObj
parseJSON (Object Object
o) =
Text -> Text -> Text -> [Text] -> PubsubSubObj
PubsubSubObj (Text -> Text -> Text -> [Text] -> PubsubSubObj)
-> Parser Text -> Parser (Text -> Text -> [Text] -> PubsubSubObj)
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 (Text -> Text -> [Text] -> PubsubSubObj)
-> Parser Text -> Parser (Text -> [Text] -> PubsubSubObj)
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
"from"
Parser (Text -> [Text] -> PubsubSubObj)
-> Parser Text -> Parser ([Text] -> PubsubSubObj)
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
"seqno"
Parser ([Text] -> PubsubSubObj)
-> Parser [Text] -> Parser PubsubSubObj
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
"topicIDs"
parseJSON Value
_ = Parser PubsubSubObj
forall (m :: * -> *) a. MonadPlus m => m a
mzero
type IpfsStreamApi = "ping" :> Capture "arg" Text :> StreamGet NewlineFraming JSON ( SourceIO PingObj )
:<|> "dht" :> "findpeer" :> Capture "arg" Text :> StreamGet NewlineFraming JSON ( SourceIO DhtObj )
:<|> "dht" :> "findprovs" :> Capture "arg" Text :> StreamGet NewlineFraming JSON ( SourceIO DhtObj )
:<|> "dht" :> "get" :> Capture "arg" Text :> StreamGet NewlineFraming JSON ( SourceIO DhtObj )
:<|> "dht" :> "provide" :> Capture "arg" Text :> StreamGet NewlineFraming JSON ( SourceIO DhtObj )
:<|> "dht" :> "query" :> Capture "arg" Text :> StreamGet NewlineFraming JSON ( SourceIO DhtObj )
:<|> "log" :> "tail" :> StreamGet NewlineFraming IpfsText ( SourceIO LogReturnType)
:<|> "repo" :> "gc" :> StreamGet NewlineFraming JSON ( SourceIO RepoGcObj)
:<|> "repo" :> "verify" :> StreamGet NewlineFraming JSON ( SourceIO RepoVerifyObj)
:<|> "refs" :> Capture "arg" Text :> StreamGet NewlineFraming JSON (SourceIO RefsObj)
:<|> "refs" :> "local" :> StreamGet NewlineFraming JSON (SourceIO RefsObj)
:<|> "pubsub" :> "sub" :> Capture "arg" Text :> StreamGet NewlineFraming JSON ( SourceIO PubsubSubObj )