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

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

Control.Monad.Component

Contents

Description

Why use ComponentM?

ComponentM values wraps vanilla IO sub-routines whose responsibility is to allocate resources that your application may need (e.g. database connections, tcp sockets, etc). Your program will execute these ComponentM sub-routines at the beginning of it's lifecyle, building an environment that your main application needs in order to work as intended.

By using ComponentM sub-routines your program will automatically:

  • Compose the cleanup sub-routines of all your allocated resources
  • Keep track of initialization time for each resource needed in your application
  • Keep track of teardown time for each resources needed in your application.
  • Isolate the teardown of each resource in your application, ensuring no thrown exception will affect the cleanup of resources.
  • Initialize resources concurrently when using Applicative notation
  • Build a dependency graph of your application resources when using Applicative or Monad notation; and then guarantees the execution of cleanup operations in a topological sorted order
  • Make sure that previously allocated resources are cleaned up when a resource throws an exception on initialization
  • Report all exceptions thrown on each resource teardown
  • Document (through types) what is the purpose of some of the IO sub-routines in your program

These properties are crucial when applications need to run for long periods of time and they are reloaded (without a process restart). It also ensures that resources are cleaned tightly when doing REPL driven development through GHCi.

Synopsis

How to build ComponentM values

ComponentM values are built from vanilla IO sub-routines that allocate resources, the two functions provided are:

buildComponent_
Used when a component in your application does not allocate a resource
buildComponent
Used when a component in your application allocates a resource and requires a cleanup on teardown

Following is an example on how to

import "sqlite-simple" qualified Database.SQLite.Simple as SQLite
import "componentm" Control.Monad.Component (ComponentM, buildComponent, buildComponent_)

-- | App environment record
data AppEnv = AppEnv { appDb :: !SQLite.Connection }

-- | Configuration record
data Config = Config { dbPath :: !String }

readConfig :: IO Config
readConfig =
  -- NOTE: Here we would have a more sophisticated algorithm for fetching
  -- configuration values for our app
  return (Config ":memory:")

configComponent :: ComponentM AppConfig
configComponent = buildComponent_ Config $ do
  readConfigFile ".resourcesconfig.yml"

dbComponent :: FilePath -> ComponentM SQLite.Connection
dbComponent dbPath =
  buildComponent Database (SQLite.open dbPath) SQLite.close

buildAppEnv :: ComponentM AppEnv
buildAppEnv = do
  config <- configComponent
  AppEnv $ dbComponent (dbPath config)

In the previous example, we use both buildComponent_ and buildComponent to create different components that our application needs.

buildComponent Source #

Arguments

:: Text

Unique name for the component being allocated

-> IO a

Allocation IO sub-routine

-> (a -> IO ())

Cleanup IO sub-routine

-> ComponentM a 

Use this function when you want to allocate a new resource (e.g. Database, Socket, etc). It registers the constructed resource in your application component tree and guarantees that its cleanup sub-routine is executed at the end of your program.

This function is similar to the bracket function with the caveat that it expects a Text argument which identifies the component being allocated.

NOTE: The name of your component must be unique; otherwise a DuplicatedComponentKeyDetected will be thrown

buildComponent_ :: Text -> 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.

This is similar to using liftIO, with the caveat that the library will register the given IO sub-routine as a Component, and it will keep track and report its initialization timespan

Making ComponentM values useful

data ComponentM a Source #

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

Instances

runComponentM Source #

Arguments

:: Text

Name of your application (used for tracing purposes)

-> ComponentM a

Builder of your application environment

-> (a -> IO b)

Function where your main application will live

-> IO b 

Constructs the environment of your application by executing the IO sub-routines provided in the buildComponent and buildComponent_ functions; it then executes a callback where your main application will run.

This function:

  • Keeps track of initialization elapsed time for each component of your application
  • Initializes components concurrently as long as they are composed using Applicative functions
  • Builds a graph of your dependencies automatically when composing your ComponentM values via Applicative or Monad interfaces; it then guarantees the execution of cleanup operations in a topological sorted order
  • Guarantees the proper cleanup of previously allocated resources if the creation of a resource throws an exception on initialization
  • Guarantees best-effort cleanup of resources on application teardown in the scenario where a cleanup sub-routine throws an exception
  • Keeps track of teardown elasped time for each component of your application; and reports what exceptions was thrown in case of failures

If you want to trace the behavior of your application on initialization and teardown, use runComponentM1 instead

runComponentM1 Source #

Arguments

:: (ComponentEvent -> IO ())

Callback function to trace ComponentEvent records

-> Text

Name of your application (used for tracing purposes)

-> ComponentM a

Builder of your application environment

-> (a -> IO b)

Function where your main application will live

-> IO b 

Enhances runComponentM with a callback function that emits ComponentEvent records. These events are a great way of tracing the lifecycle and structure of your application.

Error Records

There are two possible failures that the runComponentM functions can thrown

ComponentBuildFailed
This error happens when allocation of some component's resource fails
ComponentRuntimeFailed
This error happens when there is an exception thrown from our main application callback

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

ComponentM tracing accessors

data ComponentEvent Source #

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

data Build Source #

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

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

buildElapsedTime :: Build -> NominalDiffTime Source #

Elasped time in the allocation of a component resource

buildFailure :: Build -> Maybe SomeException Source #

Error thrown in the allocation of a component resource

data BuildResult Source #

Wraps a collection of Build records

Re-exports

data TeardownResult :: * #

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 
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)))))

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