teardown-0.5.0.1: Build safe and composable teardown sub-routines for resources

Copyright(c) Roman Gonzalez 20172018
LicenseMIT
Maintaineropen-source@roman-gonzalez.info
Stabilityexperimental
Safe HaskellNone
LanguageHaskell2010

Control.Teardown

Contents

Description

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

Synopsis

Typeclasses for extending teardown functionality

class HasTeardown teardown where Source #

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

Methods

getTeardown :: teardown -> Teardown Source #

Executes teardown sub-routine returning a TeardownResult

Instances
HasTeardown Teardown Source # 
Instance details

Defined in Control.Teardown.Internal.Core

class IResource resource Source #

A resource or sub-routine that can be transformed into a Teardown operation

Minimal complete definition

newTeardown

Instances
IResource Teardown Source #

Wraps an existing Teardown record; the wrapper Teardown record represents a "parent resource" on the TeardownResult

Instance details

Defined in Control.Teardown.Internal.Core

(TypeError (Text "DEPRECATED: Execute a 'newTeardown' call per allocated resource") :: Constraint) => IResource [(Text, IO ())] Source #

Deprecated instance that creates a Teardown record from a list of cleanup sub-routines (creating a Teardown record for each).

WARNING: This function assumes you are creating many sub-resources at once; this approach has a major risk of leaking resources, and that is why is deprecated; execute newTeardown for every resource you allocate.

NOTE: The IO () sub-routines given are going to be executed in reverse order at teardown time.

Since 0.4.1.0

Instance details

Defined in Control.Teardown.Internal.Core

Methods

newTeardown :: Text -> [(Text, IO ())] -> IO Teardown Source #

IResource [Teardown] Source #

Wraps a list of Teardown record; the new record will have one extra level of description. Same behaviour as the [(Text, IO ())] instance, but works for APIs that already return a Teardown as their cleanup.

Instance details

Defined in Control.Teardown.Internal.Core

IResource (IO [Teardown]) Source #

Wraps an IO action that returns a list of Teardown record; the new record will have one extra level of description. Same behaviour as the [(Text, IO ())] instance, but works for APIs that already return a Teardown as their cleanup.

Instance details

Defined in Control.Teardown.Internal.Core

IResource (IO [TeardownResult]) Source #

Creates a Teardown record from executing a sub-routine that releases short-lived Teardown records. This is useful when short-lived Teardown are accumulated on a collection inside a mutable variable (e.g. IORef, TVar, etc) and we want to release them

Instance details

Defined in Control.Teardown.Internal.Core

IResource (IO ()) Source #

Creates a new Teardown record from a cleanup "IO ()" sub-routine; the Teardown API guarantees:

  • The execution of given "IO ()" sub-routine happens exactly once
  • The execution is thread-safe when multiple threads try to call "runTeardown"

IMPORTANT: The IO () sub-routine _must not_ block or take a long time; this sub-routine cannot be stopped by an async exception

Instance details

Defined in Control.Teardown.Internal.Core

Methods

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

Cleanup main type and function

data Teardown Source #

Sub-routine that performs a resource cleanup operation

Instances
Generic Teardown Source # 
Instance details

Defined in Control.Teardown.Internal.Types

Associated Types

type Rep Teardown :: Type -> Type #

Methods

from :: Teardown -> Rep Teardown x #

to :: Rep Teardown x -> Teardown #

NFData Teardown Source # 
Instance details

Defined in Control.Teardown.Internal.Types

Methods

rnf :: Teardown -> () #

IResource Teardown Source #

Wraps an existing Teardown record; the wrapper Teardown record represents a "parent resource" on the TeardownResult

Instance details

Defined in Control.Teardown.Internal.Core

HasTeardown Teardown Source # 
Instance details

Defined in Control.Teardown.Internal.Core

IResource [Teardown] Source #

Wraps a list of Teardown record; the new record will have one extra level of description. Same behaviour as the [(Text, IO ())] instance, but works for APIs that already return a Teardown as their cleanup.

Instance details

Defined in Control.Teardown.Internal.Core

IResource (IO [Teardown]) Source #

Wraps an IO action that returns a list of Teardown record; the new record will have one extra level of description. Same behaviour as the [(Text, IO ())] instance, but works for APIs that already return a Teardown as their cleanup.

Instance details

Defined in Control.Teardown.Internal.Core

type Rep Teardown Source # 
Instance details

Defined in Control.Teardown.Internal.Types

type Rep Teardown = D1 (MetaData "Teardown" "Control.Teardown.Internal.Types" "teardown-0.5.0.1-CQOiJliN0tFL0A6mXwsGDY" True) (C1 (MetaCons "Teardown" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (IO TeardownResult))))

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

Instances
Show TeardownResult Source # 
Instance details

Defined in Control.Teardown.Internal.Types

Generic TeardownResult Source # 
Instance details

Defined in Control.Teardown.Internal.Types

Associated Types

type Rep TeardownResult :: Type -> Type #

NFData TeardownResult Source # 
Instance details

Defined in Control.Teardown.Internal.Types

Methods

rnf :: TeardownResult -> () #

Pretty TeardownResult Source # 
Instance details

Defined in Control.Teardown.Internal.Types

Methods

pretty :: TeardownResult -> Doc ann #

prettyList :: [TeardownResult] -> Doc ann #

Display TeardownResult Source # 
Instance details

Defined in Control.Teardown.Internal.Types

IResource (IO [TeardownResult]) Source #

Creates a Teardown record from executing a sub-routine that releases short-lived Teardown records. This is useful when short-lived Teardown are accumulated on a collection inside a mutable variable (e.g. IORef, TVar, etc) and we want to release them

Instance details

Defined in Control.Teardown.Internal.Core

type Rep TeardownResult Source # 
Instance details

Defined in Control.Teardown.Internal.Types

runTeardown :: HasTeardown t => t -> IO TeardownResult Source #

Executes all composed Teardown sub-routines safely. This version returns a Tree data structure wich can be used to gather facts from the resource cleanup

runTeardown_ :: HasTeardown t => t -> IO () Source #

Executes all composed Teardown sub-routines safely

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 :: IResource resource => Text -> resource -> IO Teardown Source #

Functions to deal with results from teardown call

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 "runTeardown"

toredownCount :: TeardownResult -> Int Source #

Returns number of released resources from a "runTeardown" execution

prettyTeardownResult :: TeardownResult -> Doc ann Source #

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