| Copyright | (c) 2015-2017 Kai Zhang |
|---|---|
| License | MIT |
| Maintainer | kai@kzhang.org |
| Stability | experimental |
| Portability | POSIX |
| Safe Haskell | None |
| Language | Haskell2010 |
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:
- Easy to use and safe: Provide a simple and flexible way to design type safe computational pipelines in Haskell.
- Automatic Checkpointing: The states of intermediate steps are automatically logged, allowing easy restart upon failures.
- 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"- defaultMain :: Builder () -> Q [Dec]
- mainWith :: MainOpts -> Builder () -> Q [Dec]
- defaultMainOpts :: MainOpts
- data MainOpts = MainOpts {
- preAction :: Name
- programHeader :: String
- type Builder = State ([Node], [Edge])
- namespace :: Text -> Builder () -> Builder ()
- node :: ToExpQ fun => PID -> fun -> State Attribute () -> Builder ()
- node' :: ToExpQ fun => PID -> fun -> State Attribute () -> Builder ()
- nodeS :: ToExpQ fun => PID -> fun -> State Attribute () -> Builder ()
- nodeP :: ToExpQ fun => Int -> PID -> fun -> State Attribute () -> Builder ()
- nodeP' :: ToExpQ fun => Int -> PID -> fun -> State Attribute () -> Builder ()
- nodePS :: ToExpQ fun => Int -> PID -> fun -> State Attribute () -> Builder ()
- nodeSharedP :: ToExpQ fun => Int -> PID -> fun -> State Attribute () -> Builder ()
- nodeSharedP' :: ToExpQ fun => Int -> PID -> fun -> State Attribute () -> Builder ()
- nodeSharedPS :: ToExpQ fun => Int -> PID -> fun -> State Attribute () -> Builder ()
- link :: [PID] -> PID -> Builder ()
- (~>) :: [PID] -> PID -> Builder ()
- path :: [PID] -> Builder ()
- label :: Lens' Attribute Text
- note :: Lens' Attribute Text
- submitToRemote :: Lens' Attribute (Maybe Bool)
- remoteParam :: Lens' Attribute String
- data ContextData context dat = ContextData {}
- type WorkflowConfig config = ReaderT config IO
Documentation
Constructors
| MainOpts | |
namespace :: Text -> Builder () -> Builder () Source #
Add a prefix to IDs of nodes for a given builder, i.e.,
id becomes prefix_id.
Arguments
| :: ToExpQ fun | |
| => PID | Node id |
| -> fun | Template Haskell expression representing
functions with type |
| -> State Attribute () | Attribues |
| -> Builder () |
Declare an IO computational step.
Arguments
| :: ToExpQ fun | |
| => PID | |
| -> fun | Template Haskell expression representing
functions with type |
| -> State Attribute () | |
| -> Builder () |
Declare a pure computational step.
Arguments
| :: ToExpQ fun | |
| => PID | |
| -> fun | Template Haskell expression representing
functions with type " |
| -> State Attribute () | |
| -> Builder () |
Declare a stateful computational step.
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 but work with pure functions.nodeP
nodePS :: ToExpQ fun => Int -> PID -> fun -> State Attribute () -> Builder () Source #
Same as but work with stateful functions.nodeP
Arguments
| :: ToExpQ fun | |
| => Int | |
| -> PID | |
| -> fun | Template Haskell expression representing
functions with type |
| -> State Attribute () | |
| -> Builder () |
Similar to but work with inputs that are associated with a
shared context. Turn nodeP into
ContextData context a -> IO b.ContextData context [a] -> IO [b]
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"
type WorkflowConfig config = ReaderT config IO Source #