{-# LANGUAGE DataKinds     #-}
{-# LANGUAGE TypeOperators #-}

-- | AUTOGENERATED
module Network.IPFS.API where

import           Data.Aeson (Value)
import           Data.ByteString (ByteString)
import qualified Data.ByteString.Lazy as L (ByteString)
import           Data.Text (Text)
import           Network.IPFS.API.Types
import           Servant.API

-- | Add a file or directory to ipfs.
--
-- Response example:
--
-- > {
-- >     "Name": "<string>"
-- >     "Hash": "<string>"
-- >     "Bytes": "<int64>"
-- >     "Size": "<string>"
-- > }
type ApiV0Add =
      "api" :> "v0" :> "add"
    :> ReqBody '[MultipartFormData] L.ByteString
    -- Add directory paths recursively. Default: false.
    :> QueryParam "recursive" Bool
    -- Write minimal output.
    :> QueryParam "quiet" Bool
    -- Write only final hash.
    :> QueryParam "quieter" Bool
    -- Write no output.
    :> QueryParam "silent" Bool
    -- Stream progress data.
    :> QueryParam "progress" Bool
    -- Use trickle-dag format for dag generation.
    :> QueryParam "trickle" Bool
    -- Only chunk and hash - do not write to disk.
    :> QueryParam "only-hash" Bool
    -- Wrap files with a directory object.
    :> QueryParam "wrap-with-directory" Bool
    -- Include files that are hidden. Only takes effect on recursive add.
    :> QueryParam "hidden" Bool
    -- Chunking algorithm, size-[bytes] or rabin-[min]-[avg]-[max]. Default:
    -- size-262144.
    :> QueryParam "chunker" Text
    -- Pin this object when adding. Default: true.
    :> QueryParam "pin" Bool
    -- Use raw blocks for leaf nodes. (experimental).
    :> QueryParam "raw-leaves" Bool
    -- Add the file using filestore. Implies raw-leaves. (experimental).
    :> QueryParam "nocopy" Bool
    -- Check the filestore for pre-existing blocks. (experimental).
    :> QueryParam "fscache" Bool
    -- CID version. Defaults to 0 unless an option that depends on CIDv1 is passed.
    -- (experimental).
    :> QueryParam "cid-version" Int
    -- Hash function to use. Implies CIDv1 if not sha2-256. (experimental). Default:
    -- sha2-256.
    :> QueryParam "hash" Text
    :> Post '[JSON] Value

-- | Show the current ledger for a peer.
--
-- Response example:
--
-- > {
-- >     "Peer": "<string>"
-- >     "Value": "<float64>"
-- >     "Sent": "<uint64>"
-- >     "Recv": "<uint64>"
-- >     "Exchanged": "<uint64>"
-- > }
type ApiV0BitswapLedger =
      "api" :> "v0" :> "bitswap" :> "ledger"
    -- The PeerID (B58) of the ledger to inspect.
    :> QueryParam' '[Required, Strict] "arg" Text
    :> Post '[JSON] Value

-- | Trigger reprovider.
type ApiV0BitswapReprovide =
      "api" :> "v0" :> "bitswap" :> "reprovide"
    :> Stream 'POST 200 NoFraming PlainText (SourceIO ByteString)

-- | Show some diagnostic information on the bitswap agent.
--
-- Response example:
--
-- > {
-- >     "ProvideBufLen": "<int>"
-- >     "Wantlist": [
-- >         "<string>"
-- >     ]
-- >     "Peers": [
-- >         "<string>"
-- >     ]
-- >     "BlocksReceived": "<uint64>"
-- >     "DataReceived": "<uint64>"
-- >     "BlocksSent": "<uint64>"
-- >     "DataSent": "<uint64>"
-- >     "DupBlksReceived": "<uint64>"
-- >     "DupDataReceived": "<uint64>"
-- > }
type ApiV0BitswapStat =
      "api" :> "v0" :> "bitswap" :> "stat"
    :> Post '[JSON] Value

-- | Remove a given block from your wantlist.
type ApiV0BitswapUnwant =
      "api" :> "v0" :> "bitswap" :> "unwant"
    -- Key(s) to remove from your wantlist.
    :> QueryParam' '[Required, Strict] "arg" Text
    :> Stream 'POST 200 NoFraming PlainText (SourceIO ByteString)

-- | Show blocks currently on the wantlist.
--
-- Response example:
--
-- > {
-- >     "Keys": [
-- >         "<string>"
-- >     ]
-- > }
type ApiV0BitswapWantlist =
      "api" :> "v0" :> "bitswap" :> "wantlist"
    -- Specify which peer to show wantlist for. Default: self.
    :> QueryParam "peer" Text
    :> Post '[JSON] Value

-- | Get a raw IPFS block.
type ApiV0BlockGet =
      "api" :> "v0" :> "block" :> "get"
    -- The base58 multihash of an existing block to get.
    :> QueryParam' '[Required, Strict] "arg" Text
    :> Stream 'POST 200 NoFraming PlainText (SourceIO ByteString)

-- | Store input as an IPFS block.
--
-- Response example:
--
-- > {
-- >     "Key": "<string>"
-- >     "Size": "<int>"
-- > }
type ApiV0BlockPut =
      "api" :> "v0" :> "block" :> "put"
    :> ReqBody '[MultipartFormData] L.ByteString
    -- cid format for blocks to be created with.
    :> QueryParam "format" Text
    -- multihash hash function. Default: sha2-256.
    :> QueryParam "mhtype" Text
    -- multihash hash length. Default: -1.
    :> QueryParam "mhlen" Int
    :> Post '[JSON] Value

-- | Remove IPFS block(s).
--
-- Response example:
--
-- > {
-- >     "Hash": "<string>"
-- >     "Error": "<string>"
-- > }
type ApiV0BlockRm =
      "api" :> "v0" :> "block" :> "rm"
    -- Bash58 encoded multihash of block(s) to remove.
    :> QueryParam' '[Required, Strict] "arg" Text
    -- Ignore nonexistent blocks.
    :> QueryParam "force" Bool
    -- Write minimal output.
    :> QueryParam "quiet" Bool
    :> Post '[JSON] Value

-- | Print information of a raw IPFS block.
--
-- Response example:
--
-- > {
-- >     "Key": "<string>"
-- >     "Size": "<int>"
-- > }
type ApiV0BlockStat =
      "api" :> "v0" :> "block" :> "stat"
    -- The base58 multihash of an existing block to stat.
    :> QueryParam' '[Required, Strict] "arg" Text
    :> Post '[JSON] Value

-- | Add default peers to the bootstrap list.
--
-- Response example:
--
-- > {
-- >     "Peers": [
-- >         "<string>"
-- >     ]
-- > }
type ApiV0BootstrapAddDefault =
      "api" :> "v0" :> "bootstrap" :> "add" :> "default"
    :> Post '[JSON] Value

-- | Show peers in the bootstrap list.
--
-- Response example:
--
-- > {
-- >     "Peers": [
-- >         "<string>"
-- >     ]
-- > }
type ApiV0BootstrapList =
      "api" :> "v0" :> "bootstrap" :> "list"
    :> Post '[JSON] Value

-- | Remove all peers from the bootstrap list.
--
-- Response example:
--
-- > {
-- >     "Peers": [
-- >         "<string>"
-- >     ]
-- > }
type ApiV0BootstrapRmAll =
      "api" :> "v0" :> "bootstrap" :> "rm" :> "all"
    :> Post '[JSON] Value

-- | Show IPFS object data.
type ApiV0Cat =
      "api" :> "v0" :> "cat"
    -- The path to the IPFS object(s) to be outputted.
    :> QueryParam' '[Required, Strict] "arg" Text
    -- Byte offset to begin reading from.
    :> QueryParam "offset" Int
    -- Maximum number of bytes to read.
    :> QueryParam "length" Int
    :> Stream 'POST 200 NoFraming PlainText (SourceIO ByteString)

-- | List all available commands.
--
-- Response example:
--
-- > {
-- >     "Name": "<string>"
-- >     "Subcommands": [
-- >         {
-- >             "Name": "<string>"
-- >             "Subcommands": [
-- >                 {
-- >                     "Name": "<string>"
-- >                     "Subcommands": [
-- >                         ...
-- >                     ]
-- >                     "Options": [
-- >                         ...
-- >                     ]
-- >                     "showOpts": "<bool>"
-- >                 }
-- >             ]
-- >             "Options": [
-- >                 {
-- >                     "Names": [
-- >                         ...
-- >                     ]
-- >                 }
-- >             ]
-- >             "showOpts": "<bool>"
-- >         }
-- >     ]
-- >     "Options": [
-- >         {
-- >             "Names": [
-- >                 "<string>"
-- >             ]
-- >         }
-- >     ]
-- >     "showOpts": "<bool>"
-- > }
type ApiV0Commands =
      "api" :> "v0" :> "commands"
    -- Show command flags.
    :> QueryParam "flags" Bool
    :> Post '[JSON] Value

-- | Open the config file for editing in $EDITOR.
type ApiV0ConfigEdit =
      "api" :> "v0" :> "config" :> "edit"
    :> Stream 'POST 200 NoFraming PlainText (SourceIO ByteString)

-- | Apply profile to config.
type ApiV0ConfigProfileApply =
      "api" :> "v0" :> "config" :> "profile" :> "apply"
    -- The profile to apply to the config.
    :> QueryParam' '[Required, Strict] "arg" Text
    :> Stream 'POST 200 NoFraming PlainText (SourceIO ByteString)

-- | Replace the config with <file>.
type ApiV0ConfigReplace =
      "api" :> "v0" :> "config" :> "replace"
    :> ReqBody '[MultipartFormData] L.ByteString
    :> Stream 'POST 200 NoFraming PlainText (SourceIO ByteString)

-- | Output config file contents.
type ApiV0ConfigShow =
      "api" :> "v0" :> "config" :> "show"
    :> Stream 'POST 200 NoFraming PlainText (SourceIO ByteString)

-- | Get a dag node from ipfs.
type ApiV0DagGet =
      "api" :> "v0" :> "dag" :> "get"
    -- The object to get
    :> QueryParam' '[Required, Strict] "arg" Text
    :> Stream 'POST 200 NoFraming PlainText (SourceIO ByteString)

-- | Add a dag node to ipfs.
--
-- Response example:
--
-- > {
-- >     "Cid": "<string>"
-- > }
type ApiV0DagPut =
      "api" :> "v0" :> "dag" :> "put"
    :> ReqBody '[MultipartFormData] L.ByteString
    -- Format that the object will be added as. Default: cbor.
    :> QueryParam "format" Text
    -- Format that the input object will be. Default: json.
    :> QueryParam "input-enc" Text
    -- Pin this object when adding.
    :> QueryParam "pin" Bool
    -- Hash function to use. Default: .
    :> QueryParam "hash" Text
    :> Post '[JSON] Value

-- | Resolve ipld block
--
-- Response example:
--
-- > {
-- >     "Cid": "<string>"
-- >     "RemPath": "<string>"
-- > }
type ApiV0DagResolve =
      "api" :> "v0" :> "dag" :> "resolve"
    -- The path to resolve
    :> QueryParam' '[Required, Strict] "arg" Text
    :> Post '[JSON] Value

-- | Query the DHT for all of the multiaddresses associated with a Peer ID.
--
-- Response example:
--
-- > {
-- >     "ID": "<string>"
-- >     "Type": "<int>"
-- >     "Responses": [
-- >         {
-- >             "ID": "<string>"
-- >             "Addrs": [
-- >                 "<object>"
-- >             ]
-- >         }
-- >     ]
-- >     "Extra": "<string>"
-- > }
type ApiV0DhtFindpeer =
      "api" :> "v0" :> "dht" :> "findpeer"
    -- The ID of the peer to search for.
    :> QueryParam' '[Required, Strict] "arg" Text
    -- Print extra information.
    :> QueryParam "verbose" Bool
    :> Post '[JSON] Value

-- | Find peers in the DHT that can provide a specific value, given a key.
--
-- Response example:
--
-- > {
-- >     "ID": "<string>"
-- >     "Type": "<int>"
-- >     "Responses": [
-- >         {
-- >             "ID": "<string>"
-- >             "Addrs": [
-- >                 "<object>"
-- >             ]
-- >         }
-- >     ]
-- >     "Extra": "<string>"
-- > }
type ApiV0DhtFindprovs =
      "api" :> "v0" :> "dht" :> "findprovs"
    -- The key to find providers for.
    :> QueryParam' '[Required, Strict] "arg" Text
    -- Print extra information.
    :> QueryParam "verbose" Bool
    -- The number of providers to find. Default: 20.
    :> QueryParam "num-providers" Int
    :> Post '[JSON] Value

-- | Given a key, query the DHT for its best value.
--
-- Response example:
--
-- > {
-- >     "ID": "<string>"
-- >     "Type": "<int>"
-- >     "Responses": [
-- >         {
-- >             "ID": "<string>"
-- >             "Addrs": [
-- >                 "<object>"
-- >             ]
-- >         }
-- >     ]
-- >     "Extra": "<string>"
-- > }
type ApiV0DhtGet =
      "api" :> "v0" :> "dht" :> "get"
    -- The key to find a value for.
    :> QueryParam' '[Required, Strict] "arg" Text
    -- Print extra information.
    :> QueryParam "verbose" Bool
    :> Post '[JSON] Value

-- | Announce to the network that you are providing given values.
--
-- Response example:
--
-- > {
-- >     "ID": "<string>"
-- >     "Type": "<int>"
-- >     "Responses": [
-- >         {
-- >             "ID": "<string>"
-- >             "Addrs": [
-- >                 "<object>"
-- >             ]
-- >         }
-- >     ]
-- >     "Extra": "<string>"
-- > }
type ApiV0DhtProvide =
      "api" :> "v0" :> "dht" :> "provide"
    -- The key[s] to send provide records for.
    :> QueryParam' '[Required, Strict] "arg" Text
    -- Print extra information.
    :> QueryParam "verbose" Bool
    -- Recursively provide entire graph.
    :> QueryParam "recursive" Bool
    :> Post '[JSON] Value

-- | Write a key/value pair to the DHT.
--
-- Response example:
--
-- > {
-- >     "ID": "<string>"
-- >     "Type": "<int>"
-- >     "Responses": [
-- >         {
-- >             "ID": "<string>"
-- >             "Addrs": [
-- >                 "<object>"
-- >             ]
-- >         }
-- >     ]
-- >     "Extra": "<string>"
-- > }
type ApiV0DhtPut =
      "api" :> "v0" :> "dht" :> "put"
    -- The key to store the value at.
    :> QueryParam' '[Required, Strict] "arg" Text
    -- The value to store.
    :> QueryParam' '[Required, Strict] "arg" Text
    -- Print extra information.
    :> QueryParam "verbose" Bool
    :> Post '[JSON] Value

-- | Find the closest Peer IDs to a given Peer ID by querying the DHT.
--
-- Response example:
--
-- > {
-- >     "ID": "<string>"
-- >     "Type": "<int>"
-- >     "Responses": [
-- >         {
-- >             "ID": "<string>"
-- >             "Addrs": [
-- >                 "<object>"
-- >             ]
-- >         }
-- >     ]
-- >     "Extra": "<string>"
-- > }
type ApiV0DhtQuery =
      "api" :> "v0" :> "dht" :> "query"
    -- The peerID to run the query against.
    :> QueryParam' '[Required, Strict] "arg" Text
    -- Print extra information.
    :> QueryParam "verbose" Bool
    :> Post '[JSON] Value

-- | Clear inactive requests from the log.
type ApiV0DiagCmdsClear =
      "api" :> "v0" :> "diag" :> "cmds" :> "clear"
    :> Stream 'POST 200 NoFraming PlainText (SourceIO ByteString)

-- | Set how long to keep inactive requests in the log.
type ApiV0DiagCmdsSetTime =
      "api" :> "v0" :> "diag" :> "cmds" :> "set-time"
    -- Time to keep inactive requests in log.
    :> QueryParam' '[Required, Strict] "arg" Text
    :> Stream 'POST 200 NoFraming PlainText (SourceIO ByteString)

-- | Print system diagnostic information.
type ApiV0DiagSys =
      "api" :> "v0" :> "diag" :> "sys"
    :> Stream 'POST 200 NoFraming PlainText (SourceIO ByteString)

-- | Resolve DNS links.
--
-- Response example:
--
-- > {
-- >     "Path": "<string>"
-- > }
type ApiV0Dns =
      "api" :> "v0" :> "dns"
    -- The domain-name name to resolve.
    :> QueryParam' '[Required, Strict] "arg" Text
    -- Resolve until the result is not a DNS link.
    :> QueryParam "recursive" Bool
    :> Post '[JSON] Value

-- | List directory contents for Unix filesystem objects.
--
-- Response example:
--
-- > {
-- >     "Arguments": {
-- >         "<string>": "<string>"
-- >     }
-- >     "Objects": {
-- >         "<string>": {
-- >             "Hash": "<string>"
-- >             "Size": "<uint64>"
-- >             "Type": "<string>"
-- >             "Links": [
-- >                 {
-- >                     "Name": "<string>"
-- >                     "Hash": "<string>"
-- >                     "Size": "<uint64>"
-- >                     "Type": "<string>"
-- >                 }
-- >             ]
-- >         }
-- >     }
-- > }
type ApiV0FileLs =
      "api" :> "v0" :> "file" :> "ls"
    -- The path to the IPFS object(s) to list links from.
    :> QueryParam' '[Required, Strict] "arg" Text
    :> Post '[JSON] Value

-- | Change the cid version or hash function of the root node of a given path.
type ApiV0FilesChcid =
      "api" :> "v0" :> "files" :> "chcid"
    -- Path to change. Default: '/'.
    :> QueryParam' '[Required, Strict] "arg" Text
    -- Cid version to use. (experimental).
    :> QueryParam "cid-version" Int
    -- Hash function to use. Will set Cid version to 1 if used. (experimental).
    :> QueryParam "hash" Text
    :> Stream 'POST 200 NoFraming PlainText (SourceIO ByteString)

-- | Copy files into mfs.
type ApiV0FilesCp =
      "api" :> "v0" :> "files" :> "cp"
    -- Source object to copy.
    :> QueryParam' '[Required, Strict] "arg" Text
    -- Destination to copy object to.
    :> QueryParam' '[Required, Strict] "arg" Text
    :> Stream 'POST 200 NoFraming PlainText (SourceIO ByteString)

-- | Flush a given path's data to disk.
type ApiV0FilesFlush =
      "api" :> "v0" :> "files" :> "flush"
    -- Path to flush. Default: '/'.
    :> QueryParam' '[Required, Strict] "arg" Text
    :> Stream 'POST 200 NoFraming PlainText (SourceIO ByteString)

-- | List directories in the local mutable namespace.
--
-- Response example:
--
-- > {
-- >     "Entries": [
-- >         {
-- >             "Name": "<string>"
-- >             "Type": "<int>"
-- >             "Size": "<int64>"
-- >             "Hash": "<string>"
-- >         }
-- >     ]
-- > }
type ApiV0FilesLs =
      "api" :> "v0" :> "files" :> "ls"
    -- Path to show listing for. Defaults to '/'.
    :> QueryParam' '[Required, Strict] "arg" Text
    -- Use long listing format.
    :> QueryParam "l" Bool
    :> Post '[JSON] Value

-- | Make directories.
type ApiV0FilesMkdir =
      "api" :> "v0" :> "files" :> "mkdir"
    -- Path to dir to make.
    :> QueryParam' '[Required, Strict] "arg" Text
    -- No error if existing, make parent directories as needed.
    :> QueryParam "parents" Bool
    -- Cid version to use. (experimental).
    :> QueryParam "cid-version" Int
    -- Hash function to use. Will set Cid version to 1 if used. (experimental).
    :> QueryParam "hash" Text
    :> Stream 'POST 200 NoFraming PlainText (SourceIO ByteString)

-- | Move files.
type ApiV0FilesMv =
      "api" :> "v0" :> "files" :> "mv"
    -- Source file to move.
    :> QueryParam' '[Required, Strict] "arg" Text
    -- Destination path for file to be moved to.
    :> QueryParam' '[Required, Strict] "arg" Text
    :> Stream 'POST 200 NoFraming PlainText (SourceIO ByteString)

-- | Read a file in a given mfs.
type ApiV0FilesRead =
      "api" :> "v0" :> "files" :> "read"
    -- Path to file to be read.
    :> QueryParam' '[Required, Strict] "arg" Text
    -- Byte offset to begin reading from.
    :> QueryParam "offset" Int
    -- Maximum number of bytes to read.
    :> QueryParam "count" Int
    :> Stream 'POST 200 NoFraming PlainText (SourceIO ByteString)

-- | Remove a file.
type ApiV0FilesRm =
      "api" :> "v0" :> "files" :> "rm"
    -- File to remove.
    :> QueryParam' '[Required, Strict] "arg" Text
    -- Recursively remove directories.
    :> QueryParam "recursive" Bool
    :> Stream 'POST 200 NoFraming PlainText (SourceIO ByteString)

-- | Display file status.
--
-- Response example:
--
-- > {
-- >     "Hash": "<string>"
-- >     "Size": "<uint64>"
-- >     "CumulativeSize": "<uint64>"
-- >     "Blocks": "<int>"
-- >     "Type": "<string>"
-- >     "WithLocality": "<bool>"
-- >     "Local": "<bool>"
-- >     "SizeLocal": "<uint64>"
-- > }
type ApiV0FilesStat =
      "api" :> "v0" :> "files" :> "stat"
    -- Path to node to stat.
    :> QueryParam' '[Required, Strict] "arg" Text
    -- Print statistics in given format. Allowed tokens: <hash> <size> <cumulsize>
    -- <type> <childs>. Conflicts with other format options. Default: <hash> Size:
    -- <size> CumulativeSize: <cumulsize> ChildBlocks: <childs> Type: <type>.
    :> QueryParam "format" Text
    -- Print only hash. Implies '--format=<hash>'. Conflicts with other format options.
    :> QueryParam "hash" Bool
    -- Print only size. Implies '--format=<cumulsize>'. Conflicts with other format
    -- options.
    :> QueryParam "size" Bool
    -- Compute the amount of the dag that is local, and if possible the total size.
    :> QueryParam "with-local" Bool
    :> Post '[JSON] Value

-- | Write to a mutable file in a given filesystem.
type ApiV0FilesWrite =
      "api" :> "v0" :> "files" :> "write"
    -- Path to write to.
    :> QueryParam' '[Required, Strict] "arg" Text
    :> ReqBody '[MultipartFormData] L.ByteString
    -- Byte offset to begin writing at.
    :> QueryParam "offset" Int
    -- Create the file if it does not exist.
    :> QueryParam "create" Bool
    -- Truncate the file to size zero before writing.
    :> QueryParam "truncate" Bool
    -- Maximum number of bytes to read.
    :> QueryParam "count" Int
    -- Use raw blocks for newly created leaf nodes. (experimental).
    :> QueryParam "raw-leaves" Bool
    -- Cid version to use. (experimental).
    :> QueryParam "cid-version" Int
    -- Hash function to use. Will set Cid version to 1 if used. (experimental).
    :> QueryParam "hash" Text
    :> Stream 'POST 200 NoFraming PlainText (SourceIO ByteString)

-- | List blocks that are both in the filestore and standard block storage.
--
-- Response example:
--
-- > {
-- >     "Ref": "<string>"
-- >     "Err": "<string>"
-- > }
type ApiV0FilestoreDups =
      "api" :> "v0" :> "filestore" :> "dups"
    :> Post '[JSON] Value

-- | List objects in filestore.
--
-- Response example:
--
-- > {
-- >     "Status": "<int32>"
-- >     "ErrorMsg": "<string>"
-- >     "Key": "<string>"
-- >     "FilePath": "<string>"
-- >     "Offset": "<uint64>"
-- >     "Size": "<uint64>"
-- > }
type ApiV0FilestoreLs =
      "api" :> "v0" :> "filestore" :> "ls"
    -- Cid of objects to list.
    :> QueryParam' '[Required, Strict] "arg" Text
    -- sort the results based on the path of the backing file.
    :> QueryParam "file-order" Bool
    :> Post '[JSON] Value

-- | Verify objects in filestore.
--
-- Response example:
--
-- > {
-- >     "Status": "<int32>"
-- >     "ErrorMsg": "<string>"
-- >     "Key": "<string>"
-- >     "FilePath": "<string>"
-- >     "Offset": "<uint64>"
-- >     "Size": "<uint64>"
-- > }
type ApiV0FilestoreVerify =
      "api" :> "v0" :> "filestore" :> "verify"
    -- Cid of objects to verify.
    :> QueryParam' '[Required, Strict] "arg" Text
    -- verify the objects based on the order of the backing file.
    :> QueryParam "file-order" Bool
    :> Post '[JSON] Value

-- | Download IPFS objects.
type ApiV0Get =
      "api" :> "v0" :> "get"
    -- The path to the IPFS object(s) to be outputted.
    :> QueryParam' '[Required, Strict] "arg" Text
    -- The path where the output should be stored.
    :> QueryParam "output" Text
    -- Output a TAR archive.
    :> QueryParam "archive" Bool
    -- Compress the output with GZIP compression.
    :> QueryParam "compress" Bool
    -- The level of compression (1-9).
    :> QueryParam "compression-level" Int
    :> Stream 'POST 200 NoFraming PlainText (SourceIO ByteString)

-- | Show ipfs node id info.
--
-- Response example:
--
-- > {
-- >     "ID": "<string>"
-- >     "PublicKey": "<string>"
-- >     "Addresses": [
-- >         "<string>"
-- >     ]
-- >     "AgentVersion": "<string>"
-- >     "ProtocolVersion": "<string>"
-- > }
type ApiV0Id =
      "api" :> "v0" :> "id"
    -- Peer.ID of node to look up.
    :> QueryParam' '[Required, Strict] "arg" Text
    -- Optional output format.
    :> QueryParam "format" Text
    :> Post '[JSON] Value

-- | Create a new keypair
--
-- Response example:
--
-- > {
-- >     "Name": "<string>"
-- >     "Id": "<string>"
-- > }
type ApiV0KeyGen =
      "api" :> "v0" :> "key" :> "gen"
    -- name of key to create
    :> QueryParam' '[Required, Strict] "arg" Text
    -- type of the key to create [rsa, ed25519].
    :> QueryParam "type" Text
    -- size of the key to generate.
    :> QueryParam "size" Int
    :> Post '[JSON] Value

-- | List all local keypairs
--
-- Response example:
--
-- > {
-- >     "Keys": [
-- >         {
-- >             "Name": "<string>"
-- >             "Id": "<string>"
-- >         }
-- >     ]
-- > }
type ApiV0KeyList =
      "api" :> "v0" :> "key" :> "list"
    -- Show extra information about keys.
    :> QueryParam "l" Bool
    :> Post '[JSON] Value

-- | Rename a keypair
--
-- Response example:
--
-- > {
-- >     "Was": "<string>"
-- >     "Now": "<string>"
-- >     "Id": "<string>"
-- >     "Overwrite": "<bool>"
-- > }
type ApiV0KeyRename =
      "api" :> "v0" :> "key" :> "rename"
    -- name of key to rename
    :> QueryParam' '[Required, Strict] "arg" Text
    -- new name of the key
    :> QueryParam' '[Required, Strict] "arg" Text
    -- Allow to overwrite an existing key.
    :> QueryParam "force" Bool
    :> Post '[JSON] Value

-- | Remove a keypair
--
-- Response example:
--
-- > {
-- >     "Keys": [
-- >         {
-- >             "Name": "<string>"
-- >             "Id": "<string>"
-- >         }
-- >     ]
-- > }
type ApiV0KeyRm =
      "api" :> "v0" :> "key" :> "rm"
    -- names of keys to remove
    :> QueryParam' '[Required, Strict] "arg" Text
    -- Show extra information about keys.
    :> QueryParam "l" Bool
    :> Post '[JSON] Value

-- | Change the logging level.
--
-- Response example:
--
-- > {
-- >     "Message": "<string>"
-- > }
type ApiV0LogLevel =
      "api" :> "v0" :> "log" :> "level"
    -- The subsystem logging identifier. Use 'all' for all subsystems.
    :> QueryParam' '[Required, Strict] "arg" Text
    -- The log level, with 'debug' the most verbose and 'critical' the least verbose.
    -- One of: debug, info, warning, error, critical.
    :> QueryParam' '[Required, Strict] "arg" Text
    :> Post '[JSON] Value

-- | List the logging subsystems.
--
-- Response example:
--
-- > {
-- >     "Strings": [
-- >         "<string>"
-- >     ]
-- > }
type ApiV0LogLs =
      "api" :> "v0" :> "log" :> "ls"
    :> Post '[JSON] Value

-- | Read the event log.
type ApiV0LogTail =
      "api" :> "v0" :> "log" :> "tail"
    :> Stream 'POST 200 NoFraming PlainText (SourceIO ByteString)

-- | List directory contents for Unix filesystem objects.
--
-- Response example:
--
-- > {
-- >     "Objects": [
-- >         {
-- >             "Hash": "<string>"
-- >             "Links": [
-- >                 {
-- >                     "Name": "<string>"
-- >                     "Hash": "<string>"
-- >                     "Size": "<uint64>"
-- >                     "Type": "<int32>"
-- >                 }
-- >             ]
-- >         }
-- >     ]
-- > }
type ApiV0Ls =
      "api" :> "v0" :> "ls"
    -- The path to the IPFS object(s) to list links from.
    :> QueryParam' '[Required, Strict] "arg" Text
    -- Print table headers (Hash, Size, Name).
    :> QueryParam "headers" Bool
    -- Resolve linked objects to find out their types. Default: true.
    :> QueryParam "resolve-type" Bool
    :> Post '[JSON] Value

-- | Mounts IPFS to the filesystem (read-only).
--
-- Response example:
--
-- > {
-- >     "IPFS": "<string>"
-- >     "IPNS": "<string>"
-- >     "FuseAllowOther": "<bool>"
-- > }
type ApiV0Mount =
      "api" :> "v0" :> "mount"
    -- The path where IPFS should be mounted.
    :> QueryParam "ipfs-path" Text
    -- The path where IPNS should be mounted.
    :> QueryParam "ipns-path" Text
    :> Post '[JSON] Value

-- | Publish IPNS names.
--
-- Response example:
--
-- > {
-- >     "Name": "<string>"
-- >     "Value": "<string>"
-- > }
type ApiV0NamePublish =
      "api" :> "v0" :> "name" :> "publish"
    -- ipfs path of the object to be published.
    :> QueryParam' '[Required, Strict] "arg" Text
    -- Resolve given path before publishing. Default: true.
    :> QueryParam "resolve" Bool
    -- Time duration that the record will be valid for. Default: 24h. This accepts
    -- durations such as "300s", "1.5h" or "2h45m". Valid time units are "ns", "us" (or
    -- "µs"), "ms", "s", "m", "h".
    :> QueryParam "lifetime" Text
    -- Time duration this record should be cached for (caution: experimental).
    :> QueryParam "ttl" Text
    -- Name of the key to be used or a valid PeerID, as listed by 'ipfs key list -l'.
    -- Default: Default: self..
    :> QueryParam "key" Text
    :> Post '[JSON] Value

-- | Cancel a name subscription
--
-- Response example:
--
-- > {
-- >     "Canceled": "<bool>"
-- > }
type ApiV0NamePubsubCancel =
      "api" :> "v0" :> "name" :> "pubsub" :> "cancel"
    -- Name to cancel the subscription for.
    :> QueryParam' '[Required, Strict] "arg" Text
    :> Post '[JSON] Value

-- | Query the state of IPNS pubsub
--
-- Response example:
--
-- > {
-- >     "Enabled": "<bool>"
-- > }
type ApiV0NamePubsubState =
      "api" :> "v0" :> "name" :> "pubsub" :> "state"
    :> Post '[JSON] Value

-- | Show current name subscriptions
--
-- Response example:
--
-- > {
-- >     "Strings": [
-- >         "<string>"
-- >     ]
-- > }
type ApiV0NamePubsubSubs =
      "api" :> "v0" :> "name" :> "pubsub" :> "subs"
    :> Post '[JSON] Value

-- | Resolve IPNS names.
--
-- Response example:
--
-- > {
-- >     "Path": "<string>"
-- > }
type ApiV0NameResolve =
      "api" :> "v0" :> "name" :> "resolve"
    -- The IPNS name to resolve. Defaults to your node's peerID.
    :> QueryParam' '[Required, Strict] "arg" Text
    -- Resolve until the result is not an IPNS name.
    :> QueryParam "recursive" Bool
    -- Do not use cached entries.
    :> QueryParam "nocache" Bool
    -- Number of records to request for DHT resolution.
    :> QueryParam "dht-record-count" Word
    -- Max time to collect values during DHT resolution eg "30s". Pass 0 for no
    -- timeout.
    :> QueryParam "dht-timeout" Text
    :> Post '[JSON] Value

-- | Output the raw bytes of an IPFS object.
type ApiV0ObjectData =
      "api" :> "v0" :> "object" :> "data"
    -- Key of the object to retrieve, in base58-encoded multihash format.
    :> QueryParam' '[Required, Strict] "arg" Text
    :> Stream 'POST 200 NoFraming PlainText (SourceIO ByteString)

-- | Display the diff between two ipfs objects.
--
-- Response example:
--
-- > {
-- >     "Changes": [
-- >         {
-- >             "Type": "<int>"
-- >             "Path": "<string>"
-- >             "Before": "<string>"
-- >             "After": "<string>"
-- >         }
-- >     ]
-- > }
type ApiV0ObjectDiff =
      "api" :> "v0" :> "object" :> "diff"
    -- Object to diff against.
    :> QueryParam' '[Required, Strict] "arg" Text
    -- Object to diff.
    :> QueryParam' '[Required, Strict] "arg" Text
    -- Print extra information.
    :> QueryParam "verbose" Bool
    :> Post '[JSON] Value

-- | Get and serialize the DAG node named by <key>.
--
-- Response example:
--
-- > {
-- >     "Links": [
-- >         {
-- >             "Name": "<string>"
-- >             "Hash": "<string>"
-- >             "Size": "<uint64>"
-- >         }
-- >     ]
-- >     "Data": "<string>"
-- > }
type ApiV0ObjectGet =
      "api" :> "v0" :> "object" :> "get"
    -- Key of the object to retrieve, in base58-encoded multihash format.
    :> QueryParam' '[Required, Strict] "arg" Text
    :> Post '[JSON] Value

-- | Output the links pointed to by the specified object.
--
-- Response example:
--
-- > {
-- >     "Hash": "<string>"
-- >     "Links": [
-- >         {
-- >             "Name": "<string>"
-- >             "Hash": "<string>"
-- >             "Size": "<uint64>"
-- >         }
-- >     ]
-- > }
type ApiV0ObjectLinks =
      "api" :> "v0" :> "object" :> "links"
    -- Key of the object to retrieve, in base58-encoded multihash format.
    :> QueryParam' '[Required, Strict] "arg" Text
    -- Print table headers (Hash, Size, Name).
    :> QueryParam "headers" Bool
    :> Post '[JSON] Value

-- | Create a new object from an ipfs template.
--
-- Response example:
--
-- > {
-- >     "Hash": "<string>"
-- >     "Links": [
-- >         {
-- >             "Name": "<string>"
-- >             "Hash": "<string>"
-- >             "Size": "<uint64>"
-- >         }
-- >     ]
-- > }
type ApiV0ObjectNew =
      "api" :> "v0" :> "object" :> "new"
    -- Template to use. Optional.
    :> QueryParam' '[Required, Strict] "arg" Text
    :> Post '[JSON] Value

-- | Add a link to a given object.
--
-- Response example:
--
-- > {
-- >     "Hash": "<string>"
-- >     "Links": [
-- >         {
-- >             "Name": "<string>"
-- >             "Hash": "<string>"
-- >             "Size": "<uint64>"
-- >         }
-- >     ]
-- > }
type ApiV0ObjectPatchAddLink =
      "api" :> "v0" :> "object" :> "patch" :> "add-link"
    -- The hash of the node to modify.
    :> QueryParam' '[Required, Strict] "arg" Text
    -- Name of link to create.
    :> QueryParam' '[Required, Strict] "arg" Text
    -- IPFS object to add link to.
    :> QueryParam' '[Required, Strict] "arg" Text
    -- Create intermediary nodes.
    :> QueryParam "create" Bool
    :> Post '[JSON] Value

-- | Append data to the data segment of a dag node.
--
-- Response example:
--
-- > {
-- >     "Hash": "<string>"
-- >     "Links": [
-- >         {
-- >             "Name": "<string>"
-- >             "Hash": "<string>"
-- >             "Size": "<uint64>"
-- >         }
-- >     ]
-- > }
type ApiV0ObjectPatchAppendData =
      "api" :> "v0" :> "object" :> "patch" :> "append-data"
    -- The hash of the node to modify.
    :> QueryParam' '[Required, Strict] "arg" Text
    :> ReqBody '[MultipartFormData] L.ByteString
    :> Post '[JSON] Value

-- | Remove a link from an object.
--
-- Response example:
--
-- > {
-- >     "Hash": "<string>"
-- >     "Links": [
-- >         {
-- >             "Name": "<string>"
-- >             "Hash": "<string>"
-- >             "Size": "<uint64>"
-- >         }
-- >     ]
-- > }
type ApiV0ObjectPatchRmLink =
      "api" :> "v0" :> "object" :> "patch" :> "rm-link"
    -- The hash of the node to modify.
    :> QueryParam' '[Required, Strict] "arg" Text
    -- Name of the link to remove.
    :> QueryParam' '[Required, Strict] "arg" Text
    :> Post '[JSON] Value

-- | Set the data field of an IPFS object.
--
-- Response example:
--
-- > {
-- >     "Hash": "<string>"
-- >     "Links": [
-- >         {
-- >             "Name": "<string>"
-- >             "Hash": "<string>"
-- >             "Size": "<uint64>"
-- >         }
-- >     ]
-- > }
type ApiV0ObjectPatchSetData =
      "api" :> "v0" :> "object" :> "patch" :> "set-data"
    -- The hash of the node to modify.
    :> QueryParam' '[Required, Strict] "arg" Text
    :> ReqBody '[MultipartFormData] L.ByteString
    :> Post '[JSON] Value

-- | Store input as a DAG object, print its key.
--
-- Response example:
--
-- > {
-- >     "Hash": "<string>"
-- >     "Links": [
-- >         {
-- >             "Name": "<string>"
-- >             "Hash": "<string>"
-- >             "Size": "<uint64>"
-- >         }
-- >     ]
-- > }
type ApiV0ObjectPut =
      "api" :> "v0" :> "object" :> "put"
    :> ReqBody '[MultipartFormData] L.ByteString
    -- Encoding type of input data. One of: {"protobuf", "json"}. Default: json.
    :> QueryParam "inputenc" Text
    -- Encoding type of the data field, either "text" or "base64". Default: text.
    :> QueryParam "datafieldenc" Text
    -- Pin this object when adding.
    :> QueryParam "pin" Bool
    -- Write minimal output.
    :> QueryParam "quiet" Bool
    :> Post '[JSON] Value

-- | Get stats for the DAG node named by <key>.
--
-- Response example:
--
-- > {
-- >     "Hash": "<string>"
-- >     "NumLinks": "<int>"
-- >     "BlockSize": "<int>"
-- >     "LinksSize": "<int>"
-- >     "DataSize": "<int>"
-- >     "CumulativeSize": "<int>"
-- > }
type ApiV0ObjectStat =
      "api" :> "v0" :> "object" :> "stat"
    -- Key of the object to retrieve, in base58-encoded multihash format.
    :> QueryParam' '[Required, Strict] "arg" Text
    :> Post '[JSON] Value

-- | Close active p2p listener.
type ApiV0P2pListenerClose =
      "api" :> "v0" :> "p2p" :> "listener" :> "close"
    -- P2P listener protocol
    :> QueryParam' '[Required, Strict] "arg" Text
    -- Close all listeners.
    :> QueryParam "all" Bool
    :> Stream 'POST 200 NoFraming PlainText (SourceIO ByteString)

-- | List active p2p listeners.
--
-- Response example:
--
-- > {
-- >     "Listeners": [
-- >         {
-- >             "Protocol": "<string>"
-- >             "Address": "<string>"
-- >         }
-- >     ]
-- > }
type ApiV0P2pListenerLs =
      "api" :> "v0" :> "p2p" :> "listener" :> "ls"
    -- Print table headers (HandlerID, Protocol, Local, Remote).
    :> QueryParam "headers" Bool
    :> Post '[JSON] Value

-- | Forward p2p connections to a network multiaddr.
type ApiV0P2pListenerOpen =
      "api" :> "v0" :> "p2p" :> "listener" :> "open"
    -- Protocol identifier.
    :> QueryParam' '[Required, Strict] "arg" Text
    -- Request handling application address.
    :> QueryParam' '[Required, Strict] "arg" Text
    :> Stream 'POST 200 NoFraming PlainText (SourceIO ByteString)

-- | Close active p2p stream.
type ApiV0P2pStreamClose =
      "api" :> "v0" :> "p2p" :> "stream" :> "close"
    -- Stream HandlerID
    :> QueryParam' '[Required, Strict] "arg" Text
    -- Close all streams.
    :> QueryParam "all" Bool
    :> Stream 'POST 200 NoFraming PlainText (SourceIO ByteString)

-- | Dial to a p2p listener.
type ApiV0P2pStreamDial =
      "api" :> "v0" :> "p2p" :> "stream" :> "dial"
    -- Remote peer to connect to
    :> QueryParam' '[Required, Strict] "arg" Text
    -- Protocol identifier.
    :> QueryParam' '[Required, Strict] "arg" Text
    -- Address to listen for connection/s (default: /ip4/127.0.0.1/tcp/0).
    :> QueryParam' '[Required, Strict] "arg" Text
    :> Stream 'POST 200 NoFraming PlainText (SourceIO ByteString)

-- | List active p2p streams.
--
-- Response example:
--
-- > {
-- >     "Streams": [
-- >         {
-- >             "HandlerID": "<string>"
-- >             "Protocol": "<string>"
-- >             "LocalPeer": "<string>"
-- >             "LocalAddress": "<string>"
-- >             "RemotePeer": "<string>"
-- >             "RemoteAddress": "<string>"
-- >         }
-- >     ]
-- > }
type ApiV0P2pStreamLs =
      "api" :> "v0" :> "p2p" :> "stream" :> "ls"
    -- Print table headers (HagndlerID, Protocol, Local, Remote).
    :> QueryParam "headers" Bool
    :> Post '[JSON] Value

-- | Pin objects to local storage.
--
-- Response example:
--
-- > {
-- >     "Pins": [
-- >         "<string>"
-- >     ]
-- >     "Progress": "<int>"
-- > }
type ApiV0PinAdd =
      "api" :> "v0" :> "pin" :> "add"
    -- Path to object(s) to be pinned.
    :> QueryParam' '[Required, Strict] "arg" Text
    -- Recursively pin the object linked to by the specified object(s). Default: true.
    :> QueryParam "recursive" Bool
    -- Show progress.
    :> QueryParam "progress" Bool
    :> Post '[JSON] Value

-- | List objects pinned to local storage.
--
-- Response example:
--
-- > {
-- >     "Keys": {
-- >         "<string>": {
-- >             "Type": "<string>"
-- >         }
-- >     }
-- > }
type ApiV0PinLs =
      "api" :> "v0" :> "pin" :> "ls"
    -- Path to object(s) to be listed.
    :> QueryParam' '[Required, Strict] "arg" Text
    -- The type of pinned keys to list. Can be "direct", "indirect", "recursive", or
    -- "all". Default: all.
    :> QueryParam "type" Text
    -- Write just hashes of objects.
    :> QueryParam "quiet" Bool
    :> Post '[JSON] Value

-- | Remove pinned objects from local storage.
--
-- Response example:
--
-- > {
-- >     "Pins": [
-- >         "<string>"
-- >     ]
-- > }
type ApiV0PinRm =
      "api" :> "v0" :> "pin" :> "rm"
    -- Path to object(s) to be unpinned.
    :> QueryParam' '[Required, Strict] "arg" Text
    -- Recursively unpin the object linked to by the specified object(s). Default:
    -- true.
    :> QueryParam "recursive" Bool
    :> Post '[JSON] Value

-- | Update a recursive pin
--
-- Response example:
--
-- > {
-- >     "Pins": [
-- >         "<string>"
-- >     ]
-- > }
type ApiV0PinUpdate =
      "api" :> "v0" :> "pin" :> "update"
    -- Path to old object.
    :> QueryParam' '[Required, Strict] "arg" Text
    -- Path to new object to be pinned.
    :> QueryParam' '[Required, Strict] "arg" Text
    -- Remove the old pin. Default: true.
    :> QueryParam "unpin" Bool
    :> Post '[JSON] Value

-- | Verify that recursive pins are complete.
--
-- Response example:
--
-- > {
-- >     "Cid": "<string>"
-- >     "PinStatus": {
-- >         "Ok": "<bool>"
-- >         "BadNodes": [
-- >             {
-- >                 "Cid": "<string>"
-- >                 "Err": "<string>"
-- >             }
-- >         ]
-- >     }
-- > }
type ApiV0PinVerify =
      "api" :> "v0" :> "pin" :> "verify"
    -- Also write the hashes of non-broken pins.
    :> QueryParam "verbose" Bool
    -- Write just hashes of broken pins.
    :> QueryParam "quiet" Bool
    :> Post '[JSON] Value

-- | Send echo request packets to IPFS hosts.
--
-- Response example:
--
-- > {
-- >     "Success": "<bool>"
-- >     "Time": "<int64>"
-- >     "Text": "<string>"
-- > }
type ApiV0Ping =
      "api" :> "v0" :> "ping"
    -- ID of peer to be pinged.
    :> QueryParam' '[Required, Strict] "arg" Text
    -- Number of ping messages to send. Default: 10.
    :> QueryParam "count" Int
    :> Post '[JSON] Value

-- | List subscribed topics by name.
--
-- Response example:
--
-- > {
-- >     "Strings": [
-- >         "<string>"
-- >     ]
-- > }
type ApiV0PubsubLs =
      "api" :> "v0" :> "pubsub" :> "ls"
    :> Post '[JSON] Value

-- | List peers we are currently pubsubbing with.
--
-- Response example:
--
-- > {
-- >     "Strings": [
-- >         "<string>"
-- >     ]
-- > }
type ApiV0PubsubPeers =
      "api" :> "v0" :> "pubsub" :> "peers"
    -- topic to list connected peers of
    :> QueryParam' '[Required, Strict] "arg" Text
    :> Post '[JSON] Value

-- | Publish a message to a given pubsub topic.
type ApiV0PubsubPub =
      "api" :> "v0" :> "pubsub" :> "pub"
    -- Topic to publish to.
    :> QueryParam' '[Required, Strict] "arg" Text
    -- Payload of message to publish.
    :> QueryParam' '[Required, Strict] "arg" Text
    :> Stream 'POST 200 NoFraming PlainText (SourceIO ByteString)

-- | Subscribe to messages on a given topic.
--
-- Response example:
--
-- > {
-- >     "Message": {
-- >         "From": [
-- >             "<uint8>"
-- >         ]
-- >         "Data": [
-- >             "<uint8>"
-- >         ]
-- >         "Seqno": [
-- >             "<uint8>"
-- >         ]
-- >         "TopicIDs": [
-- >             "<string>"
-- >         ]
-- >         "XXX_unrecognized": [
-- >             "<uint8>"
-- >         ]
-- >     }
-- > }
type ApiV0PubsubSub =
      "api" :> "v0" :> "pubsub" :> "sub"
    -- String name of topic to subscribe to.
    :> QueryParam' '[Required, Strict] "arg" Text
    -- try to discover other peers subscribed to the same topic.
    :> QueryParam "discover" Bool
    :> Post '[JSON] Value

-- | List all local references.
--
-- Response example:
--
-- > {
-- >     "Ref": "<string>"
-- >     "Err": "<string>"
-- > }
type ApiV0RefsLocal =
      "api" :> "v0" :> "refs" :> "local"
    :> Post '[JSON] Value

-- | Remove repo lockfiles.
--
-- Response example:
--
-- > {
-- >     "Message": "<string>"
-- > }
type ApiV0RepoFsck =
      "api" :> "v0" :> "repo" :> "fsck"
    :> Post '[JSON] Value

-- | Perform a garbage collection sweep on the repo.
--
-- Response example:
--
-- > {
-- >     "Key": "<string>"
-- >     "Error": "<string>"
-- > }
type ApiV0RepoGc =
      "api" :> "v0" :> "repo" :> "gc"
    -- Stream errors.
    :> QueryParam "stream-errors" Bool
    -- Write minimal output.
    :> QueryParam "quiet" Bool
    :> Post '[JSON] Value

-- | Get stats for the currently used repo.
--
-- Response example:
--
-- > {
-- >     "NumObjects": "<uint64>"
-- >     "RepoSize": "<uint64>"
-- >     "RepoPath": "<string>"
-- >     "Version": "<string>"
-- >     "StorageMax": "<uint64>"
-- > }
type ApiV0RepoStat =
      "api" :> "v0" :> "repo" :> "stat"
    -- Output RepoSize in MiB.
    :> QueryParam "human" Bool
    :> Post '[JSON] Value

-- | Verify all blocks in repo are not corrupted.
--
-- Response example:
--
-- > {
-- >     "Msg": "<string>"
-- >     "Progress": "<int>"
-- > }
type ApiV0RepoVerify =
      "api" :> "v0" :> "repo" :> "verify"
    :> Post '[JSON] Value

-- | Show the repo version.
--
-- Response example:
--
-- > {
-- >     "Version": "<string>"
-- > }
type ApiV0RepoVersion =
      "api" :> "v0" :> "repo" :> "version"
    -- Write minimal output.
    :> QueryParam "quiet" Bool
    :> Post '[JSON] Value

-- | Resolve the value of names to IPFS.
--
-- Response example:
--
-- > {
-- >     "Path": "<string>"
-- > }
type ApiV0Resolve =
      "api" :> "v0" :> "resolve"
    -- The name to resolve.
    :> QueryParam' '[Required, Strict] "arg" Text
    -- Resolve until the result is an IPFS name.
    :> QueryParam "recursive" Bool
    -- Number of records to request for DHT resolution.
    :> QueryParam "dht-record-count" Word
    -- Max time to collect values during DHT resolution eg "30s". Pass 0 for no
    -- timeout.
    :> QueryParam "dht-timeout" Text
    :> Post '[JSON] Value

-- | Shut down the ipfs daemon
type ApiV0Shutdown =
      "api" :> "v0" :> "shutdown"
    :> Stream 'POST 200 NoFraming PlainText (SourceIO ByteString)

-- | Show some diagnostic information on the bitswap agent.
--
-- Response example:
--
-- > {
-- >     "ProvideBufLen": "<int>"
-- >     "Wantlist": [
-- >         "<string>"
-- >     ]
-- >     "Peers": [
-- >         "<string>"
-- >     ]
-- >     "BlocksReceived": "<uint64>"
-- >     "DataReceived": "<uint64>"
-- >     "BlocksSent": "<uint64>"
-- >     "DataSent": "<uint64>"
-- >     "DupBlksReceived": "<uint64>"
-- >     "DupDataReceived": "<uint64>"
-- > }
type ApiV0StatsBitswap =
      "api" :> "v0" :> "stats" :> "bitswap"
    :> Post '[JSON] Value

-- | Print ipfs bandwidth information.
--
-- Response example:
--
-- > {
-- >     "TotalIn": "<int64>"
-- >     "TotalOut": "<int64>"
-- >     "RateIn": "<float64>"
-- >     "RateOut": "<float64>"
-- > }
type ApiV0StatsBw =
      "api" :> "v0" :> "stats" :> "bw"
    -- Specify a peer to print bandwidth for.
    :> QueryParam "peer" Text
    -- Specify a protocol to print bandwidth for.
    :> QueryParam "proto" Text
    -- Print bandwidth at an interval.
    :> QueryParam "poll" Bool
    -- Time interval to wait between updating output, if 'poll' is true. This accepts
    -- durations such as "300s", "1.5h" or "2h45m". Valid time units are: "ns", "us"
    -- (or "µs"), "ms", "s", "m", "h". Default: 1s.
    :> QueryParam "interval" Text
    :> Post '[JSON] Value

-- | Get stats for the currently used repo.
--
-- Response example:
--
-- > {
-- >     "NumObjects": "<uint64>"
-- >     "RepoSize": "<uint64>"
-- >     "RepoPath": "<string>"
-- >     "Version": "<string>"
-- >     "StorageMax": "<uint64>"
-- > }
type ApiV0StatsRepo =
      "api" :> "v0" :> "stats" :> "repo"
    -- Output RepoSize in MiB.
    :> QueryParam "human" Bool
    :> Post '[JSON] Value

-- | List interface listening addresses.
--
-- Response example:
--
-- > {
-- >     "Strings": [
-- >         "<string>"
-- >     ]
-- > }
type ApiV0SwarmAddrsListen =
      "api" :> "v0" :> "swarm" :> "addrs" :> "listen"
    :> Post '[JSON] Value

-- | List local addresses.
--
-- Response example:
--
-- > {
-- >     "Strings": [
-- >         "<string>"
-- >     ]
-- > }
type ApiV0SwarmAddrsLocal =
      "api" :> "v0" :> "swarm" :> "addrs" :> "local"
    -- Show peer ID in addresses.
    :> QueryParam "id" Bool
    :> Post '[JSON] Value

-- | Open connection to a given address.
--
-- Response example:
--
-- > {
-- >     "Strings": [
-- >         "<string>"
-- >     ]
-- > }
type ApiV0SwarmConnect =
      "api" :> "v0" :> "swarm" :> "connect"
    -- Address of peer to connect to.
    :> QueryParam' '[Required, Strict] "arg" Text
    :> Post '[JSON] Value

-- | Close connection to a given address.
--
-- Response example:
--
-- > {
-- >     "Strings": [
-- >         "<string>"
-- >     ]
-- > }
type ApiV0SwarmDisconnect =
      "api" :> "v0" :> "swarm" :> "disconnect"
    -- Address of peer to disconnect from.
    :> QueryParam' '[Required, Strict] "arg" Text
    :> Post '[JSON] Value

-- | Add an address filter.
--
-- Response example:
--
-- > {
-- >     "Strings": [
-- >         "<string>"
-- >     ]
-- > }
type ApiV0SwarmFiltersAdd =
      "api" :> "v0" :> "swarm" :> "filters" :> "add"
    -- Multiaddr to filter.
    :> QueryParam' '[Required, Strict] "arg" Text
    :> Post '[JSON] Value

-- | Remove an address filter.
--
-- Response example:
--
-- > {
-- >     "Strings": [
-- >         "<string>"
-- >     ]
-- > }
type ApiV0SwarmFiltersRm =
      "api" :> "v0" :> "swarm" :> "filters" :> "rm"
    -- Multiaddr filter to remove.
    :> QueryParam' '[Required, Strict] "arg" Text
    :> Post '[JSON] Value

-- | List peers with open connections.
--
-- Response example:
--
-- > {
-- >     "Peers": [
-- >         {
-- >             "Addr": "<string>"
-- >             "Peer": "<string>"
-- >             "Latency": "<string>"
-- >             "Muxer": "<string>"
-- >             "Streams": [
-- >                 {
-- >                     "Protocol": "<string>"
-- >                 }
-- >             ]
-- >         }
-- >     ]
-- > }
type ApiV0SwarmPeers =
      "api" :> "v0" :> "swarm" :> "peers"
    -- display all extra information.
    :> QueryParam "verbose" Bool
    -- Also list information about open streams for each peer.
    :> QueryParam "streams" Bool
    -- Also list information about latency to each peer.
    :> QueryParam "latency" Bool
    :> Post '[JSON] Value

-- | Import a tar file into ipfs.
--
-- Response example:
--
-- > {
-- >     "Name": "<string>"
-- >     "Hash": "<string>"
-- >     "Bytes": "<int64>"
-- >     "Size": "<string>"
-- > }
type ApiV0TarAdd =
      "api" :> "v0" :> "tar" :> "add"
    :> ReqBody '[MultipartFormData] L.ByteString
    :> Post '[JSON] Value

-- | Export a tar file from IPFS.
type ApiV0TarCat =
      "api" :> "v0" :> "tar" :> "cat"
    -- ipfs path of archive to export.
    :> QueryParam' '[Required, Strict] "arg" Text
    :> Stream 'POST 200 NoFraming PlainText (SourceIO ByteString)

-- |
type ApiV0Update =
      "api" :> "v0" :> "update"
    -- Arguments for subcommand.
    :> QueryParam' '[Required, Strict] "arg" Text
    :> Stream 'POST 200 NoFraming PlainText (SourceIO ByteString)

-- | Show ipfs version information.
--
-- Response example:
--
-- > {
-- >     "Version": "<string>"
-- >     "Commit": "<string>"
-- >     "Repo": "<string>"
-- >     "System": "<string>"
-- >     "Golang": "<string>"
-- > }
type ApiV0Version =
      "api" :> "v0" :> "version"
    -- Only show the version number.
    :> QueryParam "number" Bool
    -- Show the commit hash.
    :> QueryParam "commit" Bool
    -- Show repo version.
    :> QueryParam "repo" Bool
    -- Show all version information.
    :> QueryParam "all" Bool
    :> Post '[JSON] Value