Parry-0.1.0.0: A proven synchronization server for high performance computing.

Copyright(c) Pierre-Étienne Meunier 2014
LicenseGPL-3
Maintainerpierre-etienne.meunier@lif.univ-mrs.fr
Stabilityexperimental
PortabilityAll
Safe HaskellNone
LanguageHaskell2010

Parry.Server

Contents

Description

Tools to build synchronization servers. For instance, to write a simple server with just a web interface on port 8000, you would use:

import Control.Concurrent
import Parry.Server
import Parry.WebUI

main::IO ()
main=do
  state<-initState initial
  _<-forkIO $ webUI 8000 state
  server (defaultConfig public) state

Synopsis

Jobs on the server side

class Exhaustive j where Source

The class of jobs and job results that Parry can deal with. For efficiency and to keep types simple, jobs and results are stored in a single type.

Methods

depth :: j -> Int Source

Indication of the depth of a job in the explored tree. The server sends the least deep jobs first, as an optimization of network use.

killed :: j -> Int Source

Number of times a job has been killed. When a job is killed, either because it must be reshared, or because the client itself was killed, it is scheduled to be re-executed by the server.

kill :: j -> j Source

Called each time a job needs to be killed. For better resharing, this function must verify killed (kill j) >= killed j.

class Result j r where Source

The class of results, and how to combine them in the server state.

Methods

addResult :: HostName -> r -> j -> r Source

A function to tell how to combine job results. That function will be called on the hostname of the reporting client, with the finished job it sent, and the current result from the server state.

Server's internal state

initState :: (Exhaustive j, Ord j, Result j r) => [j] -> r -> IO (MVar (State j r)) Source

Creates a valid server state from an initial job.

stateFromFile :: (Binary r, Binary j, Exhaustive j, Result j r, Ord j) => FilePath -> [j] -> r -> IO (MVar (State j r)) Source

Reads initial state from a file, or calls initState if the file does not exist.

saveThread :: (Binary r, Binary j) => FilePath -> Int -> MVar (State j r) -> IO () Source

Saves state to the given file with the given periodicity, in microseconds. This function does not return, so calling it inside a forkIO is probably the best thing to do.

data State j r Source

This type is exposed mostly for writing alternative user interfaces. Other operations must be done using the functions in this module, or the correction of the protocol can be lost.

Constructors

State 

Fields

jobs :: Set (Int, j)

Available jobs

ongoing :: Map Integer (HostName, PublicKey, j, Double, Double)

Map from the machine id to its hostname, its current job, its starting time, the last time we heard from it.

unemployed :: Set Integer

Set of unemployed machines

results :: r

The results.

newId :: Integer

The smallest available machine id. In a run of the server, it is guaranteed that are never assigned the same.

killings :: Int

Total number of jobs killed from the beginning (for benchmarking purposes).

solved :: Integer

Number of jobs finished (for benchmarking purposes).

authorizedKeys :: [PublicKey]

The list of authorized RSA public keys.

Instances

(Ord j, Read j, Read r) => Read (State j r) 
(Show j, Show r) => Show (State j r) 
Generic (State j r) 
(Binary j, Binary r) => Binary (State j r) 
type Rep (State j r) 

Server configuration and functions

data Config Source

Server configuration

Constructors

Config 

Fields

port :: PortID

The network port the synchronization server will listen on.

maxThreads :: Int

The maximal number of simultaneous threads that can be launched.

logFile :: FilePath

Log file

defaultConfig :: Config Source

Default server configuration, matching the client. Note that you must provide your own public key for signing the messages.

server :: (Ord j, Binary j, Exhaustive j, Result j r) => Config -> MVar (State j r) -> IO () Source

Starts the synchronization server.