componentm-0.0.0.2: Monad for allocation and cleanup of application resources

Safe HaskellNone
LanguageHaskell2010

Control.Monad.Component.Internal.Types

Synopsis

Documentation

data ComponentError Source #

Exception thrown by the runComponentM family of functions

Constructors

ComponentRuntimeFailed

Failure raised when the Application Callback given to a runComponentM function throws an exception

Fields

ComponentBuildFailed

Failure raised when execution of ComponentM throws an exception

Fields

Instances

Show ComponentError Source # 
Generic ComponentError Source # 

Associated Types

type Rep ComponentError :: * -> * #

Exception ComponentError Source # 
Pretty ComponentError Source # 

Methods

pretty :: ComponentError -> Doc ann #

prettyList :: [ComponentError] -> Doc ann #

type Rep ComponentError Source # 
type Rep ComponentError = D1 * (MetaData "ComponentError" "Control.Monad.Component.Internal.Types" "componentm-0.0.0.2-1CiiSkZ0vt8JdQViYKb6rA" False) ((:+:) * (C1 * (MetaCons "ComponentRuntimeFailed" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "componentErrorOriginalException") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * SomeException)) (S1 * (MetaSel (Just Symbol "componentErrorTeardownResult") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * TeardownResult)))) (C1 * (MetaCons "ComponentBuildFailed" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "componentErrorBuildErrors") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * [ComponentBuildError])) (S1 * (MetaSel (Just Symbol "componentErrorTeardownResult") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * TeardownResult)))))

data ComponentBuildError Source #

Exception raised on the execution of IO sub-routines used when constructing ComponentM values (e.g. buildComponent)

Constructors

DuplicatedComponentKeyDetected !Description

Failure thrown when using the same component key on a Component composition

ComponentAllocationFailed !Description !SomeException

Failure thrown when the allocation sub-routine of a Component fails with an exception

ComponentErrorThrown !SomeException

Failure thrown when calling the throwM when composing ComponentM values

ComponentIOLiftFailed !SomeException

Failure thrown when calling liftIO fails with an exception

newtype ComponentM a Source #

Represents the construction of a Component in your application, components may be composed using a Monad or Applicative interface.

Constructors

ComponentM (IO (Either ([ComponentBuildError], BuildTable) (a, BuildTable))) 

Instances

data Build Source #

Contains metadata about the build of a resource from a ComponentM value

Constructors

Build 

Fields

Instances

Generic Build Source # 

Associated Types

type Rep Build :: * -> * #

Methods

from :: Build -> Rep Build x #

to :: Rep Build x -> Build #

Pretty Build Source # 

Methods

pretty :: Build -> Doc ann #

prettyList :: [Build] -> Doc ann #

Display Build Source # 

Methods

display :: Build -> Utf8Builder #

type Rep Build Source # 
type Rep Build

newtype BuildResult Source #

Wraps a collection of Build records

Constructors

BuildResult 

Fields

data TeardownResult :: * #

Result from a Teardown sub-routine

Instances

Show TeardownResult 
Generic TeardownResult 

Associated Types

type Rep TeardownResult :: * -> * #

NFData TeardownResult 

Methods

rnf :: TeardownResult -> () #

Pretty TeardownResult 

Methods

pretty :: TeardownResult -> Doc ann #

prettyList :: [TeardownResult] -> Doc ann #

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

data ComponentEvent Source #

An event record used to trace the execution of an application initialization and teardown