ipfs: Access IPFS locally and remotely

This is a package candidate release! Here you can preview how this package release will appear once published to the main package index (which can be accomplished via the 'maintain' link below). Please note that once a package has been published to the main package index it cannot be undone! Please consult the package uploading documentation for more information.

[maintain] [Publish]

Interact with the IPFS network by shelling out to a local IPFS node or communicating via the HTTP interface of a remote IPFS node.


[Skip to Readme]

Properties

Versions 1.0.0, 1.0.0, 1.0.1, 1.0.2, 1.0.3, 1.1.0, 1.1.1, 1.1.2, 1.1.3, 1.1.3.1, 1.1.4.0, 1.1.5.0, 1.1.5.1, 1.2.0.0, 1.3.0.0, 1.3.0.1, 1.3.0.2, 1.3.0.3, 1.3.1, 1.3.2, 1.4.0, 1.4.1
Change log None available
Dependencies aeson, base (<5), bytestring, data-has, envy, flow, Glob, http-client, ip, lens, monad-logger, regex-compat, rio, servant-client, servant-client-core, servant-multipart, servant-server, swagger2, text, vector [details]
License AGPL-3.0-or-later
Copyright © 2019 Fission Internet Software Services for Open Networks Inc.
Author Brooklyn Zelenka, Daniel Holmgren, Ben Church
Maintainer brooklyn@fission.codes, daniel@fission.codes, ben@fission.codes
Category Network
Home page https://github.com/fission-suite/ipfs-haskell#readme
Bug tracker https://github.com/fission-suite/ipfs-haskell/issues
Source repo head: git clone https://github.com/fission-suite/ipfs-haskell
Uploaded by dholms at 2019-12-20T00:19:51Z

Modules

[Index] [Quick Jump]

Downloads

Maintainer's Corner

Package maintainers

For package maintainers and hackage trustees


Readme for ipfs-1.0.0

[back to package description]

ipfs-haskell

Build Status License Maintainability Built by FISSION Discord Discourse

Documentation: ipfs on hackage

A library for integrating IPFS into your haskell applications. Interact with the IPFS network by shelling out to a local IPFS node or communicating via the HTTP interface of a remote node.

QuickStart

Define instances for MonadLocalIPFS and/or MonadRemoteIPFS. Each requires only one function:

class Monad m => MonadRemoteIPFS m where
  runRemote :: Servant.ClientM a -> m (Either Servant.ClientError a)

class Monad m => MonadLocalIPFS m where
  runLocal ::
       [IPFS.Opt]
    -> Lazy.ByteString
    -> m (Either Process.Error Process.RawMessage)

We use RIO processes to shell out to a local IPFS node and Servant for HTTP requests to a remote node.

After that, simply add MonadLocalIPFS m as a constraint to a function and you'll be able to call IPFS within it. For instance:

import           Network.IPFS
import qualified Network.IPFS.Add        as IPFS
import           Network.IPFS.File.Types as File

add ::
  MonadLocalIPFS  m
  => File.Serialzed
  -> m ()
add (Serialized rawData) = IPFS.addRaw rawData >>= \case
  Right newCID -> 
    -- ...
  Left err ->
    -- ...

You can see example instances below:

instance
  ( HasProcessContext cfg
  , HasLogFunc cfg
  , Has IPFS.BinPath cfg
  , Has IPFS.Timeout cfg
  )
  => MonadLocalIPFS (RIO cfg) where
    runLocal opts arg = do
      IPFS.BinPath ipfs <- view hasLens
      IPFS.Timeout secs <- view hasLens
      let opts' = ("--timeout=" <> show secs <> "s") : opts

      runProc readProcess ipfs (byteStringInput arg) byteStringOutput opts' >>= \case
        (ExitSuccess, contents, _) ->
          return $ Right contents
        (ExitFailure _, _, stdErr)
          | Lazy.isSuffixOf "context deadline exceeded" stdErr ->
              return . Left $ Process.Timeout secs
          | otherwise ->
            return . Left $ Process.UnknownErr stdErr

instance
  ( Has IPFS.URL     cfg
  , Has HTTP.Manager cfg
  )
  => MonadRemoteIPFS (RIO cfg) where
    runRemote query = do
      IPFS.URL url <- view hasLens
      manager      <- view hasLens

      url
        & mkClientEnv manager
        & runClientM query
        & liftIO