teardown-0.0.0.2: Build composable, idempotent & transparent application cleanup sub-routines

Copyright(c) Roman Gonzalez 2017
LicenseMIT
Maintainerromanandreg@gmail.com
Stabilityexperimental
Safe HaskellSafe
LanguageHaskell2010

Control.Teardown

Contents

Description

Provides functions that help on the creation of Application teardown sub-routines

Synopsis

Documentation

class ITeardown d where Source #

A record that is or contains a Teardown sub-routine should instantiate this typeclass

Minimal complete definition

teardown

Methods

teardown :: d -> IO TeardownResult Source #

Executes teardown sub-routine returning a TeardownResult

Cleanup main type and function

data Teardown Source #

Sub-routine that performs a resource cleanup operation

Instances

Generic Teardown Source # 

Associated Types

type Rep Teardown :: * -> * #

Methods

from :: Teardown -> Rep Teardown x #

to :: Rep Teardown x -> Teardown #

ITeardown Teardown Source # 
type Rep Teardown Source # 
type Rep Teardown = D1 (MetaData "Teardown" "Control.Teardown.Internal.Core" "teardown-0.0.0.2-CP23rXs1PrmGbF5PqQjcsX" True) (C1 (MetaCons "Teardown" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (IO TeardownResult))))

teardown :: ITeardown d => d -> IO TeardownResult Source #

Executes teardown sub-routine returning a TeardownResult

Functions to create a Teardown record

emptyTeardown :: Description -> Teardown Source #

Creates a stub Teardown sub-routine, normally used when a contract expects a teardown return but there is no allocation being made

newTeardown :: Description -> IO () -> IO Teardown Source #

Creates a new Teardown sub-routine from a cleanup IO action, the side-effects from this action are guaranteed to be executed only once, and also it is guaranteed to be thread-safe in the scenario of multiple threads executing the same teardown procedure.

newDynTeardown :: Description -> IO [TeardownResult] -> Teardown Source #

Creates a Teardown sub-routine that is composed of inner sub-routines that are allocated at runtime. This is useful if allocations are being created and being hold on a Mutable variable of some sort (e.g. IORef, TVar, etc) so that on cleanup this Mutable variable is read and the results of the teardown operation are returned.

concatTeardown :: Description -> [Teardown] -> Teardown Source #

Creates a Teardown sub-routine that is composed of other smaller sub-routines. This is ideal for composing the cleanup of an application from smaller resources allocations that are known at compilation time.

Functions to deal with results from teardown call

data TeardownResult Source #

Result from a Teardown sub-routine

Constructors

BranchResult

Result is composed by multiple teardown sub-routines

Fields

LeafResult

Result represents a single teardown sub-routine

Fields

EmptyResult

Represents a stub cleanup operation (for lifting pure values)

Fields

didTeardownFail :: TeardownResult -> Bool Source #

Returns a boolean indicating if any of the cleanup sub-routine failed

failedToredownCount :: TeardownResult -> Int Source #

Returns number of sub-routines that threw an exception on execution of teardown

toredownCount :: TeardownResult -> Int Source #

Returns number of sub-routines executed at teardown

renderTeardownReport :: TeardownResult -> Doc Source #

Renders an ASCII Tree with the TeardownResult of a Teardown sub-routine execution