funflow-1.5.0: Workflows with arrows

Safe HaskellNone
LanguageHaskell2010

Control.Funflow.External

Description

Definition of external tasks

Synopsis

Documentation

data InputPath Source #

Set of items which may be treated as an input path to an external task.

Constructors

IPItem Item

An item in the content store.

IPExternalFile ExternallyAssuredFile

An external file whose contents are considered assured by the external system.

IPExternalDir ExternallyAssuredDirectory

An external directory whose contents are considered assured by the external system.

Instances
Show InputPath Source # 
Instance details

Defined in Control.Funflow.External

Generic InputPath Source # 
Instance details

Defined in Control.Funflow.External

Associated Types

type Rep InputPath :: Type -> Type #

ToJSON InputPath Source # 
Instance details

Defined in Control.Funflow.External

FromJSON InputPath Source # 
Instance details

Defined in Control.Funflow.External

Store InputPath Source # 
Instance details

Defined in Control.Funflow.External

ContentHashable IO InputPath Source # 
Instance details

Defined in Control.Funflow.External

type Rep InputPath Source # 
Instance details

Defined in Control.Funflow.External

data ParamField Source #

Component of a parameter

Constructors

ParamText !Text

Text component.

ParamPath !InputPath

Reference to a path to a content store item.

ParamEnv !Text

Reference to an environment variable.

ParamUid

Reference to the effective user ID of the executor.

ParamGid

Reference to the effective group ID of the executor.

ParamOut

Reference to the output path in the content store.

ParamCmd Param

A quoted command that we can pass to another program as an argument.

Instances
Show ParamField Source # 
Instance details

Defined in Control.Funflow.External

Generic ParamField Source # 
Instance details

Defined in Control.Funflow.External

Associated Types

type Rep ParamField :: Type -> Type #

ToJSON ParamField Source # 
Instance details

Defined in Control.Funflow.External

FromJSON ParamField Source # 
Instance details

Defined in Control.Funflow.External

Store ParamField Source # 
Instance details

Defined in Control.Funflow.External

ContentHashable IO ParamField Source # 
Instance details

Defined in Control.Funflow.External

type Rep ParamField Source # 
Instance details

Defined in Control.Funflow.External

newtype Param Source #

A parameter to an external task

The runtime values to external references, e.g. environment variables, should not significantly influence the result of the external task. In particular, the content hash will not depend on these runtime values.

Constructors

Param [ParamField] 
Instances
Show Param Source # 
Instance details

Defined in Control.Funflow.External

Methods

showsPrec :: Int -> Param -> ShowS #

show :: Param -> String #

showList :: [Param] -> ShowS #

IsString Param Source # 
Instance details

Defined in Control.Funflow.External

Methods

fromString :: String -> Param #

Generic Param Source # 
Instance details

Defined in Control.Funflow.External

Associated Types

type Rep Param :: Type -> Type #

Methods

from :: Param -> Rep Param x #

to :: Rep Param x -> Param #

Semigroup Param Source # 
Instance details

Defined in Control.Funflow.External

Methods

(<>) :: Param -> Param -> Param #

sconcat :: NonEmpty Param -> Param #

stimes :: Integral b => b -> Param -> Param #

Monoid Param Source # 
Instance details

Defined in Control.Funflow.External

Methods

mempty :: Param #

mappend :: Param -> Param -> Param #

mconcat :: [Param] -> Param #

ToJSON Param Source # 
Instance details

Defined in Control.Funflow.External

FromJSON Param Source # 
Instance details

Defined in Control.Funflow.External

Store Param Source # 
Instance details

Defined in Control.Funflow.External

Methods

size :: Size Param #

poke :: Param -> Poke () #

peek :: Peek Param #

ContentHashable IO Param Source # 
Instance details

Defined in Control.Funflow.External

type Rep Param Source # 
Instance details

Defined in Control.Funflow.External

type Rep Param = D1 (MetaData "Param" "Control.Funflow.External" "funflow-1.5.0-IcEGfJSp3ag8T7kfAGHQUp" True) (C1 (MetaCons "Param" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [ParamField])))

data ConvParam f Source #

Converter of path components.

Constructors

ConvParam 

Fields

paramToText :: Applicative f => ConvParam f -> Param -> f Text Source #

Transform a parameter to text using the given converter.

pathParam :: InputPath -> Param Source #

Reference to a path to either: - a content store item, or - an externally assured file/directory.

contentParam :: Content t -> Param Source #

Reference to a path to a file or directory within a store item.

externalFileParam :: ExternallyAssuredFile -> Param Source #

Reference an externally assured file

externalDirectoryParam :: ExternallyAssuredDirectory -> Param Source #

Reference an externally assured file

envParam :: Text -> Param Source #

Reference to an environment variable.

uidParam :: Param Source #

Reference to the effective user ID of the executor.

gidParam :: Param Source #

Reference to the effective group ID of the executor.

outParam :: Param Source #

Reference to the output path in the content store.

data OutputCapture Source #

Control how and where stdout from the process is captured. Some external steps will write their output to stdout rather than to a file.

