capataz-0.2.1.0: OTP-like supervision trees in Haskell

Safe HaskellNone
LanguageHaskell2010

Control.Concurrent.Capataz

Contents

Description

Public API for the capataz library

Capataz is a library that brings an OTP-like supervisor API to the Haskell concurrency toolset.

Synopsis

Types

class HasSupervisor a where Source #

Utility typeclass to call public supervision API with types that contain a supervisor (e.g. Capataz record).

Methods

getSupervisor :: a m -> Supervisor m Source #

Fetches a supervisor from a record internals.

data CallbackType Source #

Internal record that indicates what type of callback function is being invoked; this is used for telemetry purposes

Instances
Eq CallbackType Source # 
Instance details

Defined in Control.Concurrent.Capataz.Internal.Types

Show CallbackType Source # 
Instance details

Defined in Control.Concurrent.Capataz.Internal.Types

Generic CallbackType Source # 
Instance details

Defined in Control.Concurrent.Capataz.Internal.Types

Associated Types

type Rep CallbackType :: Type -> Type #

Pretty CallbackType Source # 
Instance details

Defined in Control.Concurrent.Capataz.Internal.Types

Methods

pretty :: CallbackType -> Doc ann #

prettyList :: [CallbackType] -> Doc ann #

type Rep CallbackType Source # 
Instance details

Defined in Control.Concurrent.Capataz.Internal.Types

type Rep CallbackType = D1 (MetaData "CallbackType" "Control.Concurrent.Capataz.Internal.Types" "capataz-0.2.1.0-Fs9ChgJx0VFLAFPvWeRfkG" False) (C1 (MetaCons "OnCompletion" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "OnFailure" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "OnTermination" PrefixI False) (U1 :: Type -> Type)))

data WorkerRestartStrategy Source #

Specifies how a Supervisor deals with the lifecycle of worker process in case of completion without errors and failure.

Constructors

Permanent

Supervisor will always restart a worker process, in both completion and failure scenarios.

Transient

Supervisor will only restart worker process if it has a failure in execution.

Temporary

Supervisor will never restart a worker, even on failure.

data WorkerTerminationPolicy Source #

Defines how a Worker process termination should be handled by its supervisor.

Since: 0.0.0.0

Constructors

Infinity

Supervisor waits until infinity for the worker termination callback to finish execution.

BrutalTermination

Supervisor terminates worker process without a chance to call its termination callback.

TimeoutMillis !Int

Supervisor allows a number of milliseconds for worker termination callback complete, if not completed by specified milliseconds the termination is cancelled via a BrutalTermination signal.

Instances
Eq WorkerTerminationPolicy Source # 
Instance details

Defined in Control.Concurrent.Capataz.Internal.Types

Ord WorkerTerminationPolicy Source # 
Instance details

Defined in Control.Concurrent.Capataz.Internal.Types

Show WorkerTerminationPolicy Source # 
Instance details

Defined in Control.Concurrent.Capataz.Internal.Types

Generic WorkerTerminationPolicy Source # 
Instance details

Defined in Control.Concurrent.Capataz.Internal.Types

Associated Types

type Rep WorkerTerminationPolicy :: Type -> Type #

NFData WorkerTerminationPolicy Source # 
Instance details

Defined in Control.Concurrent.Capataz.Internal.Types

Methods

rnf :: WorkerTerminationPolicy -> () #

type Rep WorkerTerminationPolicy Source # 
Instance details

Defined in Control.Concurrent.Capataz.Internal.Types

type Rep WorkerTerminationPolicy = D1 (MetaData "WorkerTerminationPolicy" "Control.Concurrent.Capataz.Internal.Types" "capataz-0.2.1.0-Fs9ChgJx0VFLAFPvWeRfkG" False) (C1 (MetaCons "Infinity" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "BrutalTermination" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "TimeoutMillis" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Int))))

data WorkerOptions m Source #

Specifies all options that can be used to create a Worker Process. You may create a record of this type via the smart constructor buildWorkerOptions.

Since: 0.1.0.0

Instances
Generic (WorkerOptions m) Source # 
Instance details

Defined in Control.Concurrent.Capataz.Internal.Types

Associated Types

type Rep (WorkerOptions m) :: Type -> Type #

type Rep (WorkerOptions m) Source # 
Instance details

Defined in Control.Concurrent.Capataz.Internal.Types

