SciFlow-0.6.1: Scientific workflow management system

Copyright(c) 2015-2017 Kai Zhang
LicenseMIT
Maintainerkai@kzhang.org
Stabilityexperimental
PortabilityPOSIX
Safe HaskellNone
LanguageHaskell2010

Scientific.Workflow

Description

SciFlow is a DSL for building scientific workflows. Workflows built with SciFlow can be run either on desktop computers or in grid computing environments that support DRMAA.

Features:

  1. Easy to use and safe: Provide a simple and flexible way to design type safe computational pipelines in Haskell.
  2. Automatic Checkpointing: The states of intermediate steps are automatically logged, allowing easy restart upon failures.
  3. Parallelism and grid computing support.

Example:

import           Control.Lens             ((.=))
import           Scientific.Workflow

f :: Int -> Int
f = (+1)

defaultMain $ do
    nodeS "step0" [| return . const [1..10] :: () -> WorkflowConfig () [Int] |] $ return ()
    nodeP' 2 "step1" 'f $ note .= "run in parallel with batch size 2"
    nodeP' 4 "step2" 'f $ note .= "run in parallel with batch size 4"
    node' "step3" [| \(x, y) -> x ++ y |] $ return ()

    ["step0"] ~> "step1"
    ["step0"] ~> "step2"
    ["step1", "step2"] ~> "step3"

Synopsis

Documentation

data MainOpts Source #

Constructors

MainOpts 

Fields

Instances

type Builder = State ([Node], [Edge]) Source #

namespace :: Text -> Builder () -> Builder () Source #

Add a prefix to IDs of nodes for a given builder, i.e., id becomes prefix_id.

node Source #

Arguments

:: ToExpQ fun 
=> PID

Node id

-> fun

Template Haskell expression representing functions with type a -> IO b.

-> State Attribute ()

Attribues

-> Builder () 

Declare an IO computational step.

node' Source #

Arguments

:: ToExpQ fun 
=> PID 
-> fun

Template Haskell expression representing functions with type a -> b.

-> State Attribute () 
-> Builder () 

Declare a pure computational step.

nodeS Source #

Arguments

:: ToExpQ fun 
=> PID 
-> fun

Template Haskell expression representing functions with type "a -> WorkflowConfig st b".

-> State Attribute () 
-> Builder () 

Declare a stateful computational step.

nodeP Source #

Arguments

:: ToExpQ fun 
=> Int

Batch size for parallel execution.

-> PID 
-> fun 
-> State Attribute () 
-> Builder () 

Declare an IO and parallel computational step. This will turn functions with type "a -> IO b" into functions with type "[a] -> IO [b]". And [a] will be processed in parallel with provided batch size. Note: Currently, parallelism is available only when "--remote" flag is on.

nodeP' :: ToExpQ fun => Int -> PID -> fun -> State Attribute () -> Builder () Source #

Same as nodeP but work with pure functions.

nodePS :: ToExpQ fun => Int -> PID -> fun -> State Attribute () -> Builder () Source #

Same as nodeP but work with stateful functions.

nodeSharedP Source #

Arguments

:: ToExpQ fun 
=> Int 
-> PID 
-> fun

Template Haskell expression representing functions with type ContextData context a -> IO b.

-> State Attribute () 
-> Builder () 

Similar to nodeP but work with inputs that are associated with a shared context. Turn ContextData context a -> IO b into ContextData context [a] -> IO [b].

nodeSharedP' :: ToExpQ fun => Int -> PID -> fun -> State Attribute () -> Builder () Source #

nodeSharedPS :: ToExpQ fun => Int -> PID -> fun -> State Attribute () -> Builder () Source #

link :: [PID] -> PID -> Builder () Source #

Declare the dependency between nodes. Example:

node' "step1" [| \() -> 1 :: Int |] $ return ()
node' "step2" [| \() -> 2 :: Int |] $ return ()
node' "step3" [| \(x, y) -> x * y |] $ return ()
link ["step1", "step2"] "step3"

(~>) :: [PID] -> PID -> Builder () Source #

(~>) = link.

path :: [PID] -> Builder () Source #

"path [a, b, c]" is equivalent to "link a b >> link b c"

data ContextData context dat Source #

Data and its environment.

Constructors

ContextData 

Fields

Instances

Generic (ContextData context dat) Source # 

Associated Types

type Rep (ContextData context dat) :: * -> * #

Methods

from :: ContextData context dat -> Rep (ContextData context dat) x #

to :: Rep (ContextData context dat) x -> ContextData context dat #

(ToJSON c, ToJSON d) => ToJSON (ContextData c d) Source # 
(FromJSON c, FromJSON d) => FromJSON (ContextData c d) Source # 
(Serialize c, Serialize d) => Serialize (ContextData c d) Source # 

Methods

put :: Putter (ContextData c d) #

get :: Get (ContextData c d) #

type Rep (ContextData context dat) Source # 
type Rep (ContextData context dat) = D1 * (MetaData "ContextData" "Scientific.Workflow.Internal.Builder.Types" "SciFlow-0.6.1-CdrNBSgkFzOFQ5Zr3LWD5G" False) (C1 * (MetaCons "ContextData" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "_context") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * context)) (S1 * (MetaSel (Just Symbol "_data") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * dat))))

type WorkflowConfig config = ReaderT config IO Source #