syncthing-hs-0.3.0.0: Haskell bindings for the Syncthing REST API

Copyright(c) 2014 Jens Thomas
LicenseBSD-style
Maintainerjetho@gmx.de
Stabilityexperimental
PortabilityGHC
Safe HaskellNone
LanguageHaskell2010
ExtensionsOverloadedStrings

Network.Syncthing

Contents

Description

Haskell bindings for the Syncthing REST API.

The library is based on the Network.Wreq package and uses some of wreq's functionalities for client configuration. For example, to use authentication, you need to import the Network.Wreq module.

Example Usage:

{-# LANGUAGE OverloadedStrings #-}

import Control.Lens ((&), (.~), (?~))
import Control.Monad (liftM2)
import qualified Network.Wreq as Wreq
import Network.Syncthing
import qualified Network.Syncthing.Get as Get

-- A single Syncthing request.
single = syncthing defaultConfig Get.ping

-- Connection sharing for multiple Syncthing requests.
multiple1 = withManager $ \cfg ->
    syncthing cfg $ do
        p <- Get.ping
        v <- Get.version
        return (p, v)

-- Multiple Syncthing requests with connection sharing and customized configuration.
multiple2 = withManager $ \cfg -> do
    let cfg' = cfg & pServer .~ "192.168.0.10:8080"
                   & pHttps  .~ True
                   & pAuth   ?~ Wreq.basicAuth "user" "pass"
    syncthing cfg' $ liftM2 (,) Get.ping Get.version

Synopsis

The Syncthing Monad

type SyncResult a = Either SyncError a Source

The result type of Syncthing requests.

data SyncM m a Source

The SyncM Monad represents one or multiple Syncthing requests.

Instances

Monad m => Monad (SyncM m) 
Monad m => Functor (SyncM m) 
Monad m => Applicative (SyncM m) 

syncthing :: SyncConfig -> SyncM IO a -> IO (SyncResult a) Source

Run Syncthing requests.

Connection sharing

withManager :: (SyncConfig -> IO a) -> IO a Source

Create a default configuration with a new manager for connection sharing. The manager is released after running the Syncthing actions(s). This is equivalent to:

withManager' defaultManagerSettings

Examples:

withManager $ \cfg ->
    syncthing cfg $ liftM2 (,) Get.ping Get.version
withManager $ \cfg -> do
    let cfg' = cfg & pServer .~ "192.168.0.10:8080"
    syncthing cfg' $ liftM2 (,) Get.ping Get.version

withManagerNoVerify :: (SyncConfig -> IO a) -> IO a Source

Create a manager with disabled SSL certificate verification. This is equivalent to:

withManager' noSSLVerifyManagerSettings

Example:

withManagerNoVerify $ \cfg -> do
    let cfg' = cfg & pHttps .~ True
    syncthing cfg' $ liftM2 (,) Get.ping Get.version

withManager' :: ManagerSettings -> (SyncConfig -> IO a) -> IO a Source

Create a manager by using the provided manager settings.

Example:

withManager' noSSLVerifyManagerSettings $ \cfg -> do
    let cfg' = cfg & pHttps .~ True
    syncthing cfg' $ liftM2 (,) Get.ping Get.version

Configuration

data SyncConfig Source

The Syncthing configuration for specifying the Syncthing server, authentication, the API Key etc.

Constructors

SyncConfig 

Fields

server :: Server
 
apiKey :: Maybe Text
 
auth :: Maybe Auth
 
https :: Bool
 
manager :: Either ManagerSettings Manager
 

Instances

pServer :: Lens' SyncConfig Server Source

A lens for configuring the server address. Use the ADDRESS:PORT format.

Example:

let cfg = defaultConfig & pServer .~ "192.168.0.10:8080"
syncthing cfg Get.ping

pApiKey :: Lens' SyncConfig (Maybe Text) Source

A lens for specifying the Syncthing API Key.

Example:

let cfg = defaultConfig & pApiKey ?~ "XXXXXXXXXXXXXXXXXXXXXXXXXXXXXX"
syncthing cfg Get.ping

pAuth :: Lens' SyncConfig (Maybe Auth) Source

A lens for configuring request authentication provided by the Wreq package (see Auth).

Example:

import qualified Network.Wreq as Wreq

let cfg = defaultConfig & pHttps .~ True
                        & pAuth  ?~ Wreq.basicAuth "user" "pass"
syncthing cfg Get.ping

pHttps :: Lens' SyncConfig Bool Source

A lens for enabling HTTPS usage.

Example:

let cfg = defaultConfig & pHttps .~ True
syncthing cfg Get.ping

pManager :: Lens' SyncConfig (Either ManagerSettings Manager) Source

A lens for specifying your own ManagerSettings/Manager. For more information, please refer to the Network.HTTP.Client package.

Defaults

defaultConfig :: SyncConfig Source

The default Syncthing configuration. Customize it to your needs by using record syntax or the SyncConfig lenses.

Example:

>>> defaultConfig
SyncConfig { server = "127.0.0.1:8384", apiKey = Nothing, auth = Nothing, https = False, manager = Left _ }
>>> defaultConfig { server = "192.168.0.10:8080", apiKey = Just "XXXX" }
SyncConfig { server = "192.168.0.10:8080", apiKey = Just "XXXX", auth = Nothing, https = False, manager = Left _ }
>>> defaultConfig & pServer .~ "192.168.0.10:8080" & pApiKey ?~ "XXXX"
SyncConfig { server = "192.168.0.10:8080", apiKey = Just "XXXX", auth = Nothing, https = False, manager = Left _ }

defaultFolder :: FolderName Source

The Syncthing default folder (-> "default").

Manager Settings

defaultManagerSettings :: ManagerSettings Source

The default manager settings used by defaultConfig.

noSSLVerifyManagerSettings :: ManagerSettings Source

Alternative manager settings with disabled SSL certificate verification.

setResponseTimeout :: ManagerSettings -> Int -> ManagerSettings Source

Set the response timeout (in microseconds). Default is 300 seconds.

Error Handling

Manual Session Handling

Utility functions

Types