type Rep (WorkerOptions m) = D1 (MetaData "WorkerOptions" "Control.Concurrent.Capataz.Internal.Types" "capataz-0.2.1.0-Fs9ChgJx0VFLAFPvWeRfkG" False) (C1 (MetaCons "WorkerOptions" PrefixI True) ((S1 (MetaSel (Just "workerAction") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (WorkerAction m)) :*: (S1 (MetaSel (Just "workerName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 WorkerName) :*: S1 (MetaSel (Just "workerOnFailure") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (SomeException -> m ())))) :*: ((S1 (MetaSel (Just "workerOnCompletion") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (m ())) :*: S1 (MetaSel (Just "workerOnTermination") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (m ()))) :*: (S1 (MetaSel (Just "workerTerminationPolicy") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 WorkerTerminationPolicy) :*: S1 (MetaSel (Just "workerRestartStrategy") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 WorkerRestartStrategy)))))

data ProcessSpec m Source #

Record used to specify how to build a runtime Process in a static supervision tree; to create values of this type, you must use:

Since: 0.1.0.0

data ProcessTerminationOrder Source #

Specifies the order in which supervised process should be terminated by a Supervisor in case of a restart or shutdown.

Since: 0.0.0.0

Constructors

NewestFirst

Supervisor terminates supervised process from most recent to oldest.

OldestFirst

Supervisor terminates supervised process from oldest to most recent.

Instances
Eq ProcessTerminationOrder Source # 
Instance details

Defined in Control.Concurrent.Capataz.Internal.Types

Ord ProcessTerminationOrder Source # 
Instance details

Defined in Control.Concurrent.Capataz.Internal.Types

Show ProcessTerminationOrder Source # 
Instance details

Defined in Control.Concurrent.Capataz.Internal.Types

Generic ProcessTerminationOrder Source # 
Instance details

Defined in Control.Concurrent.Capataz.Internal.Types

Associated Types

type Rep ProcessTerminationOrder :: Type -> Type #

NFData ProcessTerminationOrder Source # 
Instance details

Defined in Control.Concurrent.Capataz.Internal.Types

Methods

rnf :: ProcessTerminationOrder -> () #

type Rep ProcessTerminationOrder Source # 
Instance details

Defined in Control.Concurrent.Capataz.Internal.Types

type Rep ProcessTerminationOrder = D1 (MetaData "ProcessTerminationOrder" "Control.Concurrent.Capataz.Internal.Types" "capataz-0.2.1.0-Fs9ChgJx0VFLAFPvWeRfkG" False) (C1 (MetaCons "NewestFirst" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "OldestFirst" PrefixI False) (U1 :: Type -> Type))

data ProcessError Source #

Internal exception triggered when a callback of a Worker fails

data SupervisorRestartStrategy Source #

Specifies how a Supervisor restarts a failing process.

Since: 0.0.0.0

Constructors

AllForOne

Supervisor terminates all sibling supervised processes that didn't fail, and then restarts all of them together. This strategy serves best when all processes depend upon each other.

OneForOne

Supervisor only restarts the supervised process that failed.

Instances
Eq SupervisorRestartStrategy Source # 
Instance details

Defined in Control.Concurrent.Capataz.Internal.Types

Ord SupervisorRestartStrategy Source # 
Instance details

Defined in Control.Concurrent.Capataz.Internal.Types

Show SupervisorRestartStrategy Source # 
Instance details

Defined in Control.Concurrent.Capataz.Internal.Types

Generic SupervisorRestartStrategy Source # 
Instance details

Defined in Control.Concurrent.Capataz.Internal.Types

Associated Types

type Rep SupervisorRestartStrategy :: Type -> Type #

NFData SupervisorRestartStrategy Source # 
Instance details

Defined in Control.Concurrent.Capataz.Internal.Types

type Rep SupervisorRestartStrategy Source # 
Instance details

Defined in Control.Concurrent.Capataz.Internal.Types

type Rep SupervisorRestartStrategy = D1 (MetaData "SupervisorRestartStrategy" "Control.Concurrent.Capataz.Internal.Types" "capataz-0.2.1.0-Fs9ChgJx0VFLAFPvWeRfkG" False) (C1 (MetaCons "AllForOne" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "OneForOne" PrefixI False) (U1 :: Type -> Type))

data SupervisorStatus Source #

Internal record used as a state machine, indicating the state of a supervisor process

Constructors

Initializing

This state is set when the process is created and it starts spawning its static process list.

Running

This state is set when the supervisor process starts listenting to both ControlAction and MonitorEvent messages.

Halting

This state is set when the supervisor process is terminating it's assigned worker

Halted

This state is set when the supervisor process is finished

Instances
Eq SupervisorStatus Source # 
Instance details

Defined in Control.Concurrent.Capataz.Internal.Types

Show SupervisorStatus Source # 
Instance details

Defined in Control.Concurrent.Capataz.Internal.Types

Generic SupervisorStatus Source # 
Instance details

Defined in Control.Concurrent.Capataz.Internal.Types

Associated Types

type Rep SupervisorStatus :: Type -> Type #

NFData SupervisorStatus Source # 
Instance details

Defined in Control.Concurrent.Capataz.Internal.Types

Methods

rnf :: SupervisorStatus -> () #

Pretty SupervisorStatus Source # 
Instance details

Defined in Control.Concurrent.Capataz.Internal.Types

type Rep SupervisorStatus Source # 
Instance details

Defined in Control.Concurrent.Capataz.Internal.Types

type Rep SupervisorStatus = D1 (MetaData "SupervisorStatus" "Control.Concurrent.Capataz.Internal.Types" "capataz-0.2.1.0-Fs9ChgJx0VFLAFPvWeRfkG" False) ((C1 (MetaCons "Initializing" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "Running" PrefixI False) (U1 :: Type -> Type)) :+: (C1 (MetaCons "Halting" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "Halted" PrefixI False) (U1 :: Type -> Type)))

data SupervisorOptions m Source #

Instances
HasSupervisorFailureCallback SupervisorOptions Source # 
Instance details

Defined in Control.Concurrent.Capataz.Internal.Types.Lens

Methods

supervisorOnFailureL :: Functor f => ((SomeException -> m ()) -> f (SomeException -> m ())) -> SupervisorOptions m -> f (SupervisorOptions m) Source #

HasSupervisorIntensityReachedCallback SupervisorOptions Source # 
Instance details

Defined in Control.Concurrent.Capataz.Internal.Types.Lens

Methods

supervisorOnIntensityReachedL :: Functor f => (m () -> f (m ())) -> SupervisorOptions m -> f (SupervisorOptions m) Source #

HasSupervisorProcessSpecList SupervisorOptions Source # 
Instance details

Defined in Control.Concurrent.Capataz.Internal.Types.Lens

HasSupervisorProcessTerminationOrder (SupervisorOptions m) Source # 
Instance details

Defined in Control.Concurrent.Capataz.Internal.Types.Lens

HasSupervisorRestartStrategy (SupervisorOptions m) Source # 
Instance details

Defined in Control.Concurrent.Capataz.Internal.Types.Lens

HasSupervisorPeriodSeconds (SupervisorOptions m) Source # 
Instance details

Defined in Control.Concurrent.Capataz.Internal.Types.Lens

HasSupervisorIntensity (SupervisorOptions m) Source # 
Instance details

Defined in Control.Concurrent.Capataz.Internal.Types.Lens

data CapatazOptions m Source #

Allows to:

  • Specify options for the root Supervisor of a capataz system.
  • Provide a CapatazOptions callback to monitor or log a capataz system.

Since: 0.1.0.0

Instances
HasSupervisorFailureCallback CapatazOptions Source # 
Instance details

Defined in Control.Concurrent.Capataz.Internal.Types.Lens

Methods

supervisorOnFailureL :: Functor f => ((SomeException -> m ()) -> f (SomeException -> m ())) -> CapatazOptions m -> f (CapatazOptions m) Source #

HasSupervisorIntensityReachedCallback CapatazOptions Source # 
Instance details

Defined in Control.Concurrent.Capataz.Internal.Types.Lens

Methods

supervisorOnIntensityReachedL :: Functor f => (m () -> f (m ())) -> CapatazOptions m -> f (CapatazOptions m) Source #

HasSupervisorProcessSpecList CapatazOptions Source # 
Instance details

Defined in Control.Concurrent.Capataz.Internal.Types.Lens

HasSupervisorProcessTerminationOrder (CapatazOptions m) Source # 
Instance details

Defined in Control.Concurrent.Capataz.Internal.Types.Lens

HasSupervisorRestartStrategy (CapatazOptions m) Source # 
Instance details

Defined in Control.Concurrent.Capataz.Internal.Types.Lens

HasSupervisorPeriodSeconds (CapatazOptions m) Source # 
Instance details

Defined in Control.Concurrent.Capataz.Internal.Types.Lens

HasSupervisorIntensity (CapatazOptions m) Source # 
Instance details

Defined in Control.Concurrent.Capataz.Internal.Types.Lens

data Capataz m Source #

Record that contains the environment of a capataz monitor, this is used as the main record to create workers and to stop the supervisor thread.

Since: 0.0.0.0

Default Options for Capataz Processes

buildSupervisorOptions Source #

Arguments

:: Monad m 
=> SupervisorName

Name used for telemetry purposes

-> (SupervisorOptions m -> SupervisorOptions m)

Function to modify default supervisor options

-> SupervisorOptions m 

Builds a SupervisorOptions record with defaults from buildSupervisorOptionsWithDefaults. This function allows overrides of these defaults using lenses.

This function is intended to be used in combination with forkSupervisor.

Since: 0.1.0.0

buildSupervisorOptionsWithDefaults Source #

Arguments

:: Monad m 
=> SupervisorName

Name used for telemetry purposes

-> SupervisorOptions m 

Builds a SupervisorOptions record with defaults to create a supervisor process, these defaults are:

This function is intended to be used in combination with forkSupervisor.

Since: 0.1.0.0

buildWorkerOptions Source #

Arguments

:: Monad m 
=> WorkerName

Name used for telemetry purposes

-> m ()

Process sub-routine to be supervised

-> (WorkerOptions m -> WorkerOptions m)

Function to modify default worker options

-> WorkerOptions m 

Builds a WorkerOptions record, keeps the defaults from buildWorkerOptionsWithDefaults but allows overrides using lenses.

This function is intended to be used in combination with forkWorker. See the capataz-simple-example project in the examples directory for a demonstration.

Since: 0.1.0.0

buildWorkerOptions1 Source #

Arguments

:: Monad m 
=> WorkerName

Name used for telemetry purposes

-> (WorkerId -> m ())

Process sub-routine to be supervised

-> (WorkerOptions m -> WorkerOptions m)

Function to modify default worker options

-> WorkerOptions m 

Builds a WorkerOptions record, keeps the defaults from buildWorkerOptionsWithDefaults but allows overrides using lenses.

This function is intended to be used in combination with forkWorker. See the capataz-simple-example project in the examples directory for a demonstration.

The given sub-routine will receive the WorkerId as a parameter.

Since: 0.2.0.0

buildWorkerOptionsWithDefaults Source #

Arguments

:: Monad m 
=> WorkerName

Name used for telemetry purposes

-> m ()

IO sub-routine to be supervised

-> WorkerOptions m 

Builds a WorkerOptions record with defaults to create a worker process, the defaults are:

This function is intended to be used in combination with forkWorker, for creating a worker in an static supervision tree, use workerSpecWithDefaults instead. See the capataz-simple-example project in the examples directory for a demonstration.

Since: 0.1.0.0

supervisorSpec Source #

Arguments

:: Monad m 
=> SupervisorName

Name used for telemetry purposes

-> (SupervisorOptions m -> SupervisorOptions m)

SupervisorOptions modifier

-> ProcessSpec m 

Builds a ProcessSpec record for a supervisor process with defaults from supervisorSpecWithDefaults. This function allows overrides of these defaults using lenses.

This function is used when building a supervisor branch in a static supervision trees.

Since: 0.1.0.0

supervisorSpecWithDefaults Source #

Arguments

:: Monad m 
=> SupervisorName

Name used for telemetry purposes

-> ProcessSpec m 

Builds a ProcessSpec record for a supervisor process with defaults from buildSupervisorOptionsWithDefaults.

This function is used when building a supervisor branch in a static supervision trees.

Since: 0.1.0.0

workerSpec Source #

Arguments

:: Monad m 
=> WorkerName

Name used for telemetry purposes

-> m ()

IO sub-routine to be supervised

-> (WorkerOptions m -> WorkerOptions m)

Function to modify default worker options

-> ProcessSpec m 

Builds a ProcessSpec record for a worker process with defaults from workerSpecWithDefaults. This function allows overrides of these defaults using lenses.

This function is used when building a worker in a static supervision tree.

Since: 0.1.0.0

workerSpec1 Source #

Arguments

:: Monad m 
=> WorkerName

Name used for telemetry purposes

-> (WorkerId -> m ())

sub-routine to be supervised

-> (WorkerOptions m -> WorkerOptions m)

Function to modify default worker options

-> ProcessSpec m 

Builds a ProcessSpec record for a worker process with defaults from workerSpecWithDefaults. This function allows overrides of these defaults using lenses.

This function is used when building a worker in a static supervision tree. The given sub-routine will receive the WorkerId as a parameter

Since: 0.2.0.0

workerSpecWithDefaults Source #

Arguments

:: Monad m 
=> WorkerName

Name used for telemetry purposes

-> m ()

IO sub-routine to be supervised

-> ProcessSpec m 

Builds a ProcessSpec record for a worker process with defaults from buildSupervisorOptionsWithDefaults.

This function is used when building a worker in a static supervision tree.

Since: 0.1.0.0

Lenses to modify Option Records

onSystemEventL :: Functor f => ((CapatazEvent -> m ()) -> f (CapatazEvent -> m ())) -> CapatazOptions m -> f (CapatazOptions m) Source #

supervisorIntensityL :: (HasSupervisorIntensity s, Functor f) => (Int -> f Int) -> s -> f s Source #

Specifies how many errors is a supervisor able to handle; check: http://erlang.org/doc/design_principles/sup_princ.html#max_intensity.

supervisorPeriodSecondsL :: (HasSupervisorPeriodSeconds s, Functor f) => (NominalDiffTime -> f NominalDiffTime) -> s -> f s Source #

Specifies period of time in which a supervisor can receive a number of errors specified in "supervisorIntensityL".

supervisorProcessSpecListL :: (HasSupervisorProcessSpecList s, Functor f) => ([ProcessSpec m] -> f [ProcessSpec m]) -> s m -> f (s m) Source #

Specifies a static list of processes that start automatically with a supervisor.

supervisorProcessTerminationOrderL :: (HasSupervisorProcessTerminationOrder s, Functor f) => (ProcessTerminationOrder -> f ProcessTerminationOrder) -> s -> f s Source #

Specifies order in which a supervisor is going to terminate its supervised processes.

supervisorOnIntensityReachedL :: (HasSupervisorIntensityReachedCallback s, Functor f) => (m () -> f (m ())) -> s m -> f (s m) Source #

Specifies a callback sub-routine that gets executed when there is a breach in a supervisor's error intensity.

supervisorOnFailureL :: (HasSupervisorFailureCallback s, Functor f) => ((SomeException -> m ()) -> f (SomeException -> m ())) -> s m -> f (s m) Source #

Specifies callback sub-routine that gets executed when a supervisor fails.

workerOnFailureL :: Functor f => ((SomeException -> m ()) -> f (SomeException -> m ())) -> WorkerOptions m -> f (WorkerOptions m) Source #

Specifies callback that gets executed when worker sub-routine has runtime error.

NOTE: the given sub-routine execution may be interrupted depending on the worker WorkerTerminationPolicy.

workerOnCompletionL :: Functor f => (m () -> f (m ())) -> WorkerOptions m -> f (WorkerOptions m) Source #

Specifies callback that gets executed when worker sub-routine completes with no errors.

NOTE: the given sub-routine execution may be interrupted depending on the worker WorkerTerminationPolicy.

workerOnTerminationL :: Functor f => (m () -> f (m ())) -> WorkerOptions m -> f (WorkerOptions m) Source #

Specifies callback that gets executed when worker sub-routine is terminated by its supervisor; this may happen in case of a capataz system shutdown or when there is an AllForOne restart policy in place.

NOTE: the given sub-routine execution may be interrupted depending on the worker WorkerTerminationPolicy.

workerTerminationPolicyL :: Functor f => (WorkerTerminationPolicy -> f WorkerTerminationPolicy) -> WorkerOptions m -> f (WorkerOptions m) Source #

Specifies how to handle a worker termination. See WorkerTerminationPolicy documentation for more details.

workerRestartStrategyL :: Functor f => (WorkerRestartStrategy -> f WorkerRestartStrategy) -> WorkerOptions m -> f (WorkerOptions m) Source #

Specifies how supervisor should deal with an error when worker fails or completes. See WorkerRestartStrategy documentation for more details.

Core functionality

forkWorker Source #

Arguments

:: (MonadIO m, HasSupervisor supervisor) 
=> WorkerOptions m

Worker options (restart, name, callbacks, etc)

-> supervisor m

Supervisor that supervises the worker

-> m WorkerId

An identifier that can be used to terminate the Worker

Creates a green thread from an IO () sub-routine. Depending in options defined in the WorkerOptions record, it will automatically restart this sub-routine in case of failures.

See documentation of related functions:

forkSupervisor Source #

Arguments

:: (MonadIO m, HasSupervisor parentSupervisor) 
=> SupervisorOptions m

Supervisor options

-> parentSupervisor m

Parent supervisor instance that supervises new supervisor

-> m (Supervisor m)

A record used to dynamically create and supervise other processes

Creates a green thread which monitors other green threads for failures and restarts them using settings defined on SupervisorOptions.

See documentation of related functions:

forkCapataz :: (MonadUnliftIO m, MonadIO m) => Text -> (CapatazOptions m -> CapatazOptions m) -> m (Capataz m) Source #

Creates a Capataz record, which holds both a root supervisor and a Teardown to shut down the system. The root supervisor monitors failures on process threads defined with CapatazOptions or created dynamically using forkWorker or forkSupervisor.

terminateCapataz :: MonadIO m => Capataz m -> m TeardownResult Source #

Terminates a Capataz system (all supervised threads) and returns a TeardownResult

Since: 0.2.0.0

terminateCapataz_ :: MonadIO m => Capataz m -> m () Source #

Terminates a Capataz system (all supervised threads)

Since: 0.2.0.0

terminateProcess :: (MonadIO m, HasSupervisor supervisor) => Text -> ProcessId -> supervisor m -> m Bool Source #

Stops the execution of a green thread being supervised by the given supervisor.

IMPORTANT If ProcessId maps to a worker that is configured with a Permanent worker restart strategy, the worker green thread __will be restarted again__.

Utility functions

joinCapatazThread :: MonadIO m => Capataz m -> m () Source #

Joins the thread of the root supervisor of the given capataz system to the current thread.

getSupervisorProcessId :: Supervisor m -> ProcessId Source #

Gets the process identifier of a Supervisor; normally used for termination.

getSupervisorAsync :: Supervisor m -> Async () Source #

Gets the Async of a Supervisor thread.

NOTE: There is no way to get the Async value of the root supervisor; this is done on-purpose to avoid error scenarios.

getCapatazTeardown :: Capataz m -> Teardown Source #

Gets Teardown record of this capataz system.

Teardown (re-exported)

data TeardownResult #

Result from a Teardown sub-routine

Instances
Show TeardownResult 
Instance details

Defined in Control.Teardown.Internal.Types

Generic TeardownResult 
Instance details

Defined in Control.Teardown.Internal.Types

Associated Types

type Rep TeardownResult :: Type -> Type #

NFData TeardownResult 
Instance details

Defined in Control.Teardown.Internal.Types

Methods

rnf :: TeardownResult -> () #

Pretty TeardownResult 
Instance details

Defined in Control.Teardown.Internal.Types

Methods

pretty :: TeardownResult -> Doc ann #

prettyList :: [TeardownResult] -> Doc ann #

Display TeardownResult 
Instance details

Defined in Control.Teardown.Internal.Types

type Rep TeardownResult 
Instance details

Defined in Control.Teardown.Internal.Types

type Rep TeardownResult = D1 (MetaData "TeardownResult" "Control.Teardown.Internal.Types" "teardown-0.5.0.1-AvuRz5Lduq0HYkve5d1AK9" False) (C1 (MetaCons "BranchResult" PrefixI True) ((S1 (MetaSel (Just "resultDescription") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Description) :*: S1 (MetaSel (Just "resultElapsedTime") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 NominalDiffTime)) :*: (S1 (MetaSel (Just "resultDidFail") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Bool) :*: S1 (MetaSel (Just "resultListing") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 [TeardownResult]))) :+: (C1 (MetaCons "LeafResult" PrefixI True) (S1 (MetaSel (Just "resultDescription") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Description) :*: (S1 (MetaSel (Just "resultElapsedTime") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 NominalDiffTime) :*: S1 (MetaSel (Just "resultError") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe SomeException)))) :+: C1 (MetaCons "EmptyResult" PrefixI True) (S1 (MetaSel (Just "resultDescription") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Description))))

Lens (re-exported)

(&) :: a -> (a -> b) -> b infixl 1 #

& is a reverse application operator. This provides notational convenience. Its precedence is one higher than that of the forward application operator $, which allows & to be nested in $.

>>> 5 & (+1) & show
"6"

Since: base-4.8.0.0

set :: ASetter s t a b -> b -> s -> t #

set is a synonym for (.~).

Setting the 1st component of a pair:

set _1 :: x -> (a, b) -> (x, b)
set _1 = \x t -> (x, snd t)

Using it to rewrite (<$):

set mapped :: Functor f => a -> f b -> f a
set mapped = (<$)