Constructors

NoOutputCapture

Specify that the step will write its output files directly, and that stdout will not be captured in the step output.

StdOutCapture

Capture output to a file named out in the output directory.

CustomOutCapture (Path Rel File)

Capture output to a custom named file in the output directory.

Instances
Show OutputCapture Source # 
Instance details

Defined in Control.Funflow.External

Generic OutputCapture Source # 
Instance details

Defined in Control.Funflow.External

Associated Types

type Rep OutputCapture :: Type -> Type #

ToJSON OutputCapture Source # 
Instance details

Defined in Control.Funflow.External

FromJSON OutputCapture Source # 
Instance details

Defined in Control.Funflow.External

Store OutputCapture Source # 
Instance details

Defined in Control.Funflow.External

ContentHashable IO OutputCapture Source # 
Instance details

Defined in Control.Funflow.External

type Rep OutputCapture Source # 
Instance details

Defined in Control.Funflow.External

type Rep OutputCapture = D1 (MetaData "OutputCapture" "Control.Funflow.External" "funflow-1.5.0-IcEGfJSp3ag8T7kfAGHQUp" False) (C1 (MetaCons "NoOutputCapture" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "StdOutCapture" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "CustomOutCapture" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Path Rel File)))))

outputCaptureToRelFile :: OutputCapture -> Maybe (Path Rel File) Source #

Get the file to write output to, if this is desired.

data Env Source #

Control the environment set for the external process. This can either inherit from the surrounding environment, or explicitly set things.

Constructors

EnvInherit

Inherit all environment variables from the surrounding shell. Note that the values of these variables will not be taken into account in the content hash, and so changes to them will not trigger a rerun of the step.

EnvExplicit [(Text, Param)] 
Instances
Show Env Source # 
Instance details

Defined in Control.Funflow.External

Methods

showsPrec :: Int -> Env -> ShowS #

show :: Env -> String #

showList :: [Env] -> ShowS #

Generic Env Source # 
Instance details

Defined in Control.Funflow.External

Associated Types

type Rep Env :: Type -> Type #

Methods

from :: Env -> Rep Env x #

to :: Rep Env x -> Env #

ToJSON Env Source # 
Instance details

Defined in Control.Funflow.External

FromJSON Env Source # 
Instance details

Defined in Control.Funflow.External

Store Env Source # 
Instance details

Defined in Control.Funflow.External

Methods

size :: Size Env #

poke :: Env -> Poke () #

peek :: Peek Env #

ContentHashable IO Env Source # 
Instance details

Defined in Control.Funflow.External

type Rep Env Source # 
Instance details

Defined in Control.Funflow.External

type Rep Env = D1 (MetaData "Env" "Control.Funflow.External" "funflow-1.5.0-IcEGfJSp3ag8T7kfAGHQUp" False) (C1 (MetaCons "EnvInherit" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "EnvExplicit" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [(Text, Param)])))

data ExternalTask Source #

A monomorphic description of an external task. This is basically just a command which can be run.

Constructors

ExternalTask 

Fields

Instances
Show ExternalTask Source # 
Instance details

Defined in Control.Funflow.External

Generic ExternalTask Source # 
Instance details

Defined in Control.Funflow.External

Associated Types

type Rep ExternalTask :: Type -> Type #

ToJSON ExternalTask Source # 
Instance details

Defined in Control.Funflow.External

FromJSON ExternalTask Source # 
Instance details

Defined in Control.Funflow.External

Store ExternalTask Source # 
Instance details

Defined in Control.Funflow.External

ContentHashable IO ExternalTask Source # 
Instance details

Defined in Control.Funflow.External

type Rep ExternalTask Source # 
Instance details

Defined in Control.Funflow.External

type Rep ExternalTask = D1 (MetaData "ExternalTask" "Control.Funflow.External" "funflow-1.5.0-IcEGfJSp3ag8T7kfAGHQUp" False) (C1 (MetaCons "ExternalTask" PrefixI True) ((S1 (MetaSel (Just "_etCommand") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Text) :*: S1 (MetaSel (Just "_etParams") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Param])) :*: (S1 (MetaSel (Just "_etEnv") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Env) :*: S1 (MetaSel (Just "_etWriteToStdOut") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 OutputCapture))))

data TaskDescription Source #

Instances
Show TaskDescription Source # 
Instance details

Defined in Control.Funflow.External

Generic TaskDescription Source # 
Instance details

Defined in Control.Funflow.External

Associated Types

type Rep TaskDescription :: Type -> Type #

type Rep TaskDescription Source # 
Instance details

Defined in Control.Funflow.External

type Rep TaskDescription = D1 (MetaData "TaskDescription" "Control.Funflow.External" "funflow-1.5.0-IcEGfJSp3ag8T7kfAGHQUp" False) (C1 (MetaCons "TaskDescription" PrefixI True) (S1 (MetaSel (Just "_tdOutput") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 ContentHash) :*: S1 (MetaSel (Just "_tdTask") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 ExternalTask)))