syncthing-hs-0.1.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 qualified Network.Wreq as Wreq
import Control.Monad (liftM2)
import Control.Lens ((&), (.~), (?~))
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

Types

type Server = Text Source

Use the SERVER:PORT format for specifying servers.

type Port = Int Source

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.

Instances

pServer :: Lens' SyncConfig Server Source

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

Example:

let cfg = defaultConfig & pApiKey .~ "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 the SyncConfig lenses.

Example:

>>> defaultConfig
SyncConfig { pServer = "127.0.0.1:8080", pApiKey = Nothing, pAuth = Nothing, pHttps = False, pManager = Left _ }
>>> defaultConfig & pServer .~ "192.168.0.10:8080" & pApiKey ?~ "XXXX"
SyncConfig { pServer = "192.168.0.10:8080", pApiKey = Just "XXXX", pAuth = Nothing, pHttps = False, pManager = Left _ }

defaultFolder :: FolderName Source

The default folder name.

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

Data Types

data CacheEntry Source

Represents an entry in the discovery cache.

Constructors

CacheEntry 

data AddressType Source

An address can be dynamic or static.

Constructors

Dynamic 
Address Addr 

data Connection Source

Connection information and some associated metadata.

data DirTree Source

A directory tree contains files or subdirectories.

Constructors

Dir 
File 

Fields

getModTime :: Integer

file modification time

getFileSize :: Integer

file size

data Error Source

An error message and its timestamp.

Constructors

Error 

data Ignore Source

Contains the ignores list and a list of all compiled ignore patterns.

Constructors

Ignore 

data ModelState Source

The current state of activity of a folder.

Constructors

Idle 
Scanning 
Cleaning 
Syncing 

data Need Source

Contains lists of files which are needed by a device for becoming in sync.

Constructors

Need 

Fields

getProgress :: [Progress]
 
getQueued :: [Text]
 
getRest :: [Text]
 

Instances

data Progress Source

A file that is currently downloading.

data System Source

Information about the system status and resource usage.

data Upgrade Source

Information about the current software version and upgrade possibilities.

Constructors

Upgrade 

data Version Source

Current Syncthing version information.

Constructors

Version 

Utility functions

parseAddr :: Server -> Addr Source

Parse server string (SERVER:PORT) into an address type.

encodeAddr :: Addr -> Server Source

Generate server string.

toUTC :: String -> Maybe UTCTime Source

Convert time string to UTCTime type.

fromUTC :: UTCTime -> String Source

Generate time string from UTC.