Copyright | (c) 2014 Jens Thomas |
---|---|
License | BSD-style |
Maintainer | jetho@gmx.de |
Stability | experimental |
Portability | GHC |
Safe Haskell | None |
Language | Haskell2010 |
Extensions | OverloadedStrings |
This module provides functions for manual session handling.
Example Usage:
{-# LANGUAGE OverloadedStrings #-} import Control.Lens ((&
), (.~
)) import Network.Syncthing import qualified Network.Syncthing.Get as Get -- Customized configuration. settings1 =defaultConfig
&
pServer
.~
"192.168.0.10:8080" session1 = do session <-newSyncSession
settings1 p <-runSyncSession
session Get.ping
v <-runSyncSession
session Get.version
closeSyncSession
session return (p, v) -- Customized configuration with disabled SSL certificate verification. settings2 =defaultConfig
&
pHttps
.~
True&
pManager
.~
LeftnoSSLVerifyManagerSettings
session2 = do session <-newSyncSession
settings2 p <-runSyncSession
session Get.ping
v <-runSyncSession
session Get.version
closeSyncSession
session return (p, v)
- data SyncSession
- newSyncSession :: SyncConfig -> IO SyncSession
- closeSyncSession :: SyncSession -> IO ()
- withSyncSession :: SyncConfig -> (SyncSession -> IO a) -> IO a
- runSyncSession :: SyncSession -> SyncM IO a -> IO (SyncResult a)
Types
data SyncSession Source
Holds the session configuration and the connection manager.
Session Management
newSyncSession :: SyncConfig -> IO SyncSession Source
Create a new Syncthing session for with provided configuration. You should reuse the session whenever possible because of connection sharing.
closeSyncSession :: SyncSession -> IO () Source
Close a Syncthing session.
withSyncSession :: SyncConfig -> (SyncSession -> IO a) -> IO a Source
Create a new session using the provided configuration, run the action and close the session.
Examples:
withSyncSession
defaultConfig
$ \session ->runSyncSession
session $liftM2
(,) Get.ping
Get.version
import qualified Network.Wreq as Wreq let cfg =defaultConfig
&
pHttps
.~
True&
pAuth
?~
Wreq.basicAuth
"user" "pass"&
pApiKey
?~
"XXXXXXXXXXXXXXXXXXXXXXXXXXXXXX"withSyncSession
cfg $ \session ->runSyncSession
session $liftM2
(,) Get.ping
Get.version
Running requests
runSyncSession :: SyncSession -> SyncM IO a -> IO (SyncResult a) Source
Run a Syncthing request using connection sharing within a session.