{-# LANGUAGE OverloadedStrings #-}
module Blockfrost.Client.IPFS
( ipfsAdd
, ipfsGateway
, ipfsGetPin
, ipfsListPins
, ipfsListPins'
, ipfsPin
, ipfsRemovePin
) where
import Blockfrost.API
import Blockfrost.Client.Types
import Blockfrost.Types
import Control.Monad.Except
import Data.ByteString.Lazy (ByteString)
import Data.Text (Text)
import qualified Data.Text
import qualified System.Directory
import qualified System.FilePath
ipfsAdd_ :: Project -> (ByteString, Form) -> BlockfrostClient IPFSAdd
ipfsAdd_ :: Project -> (ByteString, Form) -> BlockfrostClient IPFSAdd
ipfsAdd_ = IPFSAPI (AsClientT BlockfrostClient)
-> (ByteString, Form) -> BlockfrostClient IPFSAdd
forall route.
IPFSAPI route
-> route
:- (Summary "Add a file or directory to IPFS"
:> (Description
"You need to `/ipfs/pin/add` an object to avoid it being garbage collected. This usage is being counted in your user account quota."
:> (Tag "IPFS \187 Add"
:> ("add" :> (MultipartForm Tmp Form :> Post '[JSON] IPFSAdd)))))
_add (IPFSAPI (AsClientT BlockfrostClient)
-> (ByteString, Form) -> BlockfrostClient IPFSAdd)
-> (Project -> IPFSAPI (AsClientT BlockfrostClient))
-> Project
-> (ByteString, Form)
-> BlockfrostClient IPFSAdd
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Project -> IPFSAPI (AsClientT BlockfrostClient)
ipfsClient
ipfsAdd :: FilePath -> BlockfrostClient IPFSAdd
ipfsAdd :: FilePath -> BlockfrostClient IPFSAdd
ipfsAdd FilePath
fp = do
Bool
hasFile <- IO Bool -> ExceptT BlockfrostError (ReaderT ClientConfig IO) Bool
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Bool -> ExceptT BlockfrostError (ReaderT ClientConfig IO) Bool)
-> IO Bool
-> ExceptT BlockfrostError (ReaderT ClientConfig IO) Bool
forall a b. (a -> b) -> a -> b
$ FilePath -> IO Bool
System.Directory.doesFileExist FilePath
fp
if Bool
hasFile
then do
IO () -> ExceptT BlockfrostError (ReaderT ClientConfig IO) ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> ExceptT BlockfrostError (ReaderT ClientConfig IO) ())
-> IO () -> ExceptT BlockfrostError (ReaderT ClientConfig IO) ()
forall a b. (a -> b) -> a -> b
$ FilePath -> IO ()
putStrLn (FilePath -> IO ()) -> FilePath -> IO ()
forall a b. (a -> b) -> a -> b
$ FilePath
"Uploading: " FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
fp
let fn :: Text
fn = FilePath -> Text
Data.Text.pack (FilePath -> Text) -> FilePath -> Text
forall a b. (a -> b) -> a -> b
$ FilePath -> FilePath
System.FilePath.takeBaseName FilePath
fp
(Project -> BlockfrostClient IPFSAdd) -> BlockfrostClient IPFSAdd
forall a. (Project -> BlockfrostClient a) -> BlockfrostClient a
go (\Project
proj -> Project -> (ByteString, Form) -> BlockfrostClient IPFSAdd
ipfsAdd_ Project
proj (ByteString
"suchBoundary", (Text -> FilePath -> Form
Form Text
fn FilePath
fp)))
else
BlockfrostError -> BlockfrostClient IPFSAdd
forall e (m :: * -> *) a. MonadError e m => e -> m a
throwError (Text -> BlockfrostError
BlockfrostError Text
"No such file")
ipfsGateway_ :: Project -> Text -> BlockfrostClient IPFSData
ipfsGateway_ :: Project -> Text -> BlockfrostClient IPFSData
ipfsGateway_ = IPFSAPI (AsClientT BlockfrostClient)
-> Text -> BlockfrostClient IPFSData
forall route.
IPFSAPI route
-> route
:- (Summary "Relay to an IPFS gateway"
:> (Description
"Retrieve an object from the IFPS gateway. (Useful if you do not want to rely on a public gateway, such as ``ipfs.blockfrost.dev`)."
:> (Tag "IPFS \187 Gateway"
:> ("gateway"
:> (Capture "IPFS_path" Text
:> Get '[PlainText, OctetStream] IPFSData)))))
_gateway (IPFSAPI (AsClientT BlockfrostClient)
-> Text -> BlockfrostClient IPFSData)
-> (Project -> IPFSAPI (AsClientT BlockfrostClient))
-> Project
-> Text
-> BlockfrostClient IPFSData
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Project -> IPFSAPI (AsClientT BlockfrostClient)
ipfsClient
ipfsGateway :: Text -> BlockfrostClient IPFSData
ipfsGateway :: Text -> BlockfrostClient IPFSData
ipfsGateway Text
x = (Project -> BlockfrostClient IPFSData) -> BlockfrostClient IPFSData
forall a. (Project -> BlockfrostClient a) -> BlockfrostClient a
go (Project -> Text -> BlockfrostClient IPFSData
`ipfsGateway_` Text
x)
ipfsPin_ :: Project -> Text -> BlockfrostClient IPFSPinChange
ipfsPin_ :: Project -> Text -> BlockfrostClient IPFSPinChange
ipfsPin_ = IPFSAPI (AsClientT BlockfrostClient)
-> Text -> BlockfrostClient IPFSPinChange
forall route.
IPFSAPI route
-> route
:- (Summary "Pin an object"
:> (Description
"Pinned objects are counted in your user storage quota."
:> (Tag "IPFS \187 Pins"
:> ("pin"
:> ("add"
:> (Capture "IPFS_path" Text :> Post '[JSON] IPFSPinChange))))))
_pin (IPFSAPI (AsClientT BlockfrostClient)
-> Text -> BlockfrostClient IPFSPinChange)
-> (Project -> IPFSAPI (AsClientT BlockfrostClient))
-> Project
-> Text
-> BlockfrostClient IPFSPinChange
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Project -> IPFSAPI (AsClientT BlockfrostClient)
ipfsClient
ipfsPin :: Text -> BlockfrostClient IPFSPinChange
ipfsPin :: Text -> BlockfrostClient IPFSPinChange
ipfsPin Text
x = (Project -> BlockfrostClient IPFSPinChange)
-> BlockfrostClient IPFSPinChange
forall a. (Project -> BlockfrostClient a) -> BlockfrostClient a
go (Project -> Text -> BlockfrostClient IPFSPinChange
`ipfsPin_` Text
x)
ipfsListPins_ :: Project -> Paged -> SortOrder -> BlockfrostClient [IPFSPin]
ipfsListPins_ :: Project -> Paged -> SortOrder -> BlockfrostClient [IPFSPin]
ipfsListPins_ = IPFSAPI (AsClientT BlockfrostClient)
-> Paged -> SortOrder -> BlockfrostClient [IPFSPin]
forall route.
IPFSAPI route
-> route
:- (Summary "List pinned objects"
:> (Description "List objects pinned to local storage."
:> (Tag "IPFS \187 Pins"
:> ("pin"
:> ("list"
:> (Pagination :> (Sorting :> Get '[JSON] [IPFSPin])))))))
_listPins (IPFSAPI (AsClientT BlockfrostClient)
-> Paged -> SortOrder -> BlockfrostClient [IPFSPin])
-> (Project -> IPFSAPI (AsClientT BlockfrostClient))
-> Project
-> Paged
-> SortOrder
-> BlockfrostClient [IPFSPin]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Project -> IPFSAPI (AsClientT BlockfrostClient)
ipfsClient
ipfsListPins' :: Paged -> SortOrder -> BlockfrostClient [IPFSPin]
ipfsListPins' :: Paged -> SortOrder -> BlockfrostClient [IPFSPin]
ipfsListPins' Paged
pg SortOrder
s = (Project -> BlockfrostClient [IPFSPin])
-> BlockfrostClient [IPFSPin]
forall a. (Project -> BlockfrostClient a) -> BlockfrostClient a
go (\Project
p -> Project -> Paged -> SortOrder -> BlockfrostClient [IPFSPin]
ipfsListPins_ Project
p Paged
pg SortOrder
s)
ipfsListPins :: BlockfrostClient [IPFSPin]
ipfsListPins :: BlockfrostClient [IPFSPin]
ipfsListPins = Paged -> SortOrder -> BlockfrostClient [IPFSPin]
ipfsListPins' Paged
forall a. Default a => a
def SortOrder
forall a. Default a => a
def
ipfsGetPin_ :: Project -> Text -> BlockfrostClient IPFSPin
ipfsGetPin_ :: Project -> Text -> BlockfrostClient IPFSPin
ipfsGetPin_ = IPFSAPI (AsClientT BlockfrostClient)
-> Text -> BlockfrostClient IPFSPin
forall route.
IPFSAPI route
-> route
:- (Summary "Get pinned object details"
:> (Description "Obtain inormation about specific pinned object."
:> (Tag "IPFS \187 Pins"
:> ("pin"
:> ("list"
:> (Capture "IPFS_path" Text :> Get '[JSON] IPFSPin))))))
_getPin (IPFSAPI (AsClientT BlockfrostClient)
-> Text -> BlockfrostClient IPFSPin)
-> (Project -> IPFSAPI (AsClientT BlockfrostClient))
-> Project
-> Text
-> BlockfrostClient IPFSPin
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Project -> IPFSAPI (AsClientT BlockfrostClient)
ipfsClient
ipfsGetPin :: Text -> BlockfrostClient IPFSPin
ipfsGetPin :: Text -> BlockfrostClient IPFSPin
ipfsGetPin Text
x = (Project -> BlockfrostClient IPFSPin) -> BlockfrostClient IPFSPin
forall a. (Project -> BlockfrostClient a) -> BlockfrostClient a
go (Project -> Text -> BlockfrostClient IPFSPin
`ipfsGetPin_` Text
x)
ipfsRemovePin_ :: Project -> Text -> BlockfrostClient IPFSPinChange
ipfsRemovePin_ :: Project -> Text -> BlockfrostClient IPFSPinChange
ipfsRemovePin_ = IPFSAPI (AsClientT BlockfrostClient)
-> Text -> BlockfrostClient IPFSPinChange
forall route.
IPFSAPI route
-> route
:- (Summary "Remove pinned object from local storage"
:> (Description "Remove pinned object from local storage"
:> (Tag "IPFS \187 Pins"
:> ("pin"
:> ("remove"
:> (Capture "IPFS_path" Text :> Post '[JSON] IPFSPinChange))))))
_removePin (IPFSAPI (AsClientT BlockfrostClient)
-> Text -> BlockfrostClient IPFSPinChange)
-> (Project -> IPFSAPI (AsClientT BlockfrostClient))
-> Project
-> Text
-> BlockfrostClient IPFSPinChange
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Project -> IPFSAPI (AsClientT BlockfrostClient)
ipfsClient
ipfsRemovePin :: Text -> BlockfrostClient IPFSPinChange
ipfsRemovePin :: Text -> BlockfrostClient IPFSPinChange
ipfsRemovePin Text
x = (Project -> BlockfrostClient IPFSPinChange)
-> BlockfrostClient IPFSPinChange
forall a. (Project -> BlockfrostClient a) -> BlockfrostClient a
go (Project -> Text -> BlockfrostClient IPFSPinChange
`ipfsRemovePin_` Text
x)