teardown-0.3.0.0: Build composable components for your application with clear teardown semantics

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

Control.Monad.Component

Contents

Description

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

Synopsis

ComponentM monad and runner

data ComponentM a Source #

ComponentM is a wrapper of the IO monad that automatically deals with the composition of Teardown sub-routines from resources allocated in every resource of your application. To build ComponentM actions see the buildComponent, buildComponentWithCleanup and buildComponentWithTeardown functions.

runComponentM :: Text -> ComponentM a -> IO (Component a) Source #

Given the name and a ComponentM sub-routine, this function builds an IO sub-routine that returns a Component record.

The name argument is used for trace-ability purposes when executing the teardown of a resulting Component.

  • A note on error scenarios:

Sometimes the given ComponentM sub-routine may fail on execution, in such cases, this function will teardown all component resources allocated so far and throw a ComponentStartupFailure exception.

Component record and functions

data Component a Source #

Represents the result of a ComponentM sub-routine, it contains a resource record which can be recovered using fromComponent and a Teardown sub-routine that can be executed using the teardown function.

Instances

Generic (Component a) Source # 

Associated Types

type Rep (Component a) :: * -> * #

Methods

from :: Component a -> Rep (Component a) x #

to :: Rep (Component a) x -> Component a #

NFData a => NFData (Component a) Source # 

Methods

rnf :: Component a -> () #

ITeardown (Component a) Source # 
type Rep (Component a) Source # 
type Rep (Component a) = D1 (MetaData "Component" "Control.Monad.Component.Internal.Types" "teardown-0.3.0.0-LZiK4LTLuZAIXZzqo3R66V" False) (C1 (MetaCons "Component" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "componentResource") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 a)) (S1 (MetaSel (Just Symbol "componentTeardown") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Teardown))))

fromComponent :: Component a -> a Source #

Fetches the resource of a Component returned by a ComponentM sub-routine.

Component error record

Teardown functions

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 #

NFData Teardown Source # 

Methods

rnf :: Teardown -> () #

type Rep Teardown Source # 
type Rep Teardown = D1 (MetaData "Teardown" "Control.Teardown.Internal.Types" "teardown-0.3.0.0-LZiK4LTLuZAIXZzqo3R66V" True) (C1 (MetaCons "Teardown" PrefixI False) (S1 (MetaSel (Nothing 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

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

Executes teardown sub-routine returning a TeardownResult

newTeardown :: IResource resource => Text -> resource -> IO Teardown Source #

Re-exports

throwM :: MonadThrow m => forall e a. Exception e => e -> m a #

Throw an exception. Note that this throws when this action is run in the monad m, not when it is applied. It is a generalization of Control.Exception's throwIO.

Should satisfy the law:

throwM e >> f = throwM e

fail :: MonadFail m => forall a. String -> m a #

Functions to build ComponentM sub-routines

buildComponent :: IO a -> ComponentM a Source #

Transforms an IO sub-routine into a ComponentM sub-routine; the given IO sub-routine returns a resource that does not allocate any other resources that would need to be cleaned up on a system shutdown.

buildComponentWithCleanup :: IO (a, (Text, IO ())) -> ComponentM a Source #

Transforms an IO sub-routine into a ComponentM sub-routine; the given IO sub-routine must return a tuple where:

  • First position represents the resource being returned from the component
  • Second position represents a named cleanup action that tears down allocated resources to create the first element of the tuple

buildComponentWithTeardown :: IO (a, Teardown) -> ComponentM a Source #

Transforms an IO sub-routine into a ComponentM sub-routine; the given IO sub-routine must return a tuple where:

  • First position represents the resource being returned from the component
  • Second position represents a Teardown record that cleans up allocated resources to create the first element of the tuple