extensible-effects-concurrent-0.26.1: Message passing concurrency as extensible-effect

Safe HaskellNone
LanguageHaskell2010

Control.Eff.Concurrent.SingleThreaded

Contents

Description

Concurrent, communicating processes, executed using a single-threaded scheduler, with support for IO and Logs.

This module re-exports most of the library.

There are several scheduler implementations to choose from.

This module re-exports the impure parts of Control.Eff.Concurrent.Process.SingleThreadedScheduler.

To use another scheduler implementation, don't import this module, but instead import one of:

Since: 0.25.0

Synopsis

Generic functions and type for Processes and Messages

newtype Facility Source #

An rfc 5424 facility

Constructors

Facility 

Fields

Instances
Eq Facility Source # 
Instance details

Defined in Control.Eff.Log.Message

Ord Facility Source # 
Instance details

Defined in Control.Eff.Log.Message

Show Facility Source # 
Instance details

Defined in Control.Eff.Log.Message

Generic Facility Source # 
Instance details

Defined in Control.Eff.Log.Message

Associated Types

type Rep Facility :: Type -> Type #

Methods

from :: Facility -> Rep Facility x #

to :: Rep Facility x -> Facility #

Default Facility Source # 
Instance details

Defined in Control.Eff.Log.Message

Methods

def :: Facility #

NFData Facility Source # 
Instance details

Defined in Control.Eff.Log.Message

Methods

rnf :: Facility -> () #

type Rep Facility Source # 
Instance details

Defined in Control.Eff.Log.Message

type Rep Facility = D1 (MetaData "Facility" "Control.Eff.Log.Message" "extensible-effects-concurrent-0.26.1-H4MbFpru2ZADB31xfNLjdz" True) (C1 (MetaCons "Facility" PrefixI True) (S1 (MetaSel (Just "fromFacility") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Int)))

data Severity Source #

An rfc 5424 severity

Instances
Eq Severity Source # 
Instance details

Defined in Control.Eff.Log.Message

Ord Severity Source # 
Instance details

Defined in Control.Eff.Log.Message

Show Severity Source # 
Instance details

Defined in Control.Eff.Log.Message

Generic Severity Source # 
Instance details

Defined in Control.Eff.Log.Message

Associated Types

type Rep Severity :: Type -> Type #

Methods

from :: Severity -> Rep Severity x #

to :: Rep Severity x -> Severity #

Default Severity Source # 
Instance details

Defined in Control.Eff.Log.Message

Methods

def :: Severity #

NFData Severity Source # 
Instance details

Defined in Control.Eff.Log.Message

Methods

rnf :: Severity -> () #

type Rep Severity Source # 
Instance details

Defined in Control.Eff.Log.Message

type Rep Severity = D1 (MetaData "Severity" "Control.Eff.Log.Message" "extensible-effects-concurrent-0.26.1-H4MbFpru2ZADB31xfNLjdz" True) (C1 (MetaCons "Severity" PrefixI True) (S1 (MetaSel (Just "fromSeverity") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Int)))

data SdParameter Source #

Component of an RFC-5424 StructuredDataElement

Constructors

MkSdParameter !Text !Text 
Instances
Eq SdParameter Source # 
Instance details

Defined in Control.Eff.Log.Message

Ord SdParameter Source # 
Instance details

Defined in Control.Eff.Log.Message

Show SdParameter Source # 
Instance details

Defined in Control.Eff.Log.Message

Generic SdParameter Source # 
Instance details

Defined in Control.Eff.Log.Message

Associated Types

type Rep SdParameter :: Type -> Type #

NFData SdParameter Source # 
Instance details

Defined in Control.Eff.Log.Message

Methods

rnf :: SdParameter -> () #

type Rep SdParameter Source # 
Instance details

Defined in Control.Eff.Log.Message

type Rep SdParameter = D1 (MetaData "SdParameter" "Control.Eff.Log.Message" "extensible-effects-concurrent-0.26.1-H4MbFpru2ZADB31xfNLjdz" False) (C1 (MetaCons "MkSdParameter" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text)))

data StructuredDataElement Source #

RFC-5424 defines how structured data can be included in a log message.

Instances
Eq StructuredDataElement Source # 
Instance details

Defined in Control.Eff.Log.Message

Ord StructuredDataElement Source # 
Instance details

Defined in Control.Eff.Log.Message

Show StructuredDataElement Source # 
Instance details

Defined in Control.Eff.Log.Message

Generic StructuredDataElement Source # 
Instance details

Defined in Control.Eff.Log.Message

Associated Types

type Rep StructuredDataElement :: Type -> Type #

NFData StructuredDataElement Source # 
Instance details

Defined in Control.Eff.Log.Message

Methods

rnf :: StructuredDataElement -> () #

type Rep StructuredDataElement Source # 
Instance details

Defined in Control.Eff.Log.Message

type Rep StructuredDataElement = D1 (MetaData "StructuredDataElement" "Control.Eff.Log.Message" "extensible-effects-concurrent-0.26.1-H4MbFpru2ZADB31xfNLjdz" False) (C1 (MetaCons "SdElement" PrefixI True) (S1 (MetaSel (Just "_sdElementId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text) :*: S1 (MetaSel (Just "_sdElementParameters") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 [SdParameter])))

data LogMessage Source #

A message data type inspired by the RFC-5424 Syslog Protocol

Instances
Eq LogMessage Source # 
Instance details

Defined in Control.Eff.Log.Message

Show LogMessage Source #

This instance is only supposed to be used for unit tests and debugging.

Instance details

Defined in Control.Eff.Log.Message

IsString LogMessage Source # 
Instance details

Defined in Control.Eff.Log.Message

Generic LogMessage Source # 
Instance details

Defined in Control.Eff.Log.Message

Associated Types

type Rep LogMessage :: Type -> Type #

Default LogMessage Source # 
Instance details

Defined in Control.Eff.Log.Message

Methods

def :: LogMessage #

NFData LogMessage Source # 
Instance details

Defined in Control.Eff.Log.Message

Methods

rnf :: LogMessage -> () #

ToLogMessage LogMessage Source # 
Instance details

Defined in Control.Eff.Log.Message

Handle Logs e a (LogPredicate -> k) Source # 
Instance details

Defined in Control.Eff.Log.Handler

Methods

handle :: (Eff e a -> LogPredicate -> k) -> Arrs e v a -> Logs v -> LogPredicate -> k #

handle_relay :: (e ~ (Logs ': r'), Relay (LogPredicate -> k) r') => (a -> LogPredicate -> k) -> (Eff e a -> LogPredicate -> k) -> Eff e a -> LogPredicate -> k #

respond_relay :: (a -> LogPredicate -> k) -> (Eff e a -> LogPredicate -> k) -> Eff e a -> LogPredicate -> k #

type Rep LogMessage Source # 
Instance details

Defined in Control.Eff.Log.Message

emergencySeverity :: Severity Source #

Smart constructor for the RFC-5424 emergency LogMessage Severity. This corresponds to the severity value 0. See lmSeverity.

alertSeverity :: Severity Source #

Smart constructor for the RFC-5424 alert LogMessage Severity. This corresponds to the severity value 1. See lmSeverity.

criticalSeverity :: Severity Source #

Smart constructor for the RFC-5424 critical LogMessage Severity. This corresponds to the severity value 2. See lmSeverity.

errorSeverity :: Severity Source #

Smart constructor for the RFC-5424 error LogMessage Severity. This corresponds to the severity value 3. See lmSeverity.

warningSeverity :: Severity Source #

Smart constructor for the RFC-5424 warning LogMessage Severity. This corresponds to the severity value 4. See lmSeverity.

noticeSeverity :: Severity Source #

Smart constructor for the RFC-5424 notice LogMessage Severity. This corresponds to the severity value 5. See lmSeverity.

informationalSeverity :: Severity Source #

Smart constructor for the RFC-5424 informational LogMessage Severity. This corresponds to the severity value 6. See lmSeverity.

debugSeverity :: Severity Source #

Smart constructor for the RFC-5424 debug LogMessage Severity. This corresponds to the severity value 7. See lmSeverity.

kernelMessages :: Facility Source #

Smart constructor for the RFC-5424 LogMessage facility kernelMessages. See lmFacility.

userLevelMessages :: Facility Source #

Smart constructor for the RFC-5424 LogMessage facility userLevelMessages. See lmFacility.

mailSystem :: Facility Source #

Smart constructor for the RFC-5424 LogMessage facility mailSystem. See lmFacility.

systemDaemons :: Facility Source #

Smart constructor for the RFC-5424 LogMessage facility systemDaemons. See lmFacility.

securityAuthorizationMessages4 :: Facility Source #

Smart constructor for the RFC-5424 LogMessage facility securityAuthorizationMessages4. See lmFacility.

linePrinterSubsystem :: Facility Source #

Smart constructor for the RFC-5424 LogMessage facility linePrinterSubsystem. See lmFacility.

networkNewsSubsystem :: Facility Source #

Smart constructor for the RFC-5424 LogMessage facility networkNewsSubsystem. See lmFacility.

uucpSubsystem :: Facility Source #

Smart constructor for the RFC-5424 LogMessage facility uucpSubsystem. See lmFacility.

clockDaemon :: Facility Source #

Smart constructor for the RFC-5424 LogMessage facility clockDaemon. See lmFacility.

securityAuthorizationMessages10 :: Facility Source #

Smart constructor for the RFC-5424 LogMessage facility securityAuthorizationMessages10. See lmFacility.

ftpDaemon :: Facility Source #

Smart constructor for the RFC-5424 LogMessage facility ftpDaemon. See lmFacility.

ntpSubsystem :: Facility Source #

Smart constructor for the RFC-5424 LogMessage facility ntpSubsystem. See lmFacility.

logAuditFacility :: Facility Source #

Smart constructor for the RFC-5424 LogMessage facility logAuditFacility. See lmFacility.

logAlertFacility :: Facility Source #

Smart constructor for the RFC-5424 LogMessage facility logAlertFacility. See lmFacility.

clockDaemon2 :: Facility Source #

Smart constructor for the RFC-5424 LogMessage facility clockDaemon2. See lmFacility.

local0 :: Facility Source #

Smart constructor for the RFC-5424 LogMessage facility local0. See lmFacility.

local1 :: Facility Source #

Smart constructor for the RFC-5424 LogMessage facility local1. See lmFacility.

local2 :: Facility Source #

Smart constructor for the RFC-5424 LogMessage facility local2. See lmFacility.

local3 :: Facility Source #

Smart constructor for the RFC-5424 LogMessage facility local3. See lmFacility.

local4 :: Facility Source #

Smart constructor for the RFC-5424 LogMessage facility local4. See lmFacility.

local5 :: Facility Source #

Smart constructor for the RFC-5424 LogMessage facility local5. See lmFacility.

local6 :: Facility Source #

Smart constructor for the RFC-5424 LogMessage facility local6. See lmFacility.

local7 :: Facility Source #

Smart constructor for the RFC-5424 LogMessage facility local7. See lmFacility.

sdElementId :: Functor f => (Text -> f Text) -> StructuredDataElement -> f StructuredDataElement Source #

A lens for the key or ID of a group of RFC 5424 key-value pairs.

type LogPredicate = LogMessage -> Bool Source #

The filter predicate for message that shall be logged.

See Control.Eff.Log

class ToLogMessage a where Source #

Things that can become a LogMessage

Methods

toLogMessage :: a -> LogMessage Source #

Convert the value to a LogMessage

lmAppName :: Functor f => (Maybe Text -> f (Maybe Text)) -> LogMessage -> f LogMessage Source #

A lens for the RFC 5424 application name of a LogMessage

One useful pattern for using this field, is to implement log filters that allow info and debug message from the application itself while only allowing warning and error messages from third party libraries:

debugLogsForAppName myAppName lm =
  view lmAppName lm == Just myAppName || lmSeverityIsAtLeast warningSeverity lm

This concept is also implemented in discriminateByAppName.

lmHostname :: Functor f => (Maybe Text -> f (Maybe Text)) -> LogMessage -> f LogMessage Source #

A lens for the hostname of a LogMessage The function setLogMessageHostname can be used to set the field.

lmMessage :: Functor f => (Text -> f Text) -> LogMessage -> f LogMessage Source #

A lens for the user defined textual message of a LogMessage

lmMessageId :: Functor f => (Maybe Text -> f (Maybe Text)) -> LogMessage -> f LogMessage Source #

A lens for a user defined message id of a LogMessage

lmProcessId :: Functor f => (Maybe Text -> f (Maybe Text)) -> LogMessage -> f LogMessage Source #

A lens for a user defined of process id of a LogMessage

lmSrcLoc :: Functor f => (Maybe SrcLoc -> f (Maybe SrcLoc)) -> LogMessage -> f LogMessage Source #

A lens for the SrcLoc of a LogMessage

lmThreadId :: Functor f => (Maybe ThreadId -> f (Maybe ThreadId)) -> LogMessage -> f LogMessage Source #

A lens for the ThreadId of a LogMessage The function setLogMessageThreadId can be used to set the field.

lmTimestamp :: Functor f => (Maybe UTCTime -> f (Maybe UTCTime)) -> LogMessage -> f LogMessage Source #

A lens for the UTC time of a LogMessage The function setLogMessageTimestamp can be used to set the field.

setCallStack :: CallStack -> LogMessage -> LogMessage Source #

Put the source location of the given callstack in lmSrcLoc

setLogMessageTimestamp :: LogMessage -> IO LogMessage Source #

An IO action that sets the current UTC time in lmTimestamp.

setLogMessageThreadId :: LogMessage -> IO LogMessage Source #

An IO action appends the the ThreadId of the calling process (see myThreadId) to lmMessage.

setLogMessageHostname :: LogMessage -> IO LogMessage Source #

An IO action that sets the current hosts fully qualified hostname in lmHostname.

allLogMessages :: LogPredicate Source #

All messages.

See Control.Eff.Log.Message for more predicates.

noLogMessages :: LogPredicate Source #

No messages.

See Control.Eff.Log.Message for more predicates.

lmSeverityIs :: Severity -> LogPredicate Source #

Match LogMessages that have exactly the given severity. See lmSeverityIsAtLeast.

See Control.Eff.Log.Message for more predicates.

lmSeverityIsAtLeast :: Severity -> LogPredicate Source #

Match LogMessages that have the given severity or worse. See lmSeverityIs.

See Control.Eff.Log.Message for more predicates.

lmMessageStartsWith :: Text -> LogPredicate Source #

Match LogMessages whose lmMessage starts with the given string.

See Control.Eff.Log.Message for more predicates.

discriminateByAppName :: Text -> LogPredicate -> LogPredicate -> LogPredicate Source #

Apply a LogPredicate based on the lmAppName and delegate to one of two LogPredicates.

One useful application for this is to allow info and debug message from one application, e.g. the current application itself, while at the same time allowing only warning and error messages from third party libraries.

See Control.Eff.Log.Message for more predicates.

data LogMessageTimeRenderer Source #

A rendering function for the lmTimestamp field.

type LogMessageRenderer a = LogMessage -> a Source #

LogMessage rendering function

mkLogMessageTimeRenderer Source #

Arguments

:: String

The format string that is passed to formatTime

-> LogMessageTimeRenderer 

Make a LogMessageTimeRenderer using formatTime in the defaultLocale.

suppressTimestamp :: LogMessageTimeRenderer Source #

Don't render the time stamp

rfc3164Timestamp :: LogMessageTimeRenderer Source #

Render the time stamp using "%h %d %H:%M:%S"

rfc5424Timestamp :: LogMessageTimeRenderer Source #

Render the time stamp to iso8601DateFormat (Just "%H:%M:%S%6QZ")

rfc5424NoZTimestamp :: LogMessageTimeRenderer Source #

Render the time stamp like rfc5424Timestamp does, but omit the terminal Z character.

renderLogMessageBody :: LogMessageRenderer Text Source #

Print the thread id, the message and the source file location, seperated by simple white space.

renderLogMessageBodyNoLocation :: LogMessageRenderer Text Source #

Print the thread id, the message and the source file location, seperated by simple white space.

renderLogMessageBodyFixWidth :: LogMessageRenderer Text Source #

Print the body of a LogMessage with fix size fields (60) for the message itself and 30 characters for the location

renderMaybeLogMessageLens :: Text -> Getter LogMessage (Maybe Text) -> LogMessageRenderer Text Source #

Render a field of a LogMessage using the corresponsing lens.

renderLogMessageSrcLoc :: LogMessageRenderer (Maybe Text) Source #

Render the source location as: at filepath:linenumber.

renderSyslogSeverityAndFacility :: LogMessageRenderer Text Source #

Render the severity and facility as described in RFC-3164

Render e.g. as <192>.

Useful as header for syslog compatible log output.

renderLogMessageSyslog :: LogMessageRenderer Text Source #

Render the LogMessage to contain the severity, message, message-id, pid.

Omit hostname, PID and timestamp.

Render the header using renderSyslogSeverity

Useful for logging to devlog

renderLogMessageConsoleLog :: LogMessageRenderer Text Source #

Render a LogMessage human readable, for console logging

renderRFC3164 :: LogMessageRenderer Text Source #

Render a LogMessage according to the rules in the RFC-3164.

renderRFC3164WithRFC5424Timestamps :: LogMessageRenderer Text Source #

Render a LogMessage according to the rules in the RFC-3164 but use RFC5424 time stamps.

renderRFC3164WithTimestamp :: LogMessageTimeRenderer -> LogMessageRenderer Text Source #

Render a LogMessage according to the rules in the RFC-3164 but use the custom LogMessageTimeRenderer.

renderRFC5424 :: LogMessageRenderer Text Source #

Render a LogMessage according to the rules in the RFC-5424.

Equivalent to renderRFC5424Header <> const " " <> renderLogMessageBody.

Since: 0.21.0

renderRFC5424NoLocation :: LogMessageRenderer Text Source #

Render a LogMessage according to the rules in the RFC-5424, like renderRFC5424 but suppress the source location information.

Equivalent to renderRFC5424Header <> const " " <> renderLogMessageBodyNoLocation.

Since: 0.21.0

renderRFC5424Header :: LogMessageRenderer Text Source #

Render the header and strucuted data of a LogMessage according to the rules in the RFC-5424, but do not render the lmMessage.

Since: 0.22.0

newtype PureLogWriter a Source #

A phantom type for the HandleLogWriter class for pure LogWriters

Constructors

MkPureLogWriter 

class HandleLogWriter (writerEff :: Type -> Type) e where Source #

The instances of this class are the monads that define (side-) effect(s) of writting logs.

Minimal complete definition

handleLogWriterEffect

Methods

handleLogWriterEffect :: writerEff () -> Eff e () Source #

Run the side effect of a LogWriter in a compatible Eff.

liftWriteLogMessage :: SetMember LogWriterReader (LogWriterReader writerEff) e => LogMessage -> Eff e () Source #

Write a message using the LogWriter found in the environment.

The semantics of this function are a combination of runLogWriter and handleLogWriterEffect, with the LogWriter read from a LogWriterReader.

Instances
Lifted IO e => HandleLogWriter IO e Source # 
Instance details

Defined in Control.Eff.Log.Writer

HandleLogWriter PureLogWriter e Source #

A LogWriter monad for Trace based pure logging.

Instance details

Defined in Control.Eff.Log.Writer

Member CaptureLogWriter e => HandleLogWriter CaptureLogs e Source #

A LogWriter monad for pure logging.

The HandleLogWriter instance for this type assumes a Writer effect.

Instance details

Defined in Control.Eff.LogWriter.Capture

data LogWriterReader h v Source #

A Reader specialized for LogWriters

The existing Reader couldn't be used together with SetMember, so this lazy reader was written, specialized to reading LogWriter.

Instances
(MonadBase m m, LiftedBase m r) => MonadBaseControl m (Eff (LogWriterReader h ': r)) Source # 
Instance details

Defined in Control.Eff.Log.Writer

Associated Types

type StM (Eff (LogWriterReader h ': r)) a :: Type #

Methods

liftBaseWith :: (RunInBase (Eff (LogWriterReader h ': r)) m -> m a) -> Eff (LogWriterReader h ': r) a #

restoreM :: StM (Eff (LogWriterReader h ': r)) a -> Eff (LogWriterReader h ': r) a #

(LiftedBase m e, MonadThrow (Eff e)) => MonadThrow (Eff (LogWriterReader h ': e)) Source # 
Instance details

Defined in Control.Eff.Log.Writer

Methods

throwM :: Exception e0 => e0 -> Eff (LogWriterReader h ': e) a #

(Applicative m, LiftedBase m e, MonadCatch (Eff e)) => MonadCatch (Eff (LogWriterReader h ': e)) Source # 
Instance details

Defined in Control.Eff.Log.Writer

Methods

catch :: Exception e0 => Eff (LogWriterReader h ': e) a -> (e0 -> Eff (LogWriterReader h ': e) a) -> Eff (LogWriterReader h ': e) a #

(Applicative m, LiftedBase m e, MonadMask (Eff e)) => MonadMask (Eff (LogWriterReader h ': e)) Source # 
Instance details

Defined in Control.Eff.Log.Writer

Methods

mask :: ((forall a. Eff (LogWriterReader h ': e) a -> Eff (LogWriterReader h ': e) a) -> Eff (LogWriterReader h ': e) b) -> Eff (LogWriterReader h ': e) b #

uninterruptibleMask :: ((forall a. Eff (LogWriterReader h ': e) a -> Eff (LogWriterReader h ': e) a) -> Eff (LogWriterReader h ': e) b) -> Eff (LogWriterReader h ': e) b #

generalBracket :: Eff (LogWriterReader h ': e) a -> (a -> ExitCase b -> Eff (LogWriterReader h ': e) c) -> (a -> Eff (LogWriterReader h ': e) b) -> Eff (LogWriterReader h ': e) (b, c) #

Handle (LogWriterReader h) e a (LogWriter h -> k) Source # 
Instance details

Defined in Control.Eff.Log.Writer

Methods

handle :: (Eff e a -> LogWriter h -> k) -> Arrs e v a -> LogWriterReader h v -> LogWriter h -> k #

handle_relay :: (e ~ (LogWriterReader h ': r'), Relay (LogWriter h -> k) r') => (a -> LogWriter h -> k) -> (Eff e a -> LogWriter h -> k) -> Eff e a -> LogWriter h -> k #

respond_relay :: (a -> LogWriter h -> k) -> (Eff e a -> LogWriter h -> k) -> Eff e a -> LogWriter h -> k #

type StM (Eff (LogWriterReader h ': r)) a Source # 
Instance details

Defined in Control.Eff.Log.Writer

type StM (Eff (LogWriterReader h ': r)) a = StM (Eff r) a

newtype LogWriter writerM Source #

A function that takes a log message and returns an effect that logs the message.

Constructors

MkLogWriter 

Fields

Instances
Applicative w => Default (LogWriter w) Source # 
Instance details

Defined in Control.Eff.Log.Writer

Methods

def :: LogWriter w #

Handle (LogWriterReader h) e a (LogWriter h -> k) Source # 
Instance details

Defined in Control.Eff.Log.Writer

Methods

handle :: (Eff e a -> LogWriter h -> k) -> Arrs e v a -> LogWriterReader h v -> LogWriter h -> k #

handle_relay :: (e ~ (LogWriterReader h ': r'), Relay (LogWriter h -> k) r') => (a -> LogWriter h -> k) -> (Eff e a -> LogWriter h -> k) -> Eff e a -> LogWriter h -> k #

respond_relay :: (a -> LogWriter h -> k) -> (Eff e a -> LogWriter h -> k) -> Eff e a -> LogWriter h -> k #

runLogWriterReader :: LogWriter h -> Eff (LogWriterReader h ': e) a -> Eff e a Source #

Provide the LogWriter

Exposed for custom extensions, if in doubt use withLogging.

localLogWriterReader :: forall h e a. SetMember LogWriterReader (LogWriterReader h) e => (LogWriter h -> LogWriter h) -> Eff e a -> Eff e a Source #

Modify the current LogWriter.

noOpLogWriter :: Applicative m => LogWriter m Source #

This LogWriter will discard all messages.

NOTE: This is just an alias for def

filteringLogWriter :: Monad e => LogPredicate -> LogWriter e -> LogWriter e Source #

A LogWriter that applies a predicate to the LogMessage and delegates to to the given writer of the predicate is satisfied.

mappingLogWriter :: (LogMessage -> LogMessage) -> LogWriter e -> LogWriter e Source #

A LogWriter that applies a function to the LogMessage and delegates the result to to the given writer.

mappingLogWriterM :: Monad e => (LogMessage -> e LogMessage) -> LogWriter e -> LogWriter e Source #

Like mappingLogWriter allow the function that changes the LogMessage to have effects.

type LogIo e = (LogsTo IO e, Lifted IO e) Source #

A constraint that required LogsTo IO e and Lifted IO e.

Since: 0.24.0

type LogsTo h e = (Member Logs e, HandleLogWriter h e, SetMember LogWriterReader (LogWriterReader h) e) Source #

A constraint alias for effects that requires a LogWriterReader, as well as that the contained LogWriterReader has a HandleLogWriter instance.

The requirements of this constraint are provided by:

data Logs v Source #

This effect sends LogMessages and is a reader for a LogPredicate.

Logs are sent via logMsg; for more information about log predicates, see Control.Eff.Log

This effect is handled via withLogging.

Instances
Handle Logs e a (LogPredicate -> k) Source # 
Instance details

Defined in Control.Eff.Log.Handler

Methods

handle :: (Eff e a -> LogPredicate -> k) -> Arrs e v a -> Logs v -> LogPredicate -> k #

handle_relay :: (e ~ (Logs ': r'), Relay (LogPredicate -> k) r') => (a -> LogPredicate -> k) -> (Eff e a -> LogPredicate -> k) -> Eff e a -> LogPredicate -> k #

respond_relay :: (a -> LogPredicate -> k) -> (Eff e a -> LogPredicate -> k) -> Eff e a -> LogPredicate -> k #

(MonadBase m m, LiftedBase m e, LogsTo m (Logs ': e)) => MonadBaseControl m (Eff (Logs ': e)) Source #

This instance allows lifting the Logs effect into a base monad, e.g. IO. This instance needs a LogWriterReader in the base monad, that is capable to handle logMsg invocations.

Instance details

Defined in Control.Eff.Log.Handler

Associated Types

type StM (Eff (Logs ': e)) a :: Type #

Methods

liftBaseWith :: (RunInBase (Eff (Logs ': e)) m -> m a) -> Eff (Logs ': e) a #

restoreM :: StM (Eff (Logs ': e)) a -> Eff (Logs ': e) a #

(LiftedBase m e, MonadThrow (Eff e)) => MonadThrow (Eff (Logs ': e)) Source # 
Instance details

Defined in Control.Eff.Log.Handler

Methods

throwM :: Exception e0 => e0 -> Eff (Logs ': e) a #

(Applicative m, LiftedBase m e, MonadCatch (Eff e), LogsTo m (Logs ': e)) => MonadCatch (Eff (Logs ': e)) Source # 
Instance details

Defined in Control.Eff.Log.Handler

Methods

catch :: Exception e0 => Eff (Logs ': e) a -> (e0 -> Eff (Logs ': e) a) -> Eff (Logs ': e) a #

(Applicative m, LiftedBase m e, MonadMask (Eff e), LogsTo m (Logs ': e)) => MonadMask (Eff (Logs ': e)) Source # 
Instance details

Defined in Control.Eff.Log.Handler

Methods

mask :: ((forall a. Eff (Logs ': e) a -> Eff (Logs ': e) a) -> Eff (Logs ': e) b) -> Eff (Logs ': e) b #

uninterruptibleMask :: ((forall a. Eff (Logs ': e) a -> Eff (Logs ': e) a) -> Eff (Logs ': e) b) -> Eff (Logs ': e) b #

generalBracket :: Eff (Logs ': e) a -> (a -> ExitCase b -> Eff (Logs ': e) c) -> (a -> Eff (Logs ': e) b) -> Eff (Logs ': e) (b, c) #

type StM (Eff (Logs ': e)) a Source # 
Instance details

Defined in Control.Eff.Log.Handler

type StM (Eff (Logs ': e)) a = StM (Eff e) a

withLogging :: forall h e a. (Applicative h, LogsTo h (Logs ': (LogWriterReader h ': e))) => LogWriter h -> Eff (Logs ': (LogWriterReader h ': e)) a -> Eff e a Source #

Handle the Logs and LogWriterReader effects.

It installs the given LogWriter, which determines the underlying LogWriter type parameter.

Example:

exampleWithLogging :: IO ()
exampleWithLogging =
    runLift
  $ withLogging consoleLogWriter
  $ logDebug "Oh, hi there"

withSomeLogging :: forall h e a. (Applicative h, LogsTo h (Logs ': (LogWriterReader h ': e))) => Eff (Logs ': (LogWriterReader h ': e)) a -> Eff e a Source #

Handles the Logs and LogWriterReader effects.

By default it uses the noOpLogWriter, but using setLogWriter the LogWriter can be replaced.

This is like withLogging applied to noOpLogWriter

Example:

exampleWithSomeLogging :: ()
exampleWithSomeLogging =
    run
  $ withSomeLogging @PureLogWriter
  $ logDebug "Oh, hi there"

runLogs :: forall h e b. LogsTo h (Logs ': e) => LogPredicate -> Eff (Logs ': e) b -> Eff e b Source #

Raw handling of the Logs effect. Exposed for custom extensions, if in doubt use withLogging.

logMsg :: forall e. (HasCallStack, Member Logs e) => LogMessage -> Eff e () Source #

Log a message.

All logging goes through this function.

This function is the only place where the LogPredicate is applied.

Also, LogMessages are evaluated using deepseq, after they pass the LogPredicate.

logWithSeverity :: forall e. (HasCallStack, Member Logs e) => Severity -> Text -> Eff e () Source #

Log a Text as LogMessage with a given Severity.

logWithSeverity' :: forall e. (HasCallStack, Member Logs e) => Severity -> String -> Eff e () Source #

Log a Text as LogMessage with a given Severity.

logAlert :: forall e. (HasCallStack, Member Logs e) => Text -> Eff e () Source #

Log a message with alertSeverity.

logCritical :: forall e. (HasCallStack, Member Logs e) => Text -> Eff e () Source #

Log a criticalSeverity message.

logError :: forall e. (HasCallStack, Member Logs e) => Text -> Eff e () Source #

Log a errorSeverity message.

logWarning :: forall e. (HasCallStack, Member Logs e) => Text -> Eff e () Source #

Log a warningSeverity message.

logNotice :: forall e. (HasCallStack, Member Logs e) => Text -> Eff e () Source #

Log a noticeSeverity message.

logInfo :: forall e. (HasCallStack, Member Logs e) => Text -> Eff e () Source #

Log a informationalSeverity message.

logDebug :: forall e. (HasCallStack, Member Logs e) => Text -> Eff e () Source #

Log a debugSeverity message.

logAlert' :: forall e. (HasCallStack, Member Logs e) => String -> Eff e () Source #

Log a message with alertSeverity.

logCritical' :: forall e. (HasCallStack, Member Logs e) => String -> Eff e () Source #

Log a criticalSeverity message.

logError' :: forall e. (HasCallStack, Member Logs e) => String -> Eff e () Source #

Log a errorSeverity message.

logWarning' :: forall e. (HasCallStack, Member Logs e) => String -> Eff e () Source #

Log a warningSeverity message.

logNotice' :: forall e. (HasCallStack, Member Logs e) => String -> Eff e () Source #

Log a noticeSeverity message.

logInfo' :: forall e. (HasCallStack, Member Logs e) => String -> Eff e () Source #

Log a informationalSeverity message.

logDebug' :: forall e. (HasCallStack, Member Logs e) => String -> Eff e () Source #

Log a debugSeverity message.

askLogPredicate :: forall e. Member Logs e => Eff e LogPredicate Source #

Get the current Logs filter/transformer function.

See Control.Eff.Log

setLogPredicate :: forall r b. (Member Logs r, HasCallStack) => LogPredicate -> Eff r b -> Eff r b Source #

Keep only those messages, for which a predicate holds.

E.g. to keep only messages which begin with OMG:

exampleLogPredicate :: IO Int
exampleLogPredicate =
    runLift
  $ withLogging consoleLogWriter
  $ do logMsg "test"
       setLogPredicate (\ msg -> case view lmMessage msg of
                                  'O':'M':'G':_ -> True
                                  _             -> False)
                         (do logMsg "this message will not be logged"
                             logMsg "OMG logged"
                             return 42)

In order to also delegate to the previous predicate, use modifyLogPredicate

See Control.Eff.Log

modifyLogPredicate :: forall e b. (Member Logs e, HasCallStack) => (LogPredicate -> LogPredicate) -> Eff e b -> Eff e b Source #

Change the LogPredicate.

Other than setLogPredicate this function allows to include the previous predicate, too.

For to discard all messages currently no satisfying the predicate and also all messages that are to long:

modifyLogPredicate (previousPredicate msg -> previousPredicate msg && length (lmMessage msg) < 29 )
                   (do logMsg "this message will not be logged"
                       logMsg "this message might be logged")

See Control.Eff.Log

includeLogMessages :: forall e a. Member Logs e => LogPredicate -> Eff e a -> Eff e a Source #

Include LogMessages that match a LogPredicate.

excludeLogMessages p allows log message to be logged if p m

Although it is enough if the previous predicate holds. See excludeLogMessages and modifyLogPredicate.

See Control.Eff.Log

excludeLogMessages :: forall e a. Member Logs e => LogPredicate -> Eff e a -> Eff e a Source #

Exclude LogMessages that match a LogPredicate.

excludeLogMessages p discards logs if p m

Also the previous predicate must also hold for a message to be logged. See excludeLogMessages and modifyLogPredicate.

See Control.Eff.Log

respondToLogMessage :: forall r b. Member Logs r => (LogMessage -> Eff r ()) -> Eff r b -> Eff r b Source #

Consume log messages.

Exposed for custom extensions, if in doubt use withLogging.

Respond to all LogMessages logged from the given action, up to any MonadBaseControl liftings.

Note that all logging is done through logMsg and that means only messages passing the LogPredicate are received.

The LogMessages are consumed once they are passed to the given callback function, previous respondToLogMessage invocations further up in the call stack will not get the messages anymore.

Use interceptLogMessages if the messages shall be passed any previous handler.

NOTE: The effects of this function are lost when using MonadBaseControl, MonadMask, MonadCatch and MonadThrow.

In contrast the functions based on modifying the LogWriter, such as addLogWriter or censorLogs, are save to use in combination with the aforementioned liftings.

interceptLogMessages :: forall r b. Member Logs r => (LogMessage -> Eff r LogMessage) -> Eff r b -> Eff r b Source #

Change the LogMessages using an effectful function.

Exposed for custom extensions, if in doubt use withLogging.

This differs from respondToLogMessage in that the intercepted messages will be written either way, albeit in altered form.

NOTE: The effects of this function are lost when using MonadBaseControl, MonadMask, MonadCatch and MonadThrow.

In contrast the functions based on modifying the LogWriter, such as addLogWriter or censorLogs, are save to use in combination with the aforementioned liftings.

modifyLogWriter :: forall h e a. LogsTo h e => (LogWriter h -> LogWriter h) -> Eff e a -> Eff e a Source #

Change the current LogWriter.

setLogWriter :: forall h e a. LogsTo h e => LogWriter h -> Eff e a -> Eff e a Source #

Replace the current LogWriter. To add an additional log message consumer use addLogWriter

censorLogs :: LogsTo h e => (LogMessage -> LogMessage) -> Eff e a -> Eff e a Source #

Modify the the LogMessages written in the given sub-expression.

Note: This is equivalent to modifyLogWriter . mappingLogWriter

censorLogsM :: (LogsTo h e, Monad h) => (LogMessage -> h LogMessage) -> Eff e a -> Eff e a Source #

Modify the the LogMessages written in the given sub-expression, as in censorLogs but with a effectful function.

Note: This is equivalent to modifyLogWriter . mappingLogWriterM

addLogWriter :: forall h e a. (HasCallStack, LogsTo h e, Monad h) => LogWriter h -> Eff e a -> Eff e a Source #

Combine the effects of a given LogWriter and the existing one.

import Data.Text    as T
import Data.Text.IO as T

exampleAddLogWriter :: IO ()
exampleAddLogWriter = go >>= T.putStrLn
 where go = fmap (unlines . map renderLogMessageConsoleLog . snd)
              $  runLift
              $  runCaptureLogWriter
              $  withLogging captureLogWriter
              $  addLogWriter (mappingLogWriter (lmMessage %~ ("CAPTURED "++)) captureLogWriter)
              $  addLogWriter (filteringLogWriter severeMessages (mappingLogWriter (lmMessage %~ ("TRACED "++)) debugTraceLogWriter))
              $  do
                    logEmergency "test emergencySeverity 1"
                    logCritical "test criticalSeverity 2"
                    logAlert "test alertSeverity 3"
                    logError "test errorSeverity 4"
                    logWarning "test warningSeverity 5"
                    logInfo "test informationalSeverity 6"
                    logDebug "test debugSeverity 7"
       severeMessages = view (lmSeverity . to (<= errorSeverity))

newtype ProcessId Source #

Each process is identified by a single process id, that stays constant throughout the life cycle of a process. Also, message sending relies on these values to address messages to processes.

Constructors

ProcessId 

Fields

Instances
Bounded ProcessId Source # 
Instance details

Defined in Control.Eff.Concurrent.Process

Enum ProcessId Source # 
Instance details

Defined in Control.Eff.Concurrent.Process

Eq ProcessId Source # 
Instance details

Defined in Control.Eff.Concurrent.Process

Integral ProcessId Source # 
Instance details

Defined in Control.Eff.Concurrent.Process

Num ProcessId Source # 
Instance details

Defined in Control.Eff.Concurrent.Process

Ord ProcessId Source # 
Instance details

Defined in Control.Eff.Concurrent.Process

Read ProcessId Source # 
Instance details

Defined in Control.Eff.Concurrent.Process

Real ProcessId Source # 
Instance details

Defined in Control.Eff.Concurrent.Process

Show ProcessId Source # 
Instance details

Defined in Control.Eff.Concurrent.Process

NFData ProcessId Source # 
Instance details

Defined in Control.Eff.Concurrent.Process

Methods

rnf :: ProcessId -> () #

data ProcessDown Source #

A monitored process exited. This message is sent to a process by the scheduler, when a process that was monitored died.

Since: 0.12.0

Instances
Eq ProcessDown Source # 
Instance details

Defined in Control.Eff.Concurrent.Process

Ord ProcessDown Source # 
Instance details

Defined in Control.Eff.Concurrent.Process

Show ProcessDown Source # 
Instance details

Defined in Control.Eff.Concurrent.Process

Generic ProcessDown Source # 
Instance details

Defined in Control.Eff.Concurrent.Process

Associated Types

type Rep ProcessDown :: Type -> Type #

NFData ProcessDown Source # 
Instance details

Defined in Control.Eff.Concurrent.Process

Methods

rnf :: ProcessDown -> () #

type Rep ProcessDown Source # 
Instance details

Defined in Control.Eff.Concurrent.Process

type Rep ProcessDown = D1 (MetaData "ProcessDown" "Control.Eff.Concurrent.Process" "extensible-effects-concurrent-0.26.1-H4MbFpru2ZADB31xfNLjdz" False) (C1 (MetaCons "ProcessDown" PrefixI True) (S1 (MetaSel (Just "downReference") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 MonitorReference) :*: S1 (MetaSel (Just "downReason") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 SomeExitReason)))

data MonitorReference Source #

A value that contains a unique reference of a process monitoring.

Since: 0.12.0

Instances
Eq MonitorReference Source # 
Instance details

Defined in Control.Eff.Concurrent.Process

Ord MonitorReference Source # 
Instance details

Defined in Control.Eff.Concurrent.Process

Read MonitorReference Source # 
Instance details

Defined in Control.Eff.Concurrent.Process

Show MonitorReference Source # 
Instance details

Defined in Control.Eff.Concurrent.Process

Generic MonitorReference Source # 
Instance details

Defined in Control.Eff.Concurrent.Process

Associated Types

type Rep MonitorReference :: Type -> Type #

NFData MonitorReference Source # 
Instance details

Defined in Control.Eff.Concurrent.Process

Methods

rnf :: MonitorReference -> () #

type Rep MonitorReference Source # 
Instance details

Defined in Control.Eff.Concurrent.Process

type Rep MonitorReference = D1 (MetaData "MonitorReference" "Control.Eff.Concurrent.Process" "extensible-effects-concurrent-0.26.1-H4MbFpru2ZADB31xfNLjdz" False) (C1 (MetaCons "MonitorReference" PrefixI True) (S1 (MetaSel (Just "monitorIndex") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Int) :*: S1 (MetaSel (Just "monitoredProcess") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 ProcessId)))

type SafeProcesses r = Process r ': r Source #

Cons Process onto a list of effects. This is called SafeProcesses because the the actions cannot be interrupted in.

type Processes e = Interrupts ': SafeProcesses e Source #

This adds a layer of the Interrupts effect on top of Processes

data Interrupt (t :: ExitRecovery) where Source #

A sum-type with reasons for why a process operation, such as receiving messages, is interrupted in the scheduling loop.

This includes errors, that can occur when scheduling messages.

Since: 0.23.0

Constructors

NormalExitRequested :: Interrupt Recoverable

A process has finished a unit of work and might exit or work on something else. This is primarily used for interrupting infinite server loops, allowing for additional cleanup work before exiting (e.g. with ExitNormally)

Since: 0.13.2

OtherProcessNotRunning :: ProcessId -> Interrupt Recoverable

A process that should be running was not running.

TimeoutInterrupt :: String -> Interrupt Recoverable

A Recoverable timeout has occurred.

LinkedProcessCrashed :: ProcessId -> Interrupt Recoverable

A linked process is down

ErrorInterrupt :: String -> Interrupt Recoverable

An exit reason that has an error message and is Recoverable.

ExitNormally :: Interrupt NoRecovery

A process function returned or exited without any error.

ExitUnhandledError :: Text -> Interrupt NoRecovery

An error causes the process to exit immediately. For example an unexpected runtime exception was thrown, i.e. an exception derived from SomeException Or a Recoverable Interrupt was not recovered.

ExitProcessCancelled :: Interrupt NoRecovery

A process shall exit immediately, without any cleanup was cancelled (e.g. killed, in cancel)

Instances
Eq (Interrupt x) Source # 
Instance details

Defined in Control.Eff.Concurrent.Process

Methods

(==) :: Interrupt x -> Interrupt x -> Bool #

(/=) :: Interrupt x -> Interrupt x -> Bool #

Ord (Interrupt x) Source # 
Instance details

Defined in Control.Eff.Concurrent.Process

Show (Interrupt x) Source # 
Instance details

Defined in Control.Eff.Concurrent.Process

Exception (Interrupt Recoverable) Source # 
Instance details

Defined in Control.Eff.Concurrent.Process

Exception (Interrupt NoRecovery) Source # 
Instance details

Defined in Control.Eff.Concurrent.Process

NFData (Interrupt x) Source # 
Instance details

Defined in Control.Eff.Concurrent.Process

Methods

rnf :: Interrupt x -> () #

(LogIo q, TangibleSup p, Tangible (ChildId p), Server p (Processes q)) => Server (Sup p) (Processes q) Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol.Supervisor

Associated Types

data StartArgument (Sup p) (Processes q) :: Type Source #

type Protocol (Sup p) :: Type Source #

type Model (Sup p) :: Type Source #

type Settings (Sup p) :: Type Source #

(TangibleObserver o, IsPdu (Observer o) Asynchronous, Lifted IO q, Member Logs q) => Server (ObservationQueue o) (Processes q) Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol.Observer.Queue

Typeable tag => Show (Init (GenServer tag eLoop e) (Processes e)) Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol.EffectfulServer

Methods

showsPrec :: Int -> Init (GenServer tag eLoop e) (Processes e) -> ShowS #

show :: Init (GenServer tag eLoop e) (Processes e) -> String #

showList :: [Init (GenServer tag eLoop e) (Processes e)] -> ShowS #

NFData (Init (GenServer tag eLoop e) (Processes e)) Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol.EffectfulServer

Methods

rnf :: Init (GenServer tag eLoop e) (Processes e) -> () #

TangibleGenServer tag eLoop e => Server (GenServer tag eLoop e) (Processes e) Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol.EffectfulServer

Associated Types

data Init (GenServer tag eLoop e) (Processes e) :: Type Source #

type ServerPdu (GenServer tag eLoop e) :: Type Source #

type ServerEffects (GenServer tag eLoop e) (Processes e) :: [Type -> Type] Source #

Methods

serverTitle :: Init (GenServer tag eLoop e) (Processes e) -> ProcessTitle Source #

runEffects :: Init (GenServer tag eLoop e) (Processes e) -> Eff (ServerEffects (GenServer tag eLoop e) (Processes e)) x -> Eff (Processes e) x Source #

onEvent :: Init (GenServer tag eLoop e) (Processes e) -> Event (ServerPdu (GenServer tag eLoop e)) -> Eff (ServerEffects (GenServer tag eLoop e) (Processes e)) () Source #

data StartArgument (Sup p) (Processes q) Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol.Supervisor

data StartArgument (ObservationQueue o) (Processes q) Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol.Observer.Queue

data Init (GenServer tag eLoop e) (Processes e) Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol.EffectfulServer

type ServerEffects (GenServer tag eLoop e) (Processes e) Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol.EffectfulServer

type ServerEffects (GenServer tag eLoop e) (Processes e) = eLoop

data ExitSeverity Source #

This value indicates whether a process exited in way consistent with the planned behaviour or not.

Constructors

NormalExit 
Crash 
Instances
Eq ExitSeverity Source # 
Instance details

Defined in Control.Eff.Concurrent.Process

Ord ExitSeverity Source # 
Instance details

Defined in Control.Eff.Concurrent.Process

Show ExitSeverity Source # 
Instance details

Defined in Control.Eff.Concurrent.Process

Generic ExitSeverity Source # 
Instance details

Defined in Control.Eff.Concurrent.Process

Associated Types

type Rep ExitSeverity :: Type -> Type #

NFData ExitSeverity Source # 
Instance details

Defined in Control.Eff.Concurrent.Process

Methods

rnf :: ExitSeverity -> () #

type Rep ExitSeverity Source # 
Instance details

Defined in Control.Eff.Concurrent.Process

type Rep ExitSeverity = D1 (MetaData "ExitSeverity" "Control.Eff.Concurrent.Process" "extensible-effects-concurrent-0.26.1-H4MbFpru2ZADB31xfNLjdz" False) (C1 (MetaCons "NormalExit" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "Crash" PrefixI False) (U1 :: Type -> Type))

data ExitRecovery Source #

This kind is used to indicate if a Interrupt can be treated like a short interrupt which can be handled or ignored.

Constructors

Recoverable 
NoRecovery 
Instances
Eq ExitRecovery Source # 
Instance details

Defined in Control.Eff.Concurrent.Process

Ord ExitRecovery Source # 
Instance details

Defined in Control.Eff.Concurrent.Process

Show ExitRecovery Source # 
Instance details

Defined in Control.Eff.Concurrent.Process

Generic ExitRecovery Source # 
Instance details

Defined in Control.Eff.Concurrent.Process

Associated Types

type Rep ExitRecovery :: Type -> Type #

NFData ExitRecovery Source # 
Instance details

Defined in Control.Eff.Concurrent.Process

Methods

rnf :: ExitRecovery -> () #

type Rep ExitRecovery Source # 
Instance details

Defined in Control.Eff.Concurrent.Process

type Rep ExitRecovery = D1 (MetaData "ExitRecovery" "Control.Eff.Concurrent.Process" "extensible-effects-concurrent-0.26.1-H4MbFpru2ZADB31xfNLjdz" False) (C1 (MetaCons "Recoverable" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "NoRecovery" PrefixI False) (U1 :: Type -> Type))

data ProcessState Source #

The state that a Process is currently in.

Constructors

ProcessBooting

The process has just been started but not scheduled yet.

ProcessIdle

The process yielded it's time slice

ProcessBusy

The process is busy with non-blocking

ProcessBusyUpdatingDetails

The process is busy with UpdateProcessDetails

ProcessBusySending

The process is busy with sending a message

ProcessBusySendingShutdown

The process is busy with killing

ProcessBusySendingInterrupt

The process is busy with killing

ProcessBusyReceiving

The process blocked by a receiveAnyMessage

ProcessBusyLinking

The process blocked by a linkProcess

ProcessBusyUnlinking

The process blocked by a unlinkProcess

ProcessBusyMonitoring

The process blocked by a monitor

ProcessBusyDemonitoring

The process blocked by a demonitor

ProcessInterrupted

The process was interrupted

ProcessShuttingDown

The process was shutdown or crashed

Instances
Enum ProcessState Source # 
Instance details

Defined in Control.Eff.Concurrent.Process

Eq ProcessState Source # 
Instance details

Defined in Control.Eff.Concurrent.Process

Ord ProcessState Source # 
Instance details

Defined in Control.Eff.Concurrent.Process

Read ProcessState Source # 
Instance details

Defined in Control.Eff.Concurrent.Process

Show ProcessState Source # 
Instance details

Defined in Control.Eff.Concurrent.Process

Generic ProcessState Source # 
Instance details

Defined in Control.Eff.Concurrent.Process

Associated Types

type Rep ProcessState :: Type -> Type #

Default ProcessState Source # 
Instance details

Defined in Control.Eff.Concurrent.Process

Methods

def :: ProcessState #

NFData ProcessState Source # 
Instance details

Defined in Control.Eff.Concurrent.Process

Methods

rnf :: ProcessState -> () #

type Rep ProcessState Source # 
Instance details

Defined in Control.Eff.Concurrent.Process

type Rep ProcessState = D1 (MetaData "ProcessState" "Control.Eff.Concurrent.Process" "extensible-effects-concurrent-0.26.1-H4MbFpru2ZADB31xfNLjdz" False) (((C1 (MetaCons "ProcessBooting" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "ProcessIdle" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "ProcessBusy" PrefixI False) (U1 :: Type -> Type))) :+: ((C1 (MetaCons "ProcessBusyUpdatingDetails" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "ProcessBusySending" PrefixI False) (U1 :: Type -> Type)) :+: (C1 (MetaCons "ProcessBusySendingShutdown" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "ProcessBusySendingInterrupt" PrefixI False) (U1 :: Type -> Type)))) :+: ((C1 (MetaCons "ProcessBusyReceiving" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "ProcessBusyLinking" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "ProcessBusyUnlinking" PrefixI False) (U1 :: Type -> Type))) :+: ((C1 (MetaCons "ProcessBusyMonitoring" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "ProcessBusyDemonitoring" PrefixI False) (U1 :: Type -> Type)) :+: (C1 (MetaCons "ProcessInterrupted" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "ProcessShuttingDown" PrefixI False) (U1 :: Type -> Type)))))

data MessageSelector a Source #

A function that decided if the next message will be received by ReceiveSelectedMessage. It conveniently is an instance of Alternative so the message selector can be combined: > > selectInt :: MessageSelector Int > selectInt = selectMessage > > selectString :: MessageSelector String > selectString = selectMessage > > selectIntOrString :: MessageSelector (Either Int String) > selectIntOrString = > Left $ selectTimeout| Right $ selectString

Instances
Functor MessageSelector Source # 
Instance details

Defined in Control.Eff.Concurrent.Process

Methods

fmap :: (a -> b) -> MessageSelector a -> MessageSelector b #

(<$) :: a -> MessageSelector b -> MessageSelector a #

Applicative MessageSelector Source # 
Instance details

Defined in Control.Eff.Concurrent.Process

Alternative MessageSelector Source # 
Instance details

Defined in Control.Eff.Concurrent.Process

Semigroup a => Semigroup (MessageSelector a) Source # 
Instance details

Defined in Control.Eff.Concurrent.Process

Semigroup a => Monoid (MessageSelector a) Source # 
Instance details

Defined in Control.Eff.Concurrent.Process

data ResumeProcess v where Source #

Every Process action returns it's actual result wrapped in this type. It will allow to signal errors as well as pass on normal results such as incoming messages.

Constructors

Interrupted :: Interrupt Recoverable -> ResumeProcess v

The current operation of the process was interrupted with a Interrupt. If isRecoverable holds for the given reason, the process may choose to continue.

ResumeWith :: a -> ResumeProcess a

The process may resume to do work, using the given result.

Instances
NFData1 ResumeProcess Source # 
Instance details

Defined in Control.Eff.Concurrent.Process

Methods

liftRnf :: (a -> ()) -> ResumeProcess a -> () #

Show v => Show (ResumeProcess v) Source # 
Instance details

Defined in Control.Eff.Concurrent.Process

Generic (ResumeProcess v) Source # 
Instance details

Defined in Control.Eff.Concurrent.Process

Associated Types

type Rep (ResumeProcess v) :: Type -> Type #

NFData a => NFData (ResumeProcess a) Source # 
Instance details

Defined in Control.Eff.Concurrent.Process

Methods

rnf :: ResumeProcess a -> () #

Generic1 ResumeProcess Source # 
Instance details

Defined in Control.Eff.Concurrent.Process

Associated Types

type Rep1 ResumeProcess :: k -> Type #

type Rep (ResumeProcess v) Source # 
Instance details

Defined in Control.Eff.Concurrent.Process

type Rep (ResumeProcess v) = D1 (MetaData "ResumeProcess" "Control.Eff.Concurrent.Process" "extensible-effects-concurrent-0.26.1-H4MbFpru2ZADB31xfNLjdz" False) (C1 (MetaCons "Interrupted" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Interrupt Recoverable))) :+: C1 (MetaCons "ResumeWith" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 v)))
type Rep1 ResumeProcess Source # 
Instance details

Defined in Control.Eff.Concurrent.Process

type Rep1 ResumeProcess = D1 (MetaData "ResumeProcess" "Control.Eff.Concurrent.Process" "extensible-effects-concurrent-0.26.1-H4MbFpru2ZADB31xfNLjdz" False) (C1 (MetaCons "Interrupted" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Interrupt Recoverable))) :+: C1 (MetaCons "ResumeWith" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) Par1))

newtype Serializer message Source #

Serialize a message into a StrictDynamic value to be sent via sendAnyMessage.

This indirection allows, among other things, the composition of Servers.

Since: 0.24.1

Constructors

MkSerializer 

Fields

Instances
Contravariant Serializer Source # 
Instance details

Defined in Control.Eff.Concurrent.Process

Methods

contramap :: (a -> b) -> Serializer b -> Serializer a #

(>$) :: b -> Serializer b -> Serializer a #

data StrictDynamic Source #

Data flows between Processes via these messages.

This is just a newtype wrapper around Dynamic. The reason this type exists is to force construction through the code in this module, which always evaluates a message to normal form before sending it to another process.

Since: 0.22.0

newtype ProcessDetails Source #

A multi-line text describing the current state of a process for debugging purposes.

Since: 0.24.1

Constructors

MkProcessDetails 
Instances
Eq ProcessDetails Source # 
Instance details

Defined in Control.Eff.Concurrent.Process

Ord ProcessDetails Source # 
Instance details

Defined in Control.Eff.Concurrent.Process

Show ProcessDetails Source # 
Instance details

Defined in Control.Eff.Concurrent.Process

IsString ProcessDetails Source # 
Instance details

Defined in Control.Eff.Concurrent.Process

Generic ProcessDetails Source # 
Instance details

Defined in Control.Eff.Concurrent.Process

Associated Types

type Rep ProcessDetails :: Type -> Type #

Semigroup ProcessDetails Source # 
Instance details

Defined in Control.Eff.Concurrent.Process

Monoid ProcessDetails Source # 
Instance details

Defined in Control.Eff.Concurrent.Process

NFData ProcessDetails Source # 
Instance details

Defined in Control.Eff.Concurrent.Process

Methods

rnf :: ProcessDetails -> () #

type Rep ProcessDetails Source # 
Instance details

Defined in Control.Eff.Concurrent.Process

type Rep ProcessDetails = D1 (MetaData "ProcessDetails" "Control.Eff.Concurrent.Process" "extensible-effects-concurrent-0.26.1-H4MbFpru2ZADB31xfNLjdz" True) (C1 (MetaCons "MkProcessDetails" PrefixI True) (S1 (MetaSel (Just "_fromProcessDetails") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Text)))

newtype ProcessTitle Source #

A short title for a Process for logging purposes.

Since: 0.24.1

Constructors

MkProcessTitle 
Instances
Eq ProcessTitle Source # 
Instance details

Defined in Control.Eff.Concurrent.Process

Ord ProcessTitle Source # 
Instance details

Defined in Control.Eff.Concurrent.Process

Show ProcessTitle Source # 
Instance details

Defined in Control.Eff.Concurrent.Process

IsString ProcessTitle Source # 
Instance details

Defined in Control.Eff.Concurrent.Process

Generic ProcessTitle Source # 
Instance details

Defined in Control.Eff.Concurrent.Process

Associated Types

type Rep ProcessTitle :: Type -> Type #

Semigroup ProcessTitle Source # 
Instance details

Defined in Control.Eff.Concurrent.Process

Monoid ProcessTitle Source # 
Instance details

Defined in Control.Eff.Concurrent.Process

NFData ProcessTitle Source # 
Instance details

Defined in Control.Eff.Concurrent.Process

Methods

rnf :: ProcessTitle -> () #

type Rep ProcessTitle Source # 
Instance details

Defined in Control.Eff.Concurrent.Process

type Rep ProcessTitle = D1 (MetaData "ProcessTitle" "Control.Eff.Concurrent.Process" "extensible-effects-concurrent-0.26.1-H4MbFpru2ZADB31xfNLjdz" True) (C1 (MetaCons "MkProcessTitle" PrefixI True) (S1 (MetaSel (Just "_fromProcessTitle") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Text)))

data Process (r :: [Type -> Type]) b where Source #

The process effect is the basis for message passing concurrency. This effect describes an interface for concurrent, communicating isolated processes identified uniquely by a process-id.

Processes can raise exceptions that can be caught, exit gracefully or with an error, or be killed by other processes, with the option of ignoring the shutdown request.

Process Scheduling is implemented in different modules. All scheduler implementations should follow some basic rules:

  • fair scheduling
  • sending a message does not block
  • receiving a message does block
  • spawning a child blocks only a very moment
  • a newly spawned process shall be scheduled before the parent process after
  • the spawnRaw
  • when the first process exists, all process should be killed immediately

Constructors

FlushMessages :: Process r (ResumeProcess [StrictDynamic])

Remove all messages from the process' message queue

YieldProcess :: Process r (ResumeProcess ())

In cooperative schedulers, this will give processing time to the scheduler. Every other operation implicitly serves the same purpose.

Since: 0.12.0

SelfPid :: Process r (ResumeProcess ProcessId)

Return the current ProcessId

Spawn :: ProcessTitle -> Eff (Process r ': r) () -> Process r (ResumeProcess ProcessId)

Start a new process, the new process will execute an effect, the function will return immediately with a ProcessId.

SpawnLink :: ProcessTitle -> Eff (Process r ': r) () -> Process r (ResumeProcess ProcessId)

Start a new process, and Link to it .

Since: 0.12.0

Shutdown :: Interrupt NoRecovery -> Process r a

Shutdown the process; irregardless of the exit reason, this function never returns,

SendShutdown :: ProcessId -> Interrupt NoRecovery -> Process r (ResumeProcess ())

Shutdown another process immediately, the other process has no way of handling this!

SendInterrupt :: ProcessId -> Interrupt Recoverable -> Process r (ResumeProcess ())

Request that another a process interrupts. The targeted process is interrupted and gets an Interrupted, the target process may decide to ignore the interrupt and continue as if nothing happened.

SendMessage :: ProcessId -> StrictDynamic -> Process r (ResumeProcess ())

Send a message to a process addressed by the ProcessId. Sending a message should always succeed and return immediately, even if the destination process does not exist, or does not accept messages of the given type.

ReceiveSelectedMessage :: forall r a. MessageSelector a -> Process r (ResumeProcess a)

Receive a message that matches a criteria. This should block until an a message was received. The message is returned as a ResumeProcess value. The function should also return if an exception was caught or a shutdown was requested.

MakeReference :: Process r (ResumeProcess Int)

Generate a unique Int for the current process.

Monitor :: ProcessId -> Process r (ResumeProcess MonitorReference)

Monitor another process. When the monitored process exits a ProcessDown is sent to the calling process. The return value is a unique identifier for that monitor. There can be multiple monitors on the same process, and a message for each will be sent. If the process is already dead, the ProcessDown message will be sent immediately, without exit reason

Since: 0.12.0

Demonitor :: MonitorReference -> Process r (ResumeProcess ())

Remove a monitor.

Since: 0.12.0

Link :: ProcessId -> Process r (ResumeProcess ())

Connect the calling process to another process, such that if one of the processes crashes (i.e. isCrash returns True), the other is shutdown with the Interrupt LinkedProcessCrashed.

Since: 0.12.0

Unlink :: ProcessId -> Process r (ResumeProcess ())

Unlink the calling process from the other process.

Since: 0.12.0

UpdateProcessDetails :: ProcessDetails -> Process r (ResumeProcess ())

Update the ProcessDetails of a process

GetProcessState :: ProcessId -> Process r (ResumeProcess (Maybe (ProcessTitle, ProcessDetails, ProcessState)))

Get the ProcessState (or Nothing if the process is dead)

Instances
(LogIo q, TangibleSup p, Tangible (ChildId p), Server p (Processes q)) => Server (Sup p) (Processes q) Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol.Supervisor

Associated Types

data StartArgument (Sup p) (Processes q) :: Type Source #

type Protocol (Sup p) :: Type Source #

type Model (Sup p) :: Type Source #

type Settings (Sup p) :: Type Source #

(TangibleObserver o, IsPdu (Observer o) Asynchronous, Lifted IO q, Member Logs q) => Server (ObservationQueue o) (Processes q) Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol.Observer.Queue

Show (Process r b) Source # 
Instance details

Defined in Control.Eff.Concurrent.Process

Methods

showsPrec :: Int -> Process r b -> ShowS #

show :: Process r b -> String #

showList :: [Process r b] -> ShowS #

Typeable tag => Show (Init (GenServer tag eLoop e) (Processes e)) Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol.EffectfulServer

Methods

showsPrec :: Int -> Init (GenServer tag eLoop e) (Processes e) -> ShowS #

show :: Init (GenServer tag eLoop e) (Processes e) -> String #

showList :: [Init (GenServer tag eLoop e) (Processes e)] -> ShowS #

NFData (Init (GenServer tag eLoop e) (Processes e)) Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol.EffectfulServer

Methods

rnf :: Init (GenServer tag eLoop e) (Processes e) -> () #

TangibleGenServer tag eLoop e => Server (GenServer tag eLoop e) (Processes e) Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol.EffectfulServer

Associated Types

data Init (GenServer tag eLoop e) (Processes e) :: Type Source #

type ServerPdu (GenServer tag eLoop e) :: Type Source #

type ServerEffects (GenServer tag eLoop e) (Processes e) :: [Type -> Type] Source #

Methods

serverTitle :: Init (GenServer tag eLoop e) (Processes e) -> ProcessTitle Source #

runEffects :: Init (GenServer tag eLoop e) (Processes e) -> Eff (ServerEffects (GenServer tag eLoop e) (Processes e)) x -> Eff (Processes e) x Source #

onEvent :: Init (GenServer tag eLoop e) (Processes e) -> Event (ServerPdu (GenServer tag eLoop e)) -> Eff (ServerEffects (GenServer tag eLoop e) (Processes e)) () Source #

data StartArgument (Sup p) (Processes q) Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol.Supervisor

data StartArgument (ObservationQueue o) (Processes q) Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol.Observer.Queue

data Init (GenServer tag eLoop e) (Processes e) Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol.EffectfulServer

type ServerEffects (GenServer tag eLoop e) (Processes e) Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol.EffectfulServer

type ServerEffects (GenServer tag eLoop e) (Processes e) = eLoop

fromProcessTitle :: Lens' ProcessTitle Text Source #

An isomorphism lens for the ProcessTitle

Since: 0.24.1

fromProcessDetails :: Lens' ProcessDetails Text Source #

An isomorphism lens for the ProcessDetails

Since: 0.24.1

toStrictDynamic :: (Typeable a, NFData a) => a -> StrictDynamic Source #

Deeply evaluate the given value and wrap it into a StrictDynamic.

Since: 0.22.0

fromStrictDynamic :: Typeable a => StrictDynamic -> Maybe a Source #

Convert a StrictDynamic back to a value.

Since: 0.22.0

unwrapStrictDynamic :: StrictDynamic -> Dynamic Source #

Convert a StrictDynamic back to an unwrapped Dynamic.

Since: 0.22.0

selectMessage :: Typeable t => MessageSelector t Source #

Create a message selector for a value that can be obtained by fromStrictDynamic.

Since: 0.9.1

filterMessage :: Typeable a => (a -> Bool) -> MessageSelector a Source #

Create a message selector from a predicate.

Since: 0.9.1

selectMessageWith :: Typeable a => (a -> Maybe b) -> MessageSelector b Source #

Select a message of type a and apply the given function to it. If the function returns Just The ReceiveSelectedMessage function will return the result (sans Maybe).

Since: 0.9.1

selectDynamicMessage :: (StrictDynamic -> Maybe a) -> MessageSelector a Source #

Create a message selector.

Since: 0.9.1

selectAnyMessage :: MessageSelector StrictDynamic Source #

Create a message selector that will match every message. This is lazy because the result is not forceed.

Since: 0.9.1

isProcessDownInterrupt :: Maybe ProcessId -> Interrupt r -> Bool Source #

A predicate for linked process crashes.

provideInterruptsShutdown :: forall e a. Eff (Processes e) a -> Eff (SafeProcesses e) a Source #

Handle all Interrupts of an Processes by wrapping them up in interruptToExit and then do a process Shutdown.

handleInterrupts :: (HasCallStack, Member Interrupts r) => (Interrupt Recoverable -> Eff r a) -> Eff r a -> Eff r a Source #

Handle Interrupts arising during process operations, e.g. when a linked process crashes while we wait in a receiveSelectedMessage via a call to interrupt.

tryUninterrupted :: (HasCallStack, Member Interrupts r) => Eff r a -> Eff r (Either (Interrupt Recoverable) a) Source #

Like handleInterrupts, but instead of passing the Interrupt to a handler function, Either is returned.

Since: 0.13.2

logInterrupts :: forall r. (Member Logs r, HasCallStack, Member Interrupts r) => Eff r () -> Eff r () Source #

Handle interrupts by logging them with logProcessExit and otherwise ignoring them.

exitOnInterrupt :: (HasCallStack, Member Interrupts r, SetMember Process (Process q) r) => Eff r a -> Eff r a Source #

Handle Interrupts arising during process operations, e.g. when a linked process crashes while we wait in a receiveSelectedMessage via a call to interrupt.

provideInterrupts :: HasCallStack => Eff (Interrupts ': r) a -> Eff r (Either (Interrupt Recoverable) a) Source #

Handle Interrupts arising during process operations, e.g. when a linked process crashes while we wait in a receiveSelectedMessage via a call to interrupt.

isCrash :: Interrupt x -> Bool Source #

A predicate for crashes. A crash happens when a process exits with an Interrupt other than ExitNormally

isRecoverable :: Interrupt x -> Bool Source #

A predicate for recoverable exit reasons. This predicate defines the exit reasons which functions such as executeAndResume

toCrashReason :: Interrupt x -> Maybe Text Source #

Print a Interrupt to Just a formatted String when isCrash is True. This can be useful in combination with view patterns, e.g.:

logCrash :: Interrupt -> Eff e ()
logCrash (toCrashReason -> Just reason) = logError reason
logCrash _ = return ()

Though this can be improved to:

logCrash = traverse_ logError . toCrashReason

logProcessExit :: forall e x. (Member Logs e, HasCallStack) => Interrupt x -> Eff e () Source #

Log the Interrupts

executeAndResume :: forall q r v. (SetMember Process (Process q) r, HasCallStack) => Process q (ResumeProcess v) -> Eff r (Either (Interrupt Recoverable) v) Source #

Execute a and action and return the result; if the process is interrupted by an error or exception, or an explicit shutdown from another process, or through a crash of a linked process, i.e. whenever the exit reason satisfies isRecoverable, return the exit reason.

executeAndResumeOrExit :: forall r q v. (SetMember Process (Process q) r, HasCallStack) => Process q (ResumeProcess v) -> Eff r v Source #

Execute a Process action and resume the process, exit the process when an Interrupts was raised. Use executeAndResume to catch interrupts.

executeAndResumeOrThrow :: forall q r v. (SetMember Process (Process q) r, HasCallStack, Member Interrupts r) => Process q (ResumeProcess v) -> Eff r v Source #

Execute a Process action and resume the process, exit the process when an Interrupts was raised. Use executeAndResume to catch interrupts.

yieldProcess :: forall r q. (SetMember Process (Process q) r, HasCallStack, Member Interrupts r) => Eff r () Source #

Use executeAndResumeOrExit to execute YieldProcess. Refer to YieldProcess for more information.

sendMessage :: forall r q o. (SetMember Process (Process q) r, HasCallStack, Member Interrupts r, Typeable o, NFData o) => ProcessId -> o -> Eff r () Source #

Send a message to a process addressed by the ProcessId. See SendMessage.

The message will be reduced to normal form (rnf) by/in the caller process.

sendAnyMessage :: forall r q. (SetMember Process (Process q) r, HasCallStack, Member Interrupts r) => ProcessId -> StrictDynamic -> Eff r () Source #

Send a Dynamic value to a process addressed by the ProcessId. See SendMessage.

sendShutdown :: forall r q. (SetMember Process (Process q) r, HasCallStack, Member Interrupts r) => ProcessId -> Interrupt NoRecovery -> Eff r () Source #

Exit a process addressed by the ProcessId. The process will exit, it might do some cleanup, but is ultimately unrecoverable. See SendShutdown.

sendInterrupt :: forall r q. (SetMember Process (Process q) r, HasCallStack, Member Interrupts r) => ProcessId -> Interrupt Recoverable -> Eff r () Source #

Interrupts a process addressed by the ProcessId. The process might exit, or it may continue. | Like sendInterrupt, but also return True iff the process to exit exists.

spawn :: forall r q. (HasCallStack, SetMember Process (Process q) r, Member Interrupts r) => ProcessTitle -> Eff (Processes q) () -> Eff r ProcessId Source #

Start a new process, the new process will execute an effect, the function will return immediately with a ProcessId. If the new process is interrupted, the process will Shutdown with the Interrupt wrapped in interruptToExit. For specific use cases it might be better to use spawnRaw.

spawn_ :: forall r q. (HasCallStack, SetMember Process (Process q) r, Member Interrupts r) => ProcessTitle -> Eff (Processes q) () -> Eff r () Source #

Like spawn but return ().

spawnLink :: forall r q. (HasCallStack, SetMember Process (Process q) r, Member Interrupts r) => ProcessTitle -> Eff (Processes q) () -> Eff r ProcessId Source #

Start a new process, and immediately link to it.

Since: 0.12.0

spawnRaw :: forall r q. (HasCallStack, SetMember Process (Process q) r, Member Interrupts r) => ProcessTitle -> Eff (SafeProcesses q) () -> Eff r ProcessId Source #

Start a new process, the new process will execute an effect, the function will return immediately with a ProcessId. The spawned process has only the raw SafeProcesses effects. For non-library code spawn might be better suited.

spawnRaw_ :: forall r q. (HasCallStack, SetMember Process (Process q) r, Member Interrupts r) => ProcessTitle -> Eff (SafeProcesses q) () -> Eff r () Source #

Like spawnRaw but return ().

isProcessAlive :: forall r q. (HasCallStack, SetMember Process (Process q) r, Member Interrupts r) => ProcessId -> Eff r Bool Source #

Return True if the process is alive.

Since: 0.12.0

getProcessState :: forall r q. (HasCallStack, SetMember Process (Process q) r, Member Interrupts r) => ProcessId -> Eff r (Maybe (ProcessTitle, ProcessDetails, ProcessState)) Source #

Return the ProcessTitle, ProcessDetails and ProcessState, for the given process, if the process is alive.

Since: 0.24.1

updateProcessDetails :: forall r q. (HasCallStack, SetMember Process (Process q) r, Member Interrupts r) => ProcessDetails -> Eff r () Source #

Replace the ProcessDetails of the process.

Since: 0.24.1

receiveAnyMessage :: forall r q. (HasCallStack, SetMember Process (Process q) r, Member Interrupts r) => Eff r StrictDynamic Source #

Block until a message was received. See ReceiveSelectedMessage for more documentation.

receiveSelectedMessage :: forall r q a. (HasCallStack, Show a, SetMember Process (Process q) r, Member Interrupts r) => MessageSelector a -> Eff r a Source #

Block until a message was received, that is not Nothing after applying a callback to it. See ReceiveSelectedMessage for more documentation.

receiveMessage :: forall a r q. (HasCallStack, Typeable a, NFData a, Show a, SetMember Process (Process q) r, Member Interrupts r) => Eff r a Source #

Receive and cast the message to some Typeable instance. See ReceiveSelectedMessage for more documentation. This will wait for a message of the return type using receiveSelectedMessage

flushMessages :: forall r q. (HasCallStack, SetMember Process (Process q) r, Member Interrupts r) => Eff r [StrictDynamic] Source #

Remove and return all messages currently enqueued in the process message queue.

Since: 0.12.0

receiveSelectedLoop :: forall r q a endOfLoopResult. (SetMember Process (Process q) r, HasCallStack) => MessageSelector a -> (Either (Interrupt Recoverable) a -> Eff r (Maybe endOfLoopResult)) -> Eff r endOfLoopResult Source #

Enter a loop to receive messages and pass them to a callback, until the function returns Just a result. Only the messages of the given type will be received. If the process is interrupted by an exception of by a SendShutdown from another process, with an exit reason that satisfies isRecoverable, then the callback will be invoked with Left Interrupt, otherwise the process will be exited with the same reason using exitBecause. See also ReceiveSelectedMessage for more documentation.

receiveAnyLoop :: forall r q endOfLoopResult. (SetMember Process (Process q) r, HasCallStack) => (Either (Interrupt Recoverable) StrictDynamic -> Eff r (Maybe endOfLoopResult)) -> Eff r endOfLoopResult Source #

Like receiveSelectedLoop but not selective. See also selectAnyMessage, receiveSelectedLoop.

receiveLoop :: forall r q a endOfLoopResult. (SetMember Process (Process q) r, HasCallStack, NFData a, Typeable a) => (Either (Interrupt Recoverable) a -> Eff r (Maybe endOfLoopResult)) -> Eff r endOfLoopResult Source #

Like receiveSelectedLoop but refined to casting to a specific Typeable using selectMessage.

self :: (HasCallStack, SetMember Process (Process q) r) => Eff r ProcessId Source #

Returns the ProcessId of the current process.

makeReference :: (HasCallStack, SetMember Process (Process q) r, Member Interrupts r) => Eff r Int Source #

Generate a unique Int for the current process.

monitor :: forall r q. (HasCallStack, SetMember Process (Process q) r, Member Interrupts r) => ProcessId -> Eff r MonitorReference Source #

Monitor another process. When the monitored process exits a ProcessDown is sent to the calling process. The return value is a unique identifier for that monitor. There can be multiple monitors on the same process, and a message for each will be sent. If the process is already dead, the ProcessDown message will be sent immediately, without exit reason

Since: 0.12.0

demonitor :: forall r q. (HasCallStack, SetMember Process (Process q) r, Member Interrupts r) => MonitorReference -> Eff r () Source #

Remove a monitor created with monitor.

Since: 0.12.0

withMonitor :: (HasCallStack, Member Interrupts r, SetMember Process (Process q) r, Member Interrupts r) => ProcessId -> (MonitorReference -> Eff r a) -> Eff r a Source #

monitor another process before while performing an action and demonitor afterwards.

Since: 0.12.0

receiveWithMonitor :: (HasCallStack, Member Interrupts r, SetMember Process (Process q) r, Member Interrupts r, Typeable a, Show a) => ProcessId -> MessageSelector a -> Eff r (Either ProcessDown a) Source #

A MessageSelector for receiving either a monitor of the given process or another message.

Since: 0.12.0

becauseProcessIsDown :: ProcessDown -> Interrupt Recoverable Source #

Make an Interrupt for a ProcessDown message.

For example: doSomething >>= either (interrupt . becauseProcessIsDown) return

Since: 0.12.0

selectProcessDown :: MonitorReference -> MessageSelector ProcessDown Source #

A MessageSelector for the ProcessDown message of a specific process.

Since: 0.12.0

linkProcess :: forall r q. (HasCallStack, SetMember Process (Process q) r, Member Interrupts r) => ProcessId -> Eff r () Source #

Connect the calling process to another process, such that if one of the processes crashes (i.e. isCrash returns True), the other is shutdown with the Interrupt LinkedProcessCrashed.

Since: 0.12.0

unlinkProcess :: forall r q. (HasCallStack, SetMember Process (Process q) r, Member Interrupts r) => ProcessId -> Eff r () Source #

Unlink the calling process from the other process.

Since: 0.12.0

exitBecause :: forall r q a. (HasCallStack, SetMember Process (Process q) r) => Interrupt NoRecovery -> Eff r a Source #

Exit the process with a Interrupt.

exitNormally :: forall r q a. (HasCallStack, SetMember Process (Process q) r) => Eff r a Source #

Exit the process.

exitWithError :: forall r q a. (HasCallStack, SetMember Process (Process q) r) => String -> Eff r a Source #

Exit the process with an error.

newtype Endpoint protocol Source #

This is a tag-type that wraps around a ProcessId and holds an Pdu index type.

Constructors

Endpoint 
Instances
Eq (Endpoint protocol) Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol

Methods

(==) :: Endpoint protocol -> Endpoint protocol -> Bool #

(/=) :: Endpoint protocol -> Endpoint protocol -> Bool #

Ord (Endpoint protocol) Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol

Methods

compare :: Endpoint protocol -> Endpoint protocol -> Ordering #

(<) :: Endpoint protocol -> Endpoint protocol -> Bool #

(<=) :: Endpoint protocol -> Endpoint protocol -> Bool #

(>) :: Endpoint protocol -> Endpoint protocol -> Bool #

(>=) :: Endpoint protocol -> Endpoint protocol -> Bool #

max :: Endpoint protocol -> Endpoint protocol -> Endpoint protocol #

min :: Endpoint protocol -> Endpoint protocol -> Endpoint protocol #

Typeable protocol => Show (Endpoint protocol) Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol

Methods

showsPrec :: Int -> Endpoint protocol -> ShowS #

show :: Endpoint protocol -> String #

showList :: [Endpoint protocol] -> ShowS #

NFData (Endpoint protocol) Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol

Methods

rnf :: Endpoint protocol -> () #

type ToPretty (Endpoint a :: Type) Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol

type ToPretty (Endpoint a :: Type) = ToPretty a <+> PutStr "endpoint"

type family ProtocolReply (s :: Synchronicity) where ... Source #

This type function takes an Pdu and analysis the reply type, i.e. the Synchronicity and evaluates to either t for an Pdu x (Synchronous t) or to '()' for an Pdu x Asynchronous.

Since: 0.24.0

data Synchronicity Source #

The (promoted) constructors of this type specify (at the type level) the reply behavior of a specific constructor of an Pdu instance.

Constructors

Synchronous Type

Specify that handling a request is a blocking operation with a specific return type, e.g. ('Synchronous (Either RentalError RentalId))

Asynchronous

Non-blocking, asynchronous, request handling

type TangiblePdu p r = (Typeable p, Typeable r, Tangible (Pdu p r)) Source #

A Constraint that bundles the requirements for the Pdu values of a protocol.

This ensures that Pdus can be strictly and deeply evaluated and shown such that for example logging is possible.

Since: 0.24.0

type Tangible i = (NFData i, Typeable i, Show i) Source #

A set of constraints for types that can evaluated via NFData, compared via Ord and presented dynamically via Typeable, and represented both as values via Show.

Since: 0.23.0

class (NFData (Pdu protocol reply), Show (Pdu protocol reply), Typeable protocol, Typeable reply) => IsPdu (protocol :: Type) (reply :: Synchronicity) where Source #

This data family defines the protocol data units (PDU) of a protocol.

A Protocol in the sense of a communication interface description between processes.

The first parameter is usually a user defined type that identifies the protocol that uses the Pdus are. It maybe a phantom type.

The second parameter specifies if a specific constructor of an (GADT-like) Pdu instance is Synchronous, i.e. returns a result and blocks the caller or if it is Asynchronous

Example:

data BookShop deriving Typeable

instance IsPdu BookShop r where
  data instance Pdu BookShop r where
    RentBook  :: BookId   -> Pdu BookShop ('Synchronous (Either RentalError RentalId))
    BringBack :: RentalId -> Pdu BookShop 'Asynchronous
    deriving Typeable

type BookId = Int
type RentalId = Int
type RentalError = String

Since: 0.25.1

Minimal complete definition

Nothing

Associated Types

data Pdu protocol reply Source #

The protocol data unit type for the given protocol.

Methods

deserializePdu :: Dynamic -> Maybe (Pdu protocol reply) Source #

Deserialize a Pdu from a Dynamic i.e. from a message received by a process.

Since: 0.25.1

deserializePdu :: Typeable (Pdu protocol reply) => Dynamic -> Maybe (Pdu protocol reply) Source #

Deserialize a Pdu from a Dynamic i.e. from a message received by a process.

Since: 0.25.1

Instances
(NFData (Pdu (Sup p) r), Show (Pdu (Sup p) r), Typeable p, Typeable r) => IsPdu (Sup p) r Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol.Supervisor

Associated Types

data Pdu (Sup p) r :: Type Source #

Methods

deserializePdu :: Dynamic -> Maybe (Pdu (Sup p) r) Source #

(Typeable o, Typeable r) => IsPdu (ObserverRegistry o) r Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol.Observer

Associated Types

data Pdu (ObserverRegistry o) r :: Type Source #

(NFData o, Show o, Typeable o, Typeable r) => IsPdu (Observer o) r Source #

A minimal Protocol for handling observations. This is one simple way of receiving observations - of course users can use any other Asynchronous Pdu message type for receiving observations.

Since: 0.16.0

Instance details

Defined in Control.Eff.Concurrent.Protocol.Observer

Associated Types

data Pdu (Observer o) r :: Type Source #

(IsPdu a1 r, IsPdu a2 r) => IsPdu (a1, a2) r Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol

Associated Types

data Pdu (a1, a2) r :: Type Source #

Methods

deserializePdu :: Dynamic -> Maybe (Pdu (a1, a2) r) Source #

(IsPdu a1 r, IsPdu a2 r, IsPdu a3 r) => IsPdu (a1, a2, a3) r Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol

Associated Types

data Pdu (a1, a2, a3) r :: Type Source #

Methods

deserializePdu :: Dynamic -> Maybe (Pdu (a1, a2, a3) r) Source #

(IsPdu a1 r, IsPdu a2 r, IsPdu a3 r, IsPdu a4 r) => IsPdu (a1, a2, a3, a4) r Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol

Associated Types

data Pdu (a1, a2, a3, a4) r :: Type Source #

Methods

deserializePdu :: Dynamic -> Maybe (Pdu (a1, a2, a3, a4) r) Source #

(IsPdu a1 r, IsPdu a2 r, IsPdu a3 r, IsPdu a4 r, IsPdu a5 r) => IsPdu (a1, a2, a3, a4, a5) r Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol

Associated Types

data Pdu (a1, a2, a3, a4, a5) r :: Type Source #

Methods

deserializePdu :: Dynamic -> Maybe (Pdu (a1, a2, a3, a4, a5) r) Source #

class EmbedProtocol protocol embeddedProtocol where Source #

A class for Pdu instances that embed other Pdu. A Prism for the embedded Pdu is the center of this class

Laws: embeddedPdu = prism' embedPdu fromPdu

Since: 0.24.0

Minimal complete definition

Nothing

Methods

embeddedPdu :: Prism' (Pdu protocol result) (Pdu embeddedProtocol result) Source #

A Prism for the embedded Pdus.

embedPdu :: Pdu embeddedProtocol r -> Pdu protocol r Source #

Embed the Pdu value of an embedded protocol into the corresponding Pdu value.

fromPdu :: Pdu protocol r -> Maybe (Pdu embeddedProtocol r) Source #

Examine a Pdu value from the outer protocol, and return it, if it embeds a Pdu of embedded protocol, otherwise return Nothing/

Instances
EmbedProtocol a a Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol

Methods

embeddedPdu :: Prism' (Pdu a result) (Pdu a result) Source #

embedPdu :: Pdu a r -> Pdu a r Source #

fromPdu :: Pdu a r -> Maybe (Pdu a r) Source #

EmbedProtocol (a1, a2) a2 Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol

Methods

embeddedPdu :: Prism' (Pdu (a1, a2) result) (Pdu a2 result) Source #

embedPdu :: Pdu a2 r -> Pdu (a1, a2) r Source #

fromPdu :: Pdu (a1, a2) r -> Maybe (Pdu a2 r) Source #

EmbedProtocol (a1, a2) a1 Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol

Methods

embeddedPdu :: Prism' (Pdu (a1, a2) result) (Pdu a1 result) Source #

embedPdu :: Pdu a1 r -> Pdu (a1, a2) r Source #

fromPdu :: Pdu (a1, a2) r -> Maybe (Pdu a1 r) Source #

EmbedProtocol (a1, a2, a3) a3 Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol

Methods

embeddedPdu :: Prism' (Pdu (a1, a2, a3) result) (Pdu a3 result) Source #

embedPdu :: Pdu a3 r -> Pdu (a1, a2, a3) r Source #

fromPdu :: Pdu (a1, a2, a3) r -> Maybe (Pdu a3 r) Source #

EmbedProtocol (a1, a2, a3) a2 Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol

Methods

embeddedPdu :: Prism' (Pdu (a1, a2, a3) result) (Pdu a2 result) Source #

embedPdu :: Pdu a2 r -> Pdu (a1, a2, a3) r Source #

fromPdu :: Pdu (a1, a2, a3) r -> Maybe (Pdu a2 r) Source #

EmbedProtocol (a1, a2, a3) a1 Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol

Methods

embeddedPdu :: Prism' (Pdu (a1, a2, a3) result) (Pdu a1 result) Source #

embedPdu :: Pdu a1 r -> Pdu (a1, a2, a3) r Source #

fromPdu :: Pdu (a1, a2, a3) r -> Maybe (Pdu a1 r) Source #

EmbedProtocol (a1, a2, a3, a4) a4 Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol

Methods

embeddedPdu :: Prism' (Pdu (a1, a2, a3, a4) result) (Pdu a4 result) Source #

embedPdu :: Pdu a4 r -> Pdu (a1, a2, a3, a4) r Source #

fromPdu :: Pdu (a1, a2, a3, a4) r -> Maybe (Pdu a4 r) Source #

EmbedProtocol (a1, a2, a3, a4) a3 Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol

Methods

embeddedPdu :: Prism' (Pdu (a1, a2, a3, a4) result) (Pdu a3 result) Source #

embedPdu :: Pdu a3 r -> Pdu (a1, a2, a3, a4) r Source #

fromPdu :: Pdu (a1, a2, a3, a4) r -> Maybe (Pdu a3 r) Source #

EmbedProtocol (a1, a2, a3, a4) a2 Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol

Methods

embeddedPdu :: Prism' (Pdu (a1, a2, a3, a4) result) (Pdu a2 result) Source #

embedPdu :: Pdu a2 r -> Pdu (a1, a2, a3, a4) r Source #

fromPdu :: Pdu (a1, a2, a3, a4) r -> Maybe (Pdu a2 r) Source #

EmbedProtocol (a1, a2, a3, a4) a1 Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol

Methods

embeddedPdu :: Prism' (Pdu (a1, a2, a3, a4) result) (Pdu a1 result) Source #

embedPdu :: Pdu a1 r -> Pdu (a1, a2, a3, a4) r Source #

fromPdu :: Pdu (a1, a2, a3, a4) r -> Maybe (Pdu a1 r) Source #

EmbedProtocol (a1, a2, a3, a4, a5) a5 Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol

Methods

embeddedPdu :: Prism' (Pdu (a1, a2, a3, a4, a5) result) (Pdu a5 result) Source #

embedPdu :: Pdu a5 r -> Pdu (a1, a2, a3, a4, a5) r Source #

fromPdu :: Pdu (a1, a2, a3, a4, a5) r -> Maybe (Pdu a5 r) Source #

EmbedProtocol (a1, a2, a3, a4, a5) a4 Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol

Methods

embeddedPdu :: Prism' (Pdu (a1, a2, a3, a4, a5) result) (Pdu a4 result) Source #

embedPdu :: Pdu a4 r -> Pdu (a1, a2, a3, a4, a5) r Source #

fromPdu :: Pdu (a1, a2, a3, a4, a5) r -> Maybe (Pdu a4 r) Source #

EmbedProtocol (a1, a2, a3, a4, a5) a3 Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol

Methods

embeddedPdu :: Prism' (Pdu (a1, a2, a3, a4, a5) result) (Pdu a3 result) Source #

embedPdu :: Pdu a3 r -> Pdu (a1, a2, a3, a4, a5) r Source #

fromPdu :: Pdu (a1, a2, a3, a4, a5) r -> Maybe (Pdu a3 r) Source #

EmbedProtocol (a1, a2, a3, a4, a5) a2 Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol

Methods

embeddedPdu :: Prism' (Pdu (a1, a2, a3, a4, a5) result) (Pdu a2 result) Source #

embedPdu :: Pdu a2 r -> Pdu (a1, a2, a3, a4, a5) r Source #

fromPdu :: Pdu (a1, a2, a3, a4, a5) r -> Maybe (Pdu a2 r) Source #

EmbedProtocol (a1, a2, a3, a4, a5) a1 Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol

Methods

embeddedPdu :: Prism' (Pdu (a1, a2, a3, a4, a5) result) (Pdu a1 result) Source #

embedPdu :: Pdu a1 r -> Pdu (a1, a2, a3, a4, a5) r Source #

fromPdu :: Pdu (a1, a2, a3, a4, a5) r -> Maybe (Pdu a1 r) Source #

fromEndpoint :: forall protocol protocol. Iso (Endpoint protocol) (Endpoint protocol) ProcessId ProcessId Source #

proxyAsEndpoint :: proxy protocol -> ProcessId -> Endpoint protocol Source #

Tag a ProcessId with an Pdu type index to mark it a Endpoint process handling that API

asEndpoint :: forall protocol. ProcessId -> Endpoint protocol Source #

Tag a ProcessId with an Pdu type index to mark it a Endpoint process handling that API

toEmbeddedEndpoint :: forall inner outer. EmbedProtocol outer inner => Endpoint outer -> Endpoint inner Source #

Convert an Endpoint to an endpoint for an embedded protocol.

See EmbedProtocol, fromEmbeddedEndpoint.

Since: 0.25.1

fromEmbeddedEndpoint :: forall outer inner. EmbedProtocol outer inner => Endpoint inner -> Endpoint outer Source #

Convert an Endpoint to an endpoint for a server, that embeds the protocol.

See EmbedProtocol, toEmbeddedEndpoint.

Since: 0.25.1

newtype ReplyTarget p r Source #

Target of a Call reply.

This combines a RequestOrigin with a Serializer for a Reply using Arg. There are to smart constructors for this type: replyTarget and embeddedReplyTarget.

Because of Arg the Eq and Ord instances are implemented via the RequestOrigin instances.

Since: 0.26.0

Constructors

MkReplyTarget (Arg (RequestOrigin p r) (Serializer (Reply p r))) 
Instances
Eq (ReplyTarget p r) Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol.Request

Methods

(==) :: ReplyTarget p r -> ReplyTarget p r -> Bool #

(/=) :: ReplyTarget p r -> ReplyTarget p r -> Bool #

Ord (ReplyTarget p r) Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol.Request

Methods

compare :: ReplyTarget p r -> ReplyTarget p r -> Ordering #

(<) :: ReplyTarget p r -> ReplyTarget p r -> Bool #

(<=) :: ReplyTarget p r -> ReplyTarget p r -> Bool #

(>) :: ReplyTarget p r -> ReplyTarget p r -> Bool #

(>=) :: ReplyTarget p r -> ReplyTarget p r -> Bool #

max :: ReplyTarget p r -> ReplyTarget p r -> ReplyTarget p r #

min :: ReplyTarget p r -> ReplyTarget p r -> ReplyTarget p r #

Show (ReplyTarget p r) Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol.Request

Methods

showsPrec :: Int -> ReplyTarget p r -> ShowS #

show :: ReplyTarget p r -> String #

showList :: [ReplyTarget p r] -> ShowS #

NFData (ReplyTarget p r) Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol.Request

Methods

rnf :: ReplyTarget p r -> () #

data RequestOrigin (proto :: Type) reply Source #

Wraps the source ProcessId and a unique identifier for a Call.

Since: 0.15.0

Instances
Eq (RequestOrigin proto reply) Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol.Request

Methods

(==) :: RequestOrigin proto reply -> RequestOrigin proto reply -> Bool #

(/=) :: RequestOrigin proto reply -> RequestOrigin proto reply -> Bool #

Ord (RequestOrigin proto reply) Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol.Request

Methods

compare :: RequestOrigin proto reply -> RequestOrigin proto reply -> Ordering #

(<) :: RequestOrigin proto reply -> RequestOrigin proto reply -> Bool #

(<=) :: RequestOrigin proto reply -> RequestOrigin proto reply -> Bool #

(>) :: RequestOrigin proto reply -> RequestOrigin proto reply -> Bool #

(>=) :: RequestOrigin proto reply -> RequestOrigin proto reply -> Bool #

max :: RequestOrigin proto reply -> RequestOrigin proto reply -> RequestOrigin proto reply #

min :: RequestOrigin proto reply -> RequestOrigin proto reply -> RequestOrigin proto reply #

Show (RequestOrigin p r) Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol.Request

Generic (RequestOrigin proto reply) Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol.Request

Associated Types

type Rep (RequestOrigin proto reply) :: Type -> Type #

Methods

from :: RequestOrigin proto reply -> Rep (RequestOrigin proto reply) x #

to :: Rep (RequestOrigin proto reply) x -> RequestOrigin proto reply #

NFData (RequestOrigin p r) Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol.Request

Methods

rnf :: RequestOrigin p r -> () #

type Rep (RequestOrigin proto reply) Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol.Request

type Rep (RequestOrigin proto reply) = D1 (MetaData "RequestOrigin" "Control.Eff.Concurrent.Protocol.Request" "extensible-effects-concurrent-0.26.1-H4MbFpru2ZADB31xfNLjdz" False) (C1 (MetaCons "RequestOrigin" PrefixI True) (S1 (MetaSel (Just "_requestOriginPid") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 ProcessId) :*: S1 (MetaSel (Just "_requestOriginCallRef") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Int)))

data Reply protocol reply where Source #

The wrapper around replies to Calls.

Since: 0.15.0

Constructors

Reply 

Fields

Instances
Show r => Show (Reply p r) Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol.Request

Methods

showsPrec :: Int -> Reply p r -> ShowS #

show :: Reply p r -> String #

showList :: [Reply p r] -> ShowS #

NFData (Reply p r) Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol.Request

Methods

rnf :: Reply p r -> () #

data Request protocol where Source #

A wrapper sum type for calls and casts for the Pdus of a protocol

Since: 0.15.0

Constructors

Call :: forall protocol reply. (Tangible reply, TangiblePdu protocol (Synchronous reply)) => RequestOrigin protocol reply -> Pdu protocol (Synchronous reply) -> Request protocol 
Cast :: forall protocol. (TangiblePdu protocol Asynchronous, NFData (Pdu protocol Asynchronous)) => Pdu protocol Asynchronous -> Request protocol 
Instances
Show (Request protocol) Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol.Request

Methods

showsPrec :: Int -> Request protocol -> ShowS #

show :: Request protocol -> String #

showList :: [Request protocol] -> ShowS #

NFData (Request protocol) Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol.Request

Methods

rnf :: Request protocol -> () #

makeRequestOrigin :: (Typeable r, NFData r, SetMember Process (Process q0) e, '[Interrupts] <:: e) => Eff e (RequestOrigin p r) Source #

Create a new, unique RequestOrigin value for the current process.

Since: 0.24.0

toEmbeddedOrigin :: forall outer inner reply. EmbedProtocol outer inner => RequestOrigin outer reply -> RequestOrigin inner reply Source #

Turn an RequestOrigin to an origin for an embedded request (See EmbedProtocol).

This is useful of a server delegates the calls and casts for an embedded protocol to functions, that require the Serializer and RequestOrigin in order to call sendReply.

See also embedReplySerializer.

Since: 0.24.3

embedRequestOrigin :: forall outer inner reply. EmbedProtocol outer inner => RequestOrigin inner reply -> RequestOrigin outer reply Source #

Turn an embedded RequestOrigin to a RequestOrigin for the bigger request.

This is the inverse of toEmbeddedOrigin.

This function is strict in all parameters.

Since: 0.24.2

embedReplySerializer :: forall outer inner reply. EmbedProtocol outer inner => Serializer (Reply outer reply) -> Serializer (Reply inner reply) Source #

Turn a Serializer for a Pdu instance that contains embedded Pdu values into a Reply Serializer for the embedded Pdu.

This is useful of a server delegates the calls and casts for an embedded protocol to functions, that require the Serializer and RequestOrigin in order to call sendReply.

See also toEmbeddedOrigin.

Since: 0.24.2

sendReply :: (SetMember Process (Process q) eff, Member Interrupts eff, Tangible reply, Typeable protocol) => ReplyTarget protocol reply -> reply -> Eff eff () Source #

Answer a Call by sending the reply value to the client process.

The ProcessId, the RequestOrigin and the Reply Serializer are stored in the ReplyTarget.

Since: 0.25.1

replyTarget :: Serializer (Reply p reply) -> RequestOrigin p reply -> ReplyTarget p reply Source #

Smart constructor for a ReplyTarget.

To build a ReplyTarget for an EmbedProtocol instance use embeddedReplyTarget.

Since: 0.26.0

replyTargetOrigin :: Lens' (ReplyTarget p reply) (RequestOrigin p reply) Source #

A simple Lens for the RequestOrigin of a ReplyTarget.

Since: 0.26.0

replyTargetSerializer :: Lens' (ReplyTarget p reply) (Serializer (Reply p reply)) Source #

A simple Lens for the Reply Serializer of a ReplyTarget.

Since: 0.26.0

embeddedReplyTarget :: EmbedProtocol outer inner => Serializer (Reply outer reply) -> RequestOrigin outer reply -> ReplyTarget inner reply Source #

Smart constructor for an embedded ReplyTarget.

This combines replyTarget and toEmbeddedReplyTarget.

Since: 0.26.0

toEmbeddedReplyTarget :: EmbedProtocol outer inner => ReplyTarget outer r -> ReplyTarget inner r Source #

Convert a ReplyTarget to be usable for embedded replies.

This combines a toEmbeddedOrigin with embedReplySerializer to produce a ReplyTarget that can be passed to functions defined soley on an embedded protocol.

Since: 0.26.0

data TimerReference Source #

The reference to a timer started by startTimer, required to stop a timer via cancelTimer.

Since: 0.12.0

Instances
Enum TimerReference Source # 
Instance details

Defined in Control.Eff.Concurrent.Process.Timer

Eq TimerReference Source # 
Instance details

Defined in Control.Eff.Concurrent.Process.Timer

Integral TimerReference Source # 
Instance details

Defined in Control.Eff.Concurrent.Process.Timer

Num TimerReference Source # 
Instance details

Defined in Control.Eff.Concurrent.Process.Timer

Ord TimerReference Source # 
Instance details

Defined in Control.Eff.Concurrent.Process.Timer

Real TimerReference Source # 
Instance details

Defined in Control.Eff.Concurrent.Process.Timer

Show TimerReference Source # 
Instance details

Defined in Control.Eff.Concurrent.Process.Timer

NFData TimerReference Source # 
Instance details

Defined in Control.Eff.Concurrent.Process.Timer

Methods

rnf :: TimerReference -> () #

data Timeout Source #

A number of micro seconds.

Since: 0.12.0

Instances
Enum Timeout Source # 
Instance details

Defined in Control.Eff.Concurrent.Process.Timer

Eq Timeout Source # 
Instance details

Defined in Control.Eff.Concurrent.Process.Timer

Methods

(==) :: Timeout -> Timeout -> Bool #

(/=) :: Timeout -> Timeout -> Bool #

Integral Timeout Source # 
Instance details

Defined in Control.Eff.Concurrent.Process.Timer

Num Timeout Source # 
Instance details

Defined in Control.Eff.Concurrent.Process.Timer

Ord Timeout Source # 
Instance details

Defined in Control.Eff.Concurrent.Process.Timer

Real Timeout Source # 
Instance details

Defined in Control.Eff.Concurrent.Process.Timer

Show Timeout Source # 
Instance details

Defined in Control.Eff.Concurrent.Process.Timer

NFData Timeout Source # 
Instance details

Defined in Control.Eff.Concurrent.Process.Timer

Methods

rnf :: Timeout -> () #

receiveAfter :: forall a r q. (Lifted IO q, HasCallStack, SetMember Process (Process q) r, Member Interrupts r, Typeable a, NFData a, Show a) => Timeout -> Eff r (Maybe a) Source #

Wait for a message of the given type for the given time. When no message arrives in time, return Nothing. This is based on receiveSelectedAfter.

Since: 0.12.0

receiveSelectedAfter :: forall a r q. (Lifted IO q, HasCallStack, SetMember Process (Process q) r, Member Interrupts r, Show a) => MessageSelector a -> Timeout -> Eff r (Either TimerElapsed a) Source #

Wait for a message of the given type for the given time. When no message arrives in time, return Left TimerElapsed. This is based on selectTimerElapsed and startTimer.

Since: 0.12.0

sendAfter :: forall r q message. (Lifted IO q, HasCallStack, SetMember Process (Process q) r, Member Interrupts r, Typeable message, NFData message) => ProcessId -> Timeout -> (TimerReference -> message) -> Eff r TimerReference Source #

Send a message to a given process after waiting. The message is created by applying the function parameter to the TimerReference, such that the message can directly refer to the timer.

Since: 0.12.0

startTimer :: forall r q. (Lifted IO q, HasCallStack, SetMember Process (Process q) r, Member Interrupts r) => Timeout -> Eff r TimerReference Source #

Start a new timer, after the time has elapsed, TimerElapsed is sent to calling process. The message also contains the TimerReference returned by this function. Use cancelTimer to cancel the timer. Use selectTimerElapsed to receive the message using receiveSelectedMessage. To receive messages with guarded with a timeout see receiveAfter.

Since: 0.12.0

cancelTimer :: forall r q. (Lifted IO q, HasCallStack, SetMember Process (Process q) r, Member Interrupts r) => TimerReference -> Eff r () Source #

Cancel a timer started with startTimer.

Since: 0.12.0

type EndpointReader o = Reader (Endpoint o) Source #

The reader effect for ProcessIds for Pdus, see runEndpointReader

type ServesProtocol o r q = (Typeable o, SetMember Process (Process q) r, Member (EndpointReader o) r) Source #

Instead of passing around a Endpoint value and passing to functions like cast or call, a Endpoint can provided by a Reader effect, if there is only a single server for a given Pdu instance. This type alias is convenience to express that an effect has Process and a reader for a Endpoint.

cast :: forall o' o r q. (HasCallStack, SetMember Process (Process q) r, Member Interrupts r, IsPdu o' Asynchronous, IsPdu o Asynchronous, EmbedProtocol o' o) => Endpoint o' -> Pdu o Asynchronous -> Eff r () Source #

Send a request Pdu that has no reply and return immediately.

The type signature enforces that the corresponding Pdu clause is Asynchronous. The operation never fails, if it is important to know if the message was delivered, use call instead.

The message will be reduced to normal form (rnf) in the caller process.

call :: forall result protocol' protocol r q. (SetMember Process (Process q) r, Member Interrupts r, TangiblePdu protocol' (Synchronous result), TangiblePdu protocol (Synchronous result), EmbedProtocol protocol' protocol, Tangible result, HasCallStack) => Endpoint protocol' -> Pdu protocol (Synchronous result) -> Eff r result Source #

Send a request Pdu and wait for the server to return a result value.

The type signature enforces that the corresponding Pdu clause is Synchronous.

Always prefer callWithTimeout over call

callWithTimeout :: forall result protocol' protocol r q. (SetMember Process (Process q) r, Member Interrupts r, TangiblePdu protocol' (Synchronous result), TangiblePdu protocol (Synchronous result), EmbedProtocol protocol' protocol, Tangible result, Member Logs r, Lifted IO q, Lifted IO r, HasCallStack) => Endpoint protocol' -> Pdu protocol (Synchronous result) -> Timeout -> Eff r result Source #

Send an request Pdu and wait for the server to return a result value.

The type signature enforces that the corresponding Pdu clause is Synchronous.

If the server that was called dies, this function interrupts the process with ProcessDown. If the server takes longer to reply than the given timeout, this function interrupts the process with TimeoutInterrupt.

Always prefer this function over call

Since: 0.22.0

runEndpointReader :: HasCallStack => Endpoint o -> Eff (EndpointReader o ': r) a -> Eff r a Source #

Run a reader effect that contains the one server handling a specific Pdu instance.

askEndpoint :: Member (EndpointReader o) e => Eff e (Endpoint o) Source #

Get the Endpoint registered with runEndpointReader.

callEndpointReader :: forall reply o r q. (ServesProtocol o r q, HasCallStack, Tangible reply, TangiblePdu o (Synchronous reply), Member Interrupts r) => Pdu o (Synchronous reply) -> Eff r reply Source #

Like call but take the Endpoint from the reader provided by runEndpointReader.

When working with an embedded Pdu use callSingleton.

castEndpointReader :: forall o r q. (ServesProtocol o r q, HasCallStack, Member Interrupts r, IsPdu o Asynchronous) => Pdu o Asynchronous -> Eff r () Source #

Like cast but take the Endpoint from the reader provided by runEndpointReader.

When working with an embedded Pdu use castSingleton.

callSingleton :: forall outer inner reply q e. (HasCallStack, EmbedProtocol outer inner, Member (EndpointReader outer) e, SetMember Process (Process q) e, Member Interrupts e, TangiblePdu outer (Synchronous reply), TangiblePdu inner (Synchronous reply), Tangible reply) => Pdu inner (Synchronous reply) -> Eff e reply Source #

Like callEndpointReader, uses embedPdu to embed the value.

This function makes use of AmbigousTypes and TypeApplications.

When not working with an embedded Pdu use callEndpointReader.

Since: 0.25.1

castSingleton :: forall outer inner q e. (HasCallStack, EmbedProtocol outer inner, Member (EndpointReader outer) e, SetMember Process (Process q) e, Member Interrupts e, IsPdu outer Asynchronous, IsPdu inner Asynchronous) => Pdu inner Asynchronous -> Eff e () Source #

Like castEndpointReader, but uses embedPdu to embed the value.

This function makes use of AmbigousTypes and TypeApplications.

When not working with an embedded Pdu use castEndpointReader.

Since: 0.25.1

type ObserverState o = State (Observers o) Source #

Alias for the effect that contains the observers managed by manageObservers

data Observers o Source #

Internal state for manageObservers

Instances
Eq (Observers o) Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol.Observer

Methods

(==) :: Observers o -> Observers o -> Bool #

(/=) :: Observers o -> Observers o -> Bool #

Ord (Observers o) Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol.Observer

Show (Observers o) Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol.Observer

NFData o => NFData (Observers o) Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol.Observer

Methods

rnf :: Observers o -> () #

data ObserverRegistry (o :: Type) Source #

A protocol for managing Observers, encompassing registration and de-registration of Observers.

Since: 0.16.0

Instances
(Typeable o, Typeable r) => IsPdu (ObserverRegistry o) r Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol.Observer

Associated Types

data Pdu (ObserverRegistry o) r :: Type Source #

Show (Pdu (ObserverRegistry o) r) Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol.Observer

NFData (Pdu (ObserverRegistry o) r) Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol.Observer

Methods

rnf :: Pdu (ObserverRegistry o) r -> () #

data Pdu (ObserverRegistry o) r Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol.Observer

type ToPretty (ObserverRegistry o :: Type) Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol.Observer

type ToPretty (ObserverRegistry o :: Type) = PrettyParens ("observer registry" <:> ToPretty o)

data Observer o where Source #

Describes a process that observes another via Asynchronous Pdu messages.

An observer consists of a filter and a process id. The filter converts an observation to a message understood by the observer process, and the ProcessId is used to send the message.

Since: 0.16.0

Constructors

Observer :: (Tangible o, IsPdu p Asynchronous, Tangible (Endpoint p), Typeable p) => (o -> Maybe (Pdu p Asynchronous)) -> Endpoint p -> Observer o 
Instances
Eq (Observer o) Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol.Observer

Methods

(==) :: Observer o -> Observer o -> Bool #

(/=) :: Observer o -> Observer o -> Bool #

Ord (Observer o) Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol.Observer

Methods

compare :: Observer o -> Observer o -> Ordering #

(<) :: Observer o -> Observer o -> Bool #

(<=) :: Observer o -> Observer o -> Bool #

(>) :: Observer o -> Observer o -> Bool #

(>=) :: Observer o -> Observer o -> Bool #

max :: Observer o -> Observer o -> Observer o #

min :: Observer o -> Observer o -> Observer o #

Show (Observer o) Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol.Observer

Methods

showsPrec :: Int -> Observer o -> ShowS #

show :: Observer o -> String #

showList :: [Observer o] -> ShowS #

NFData o => NFData (Observer o) Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol.Observer

Methods

rnf :: Observer o -> () #

(NFData o, Show o, Typeable o, Typeable r) => IsPdu (Observer o) r Source #

A minimal Protocol for handling observations. This is one simple way of receiving observations - of course users can use any other Asynchronous Pdu message type for receiving observations.

Since: 0.16.0

Instance details

Defined in Control.Eff.Concurrent.Protocol.Observer

Associated Types

data Pdu (Observer o) r :: Type Source #

Show o => Show (Pdu (Observer o) r) Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol.Observer

Methods

showsPrec :: Int -> Pdu (Observer o) r -> ShowS #

show :: Pdu (Observer o) r -> String #

showList :: [Pdu (Observer o) r] -> ShowS #

NFData o => NFData (Pdu (Observer o) r) Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol.Observer

Methods

rnf :: Pdu (Observer o) r -> () #

data Pdu (Observer o) r Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol.Observer

data Pdu (Observer o) r where
type ToPretty (Observer o :: Type) Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol.Observer

type ToPretty (Observer o :: Type) = PrettyParens ("observing" <:> ToPretty o)

registerObserver :: (SetMember Process (Process q) r, HasCallStack, Member Interrupts r, TangibleObserver o, EmbedProtocol x (ObserverRegistry o), IsPdu x Asynchronous) => Observer o -> Endpoint x -> Eff r () Source #

And an Observer to the set of recipients for all observations reported by observed. Note that the observers are keyed by the observing process, i.e. a previous entry for the process contained in the Observer is overwritten. If you want multiple entries for a single process, just combine several filter functions.

Since: 0.16.0

handleObservations :: (HasCallStack, Typeable o, SetMember Process (Process q) r, NFData (Observer o)) => (o -> Eff r ()) -> Pdu (Observer o) Asynchronous -> Eff r () Source #

Based on the Pdu instance for Observer this simplified writing a callback handler for observations. In order to register to and ObserverRegistry use toObserver.

Since: 0.16.0

toObserverFor :: (TangibleObserver o, Typeable a, IsPdu a Asynchronous) => (o -> Pdu a Asynchronous) -> Endpoint a -> Observer o Source #

Create an Observer that conditionally accepts all observations of the given type and applies the given function to them; the function takes an observation and returns an Pdu cast that the observer server is compatible to.

Since: 0.16.0

handleObserverRegistration :: forall o q r. (HasCallStack, Typeable o, SetMember Process (Process q) r, Member (ObserverState o) r, Member Logs r) => Pdu (ObserverRegistry o) Asynchronous -> Eff r () Source #

Provide the implementation for the ObserverRegistry Protocol, this handled RegisterObserver and ForgetObserver messages. It also adds the ObserverState constraint to the effect list.

Since: 0.16.0

manageObservers :: Eff (ObserverState o ': r) a -> Eff r a Source #

Keep track of registered Observers.

Handle the ObserverState introduced by handleObserverRegistration.

Since: 0.16.0

emptyObservers :: Observers o Source #

The empty ObserverState

Since: 0.24.0

observed :: forall o r q. (SetMember Process (Process q) r, Member (ObserverState o) r, Member Interrupts r, TangibleObserver o) => o -> Eff r () Source #

Report an observation to all observers. The process needs to manageObservers and to handleObserverRegistration.

Since: 0.16.0

data ObservationQueue a Source #

Contains a TBQueue capturing observations. See spawnLinkObservationQueueWriter, readObservationQueue.

Instances
(TangibleObserver o, IsPdu (Observer o) Asynchronous, Lifted IO q, Member Logs q) => Server (ObservationQueue o) (Processes q) Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol.Observer.Queue

type Protocol (ObservationQueue o) Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol.Observer.Queue

type Model (ObservationQueue o) Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol.Observer.Queue

type Model (ObservationQueue o) = ()
type Settings (ObservationQueue o) Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol.Observer.Queue

data StartArgument (ObservationQueue o) (Processes q) Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol.Observer.Queue

readObservationQueue :: forall o r. (Member (ObservationQueueReader o) r, HasCallStack, MonadIO (Eff r), Typeable o, Member Logs r) => Eff r o Source #

Read queued observations captured and enqueued in the shared TBQueue by spawnLinkObservationQueueWriter. This blocks until something was captured or an interrupt or exceptions was thrown. For a non-blocking variant use tryReadObservationQueue or flushObservationQueue.

tryReadObservationQueue :: forall o r. (Member (ObservationQueueReader o) r, HasCallStack, MonadIO (Eff r), Typeable o, Member Logs r) => Eff r (Maybe o) Source #

Read queued observations captured and enqueued in the shared TBQueue by spawnLinkObservationQueueWriter. Return the oldest enqueued observation immediately or Nothing if the queue is empty. Use readObservationQueue to block until an observation is observed.

flushObservationQueue :: forall o r. (Member (ObservationQueueReader o) r, HasCallStack, MonadIO (Eff r), Typeable o, Member Logs r) => Eff r [o] Source #

Read at once all currently queued observations captured and enqueued in the shared TBQueue by spawnLinkObservationQueueWriter. This returns immediately all currently enqueued observations. For a blocking variant use readObservationQueue.

withObservationQueue :: forall o b e len. (HasCallStack, Typeable o, Show o, Member Logs e, Lifted IO e, Integral len, Member Interrupts e) => len -> Eff (ObservationQueueReader o ': e) b -> Eff e b Source #

Create a mutable queue for observations. Use spawnLinkObservationQueueWriter for a simple way to get a process that enqueues all observations.

Example

Expand
withObservationQueue 100 $ do
  q  <- ask @(ObservationQueue TestEvent)
  wq <- spawnLinkObservationQueueWriter q
  registerObserver wq testServer
  ...
  cast testServer DoSomething
  evt <- readObservationQueue @TestEvent
  ...

Since: 0.18.0

spawnLinkObservationQueueWriter :: forall o q h. (TangibleObserver o, IsPdu (Observer o) Asynchronous, Member Logs q, Lifted IO q, LogsTo h (Processes q), HasCallStack) => ObservationQueue o -> Eff (Processes q) (Observer o) Source #

Spawn a process that can be used as an Observer that enqueues the observations into an ObservationQueue. See withObservationQueue for an example.

The observations can be obtained by readObservationQueue. All observations are captured up to the queue size limit, such that the first message received will be first message returned by readObservationQueue.

Since: 0.18.0

type CaptureLogWriter = Writer LogMessage Source #

Alias for the Writer that contains the captured LogMessages from CaptureLogs.

newtype CaptureLogs a Source #

A LogWriter monad that provides pure logging by capturing via the Writer effect.

Constructors

MkCaptureLogs 
Instances
Monad CaptureLogs Source # 
Instance details

Defined in Control.Eff.LogWriter.Capture

Functor CaptureLogs Source # 
Instance details

Defined in Control.Eff.LogWriter.Capture

Methods

fmap :: (a -> b) -> CaptureLogs a -> CaptureLogs b #

(<$) :: a -> CaptureLogs b -> CaptureLogs a #

Applicative CaptureLogs Source # 
Instance details

Defined in Control.Eff.LogWriter.Capture

Methods

pure :: a -> CaptureLogs a #

(<*>) :: CaptureLogs (a -> b) -> CaptureLogs a -> CaptureLogs b #

liftA2 :: (a -> b -> c) -> CaptureLogs a -> CaptureLogs b -> CaptureLogs c #

(*>) :: CaptureLogs a -> CaptureLogs b -> CaptureLogs b #

(<*) :: CaptureLogs a -> CaptureLogs b -> CaptureLogs a #

Member CaptureLogWriter e => HandleLogWriter CaptureLogs e Source #

A LogWriter monad for pure logging.

The HandleLogWriter instance for this type assumes a Writer effect.

Instance details

Defined in Control.Eff.LogWriter.Capture

captureLogWriter :: LogWriter CaptureLogs Source #

A LogWriter monad that provides pure logging by capturing via the Writer effect.

See exampleLogCapture

runCaptureLogWriter :: Eff (CaptureLogWriter ': e) a -> Eff e (a, [LogMessage]) Source #

Run a Writer for LogMessages.

Such a Writer is needed to handle CaptureLogWriter

type LoggingAndIo = '[Logs, LogWriterReader IO, Lift IO] Source #

The concrete list of Effects for logging with an IO based LogWriter, and a LogWriterReader.

mkLogWriterIO :: HasCallStack => (LogMessage -> IO ()) -> LogWriter IO Source #

A LogWriter that uses an IO action to write the message.

This is just an alias for MkLogWriter but with IO as parameter. This reduces the need to apply something to the extra type argument @IO.

Example use cases for this function are the consoleLogWriter and the ioHandleLogWriter.

ioHandleLogWriter :: HasCallStack => Handle -> LogWriter IO Source #

A LogWriter that renders LogMessages to strings via renderLogMessageConsoleLog and prints them to an Handle using hPutStrLn.

withIoLogging Source #

Arguments

:: SetMember Lift (Lift IO) e 
=> LogWriter IO

The LogWriter that will be used to write log messages.

-> Text

The default application name to put into the lmAppName field.

-> Facility

The default RFC-5424 facility to put into the lmFacility field.

-> LogPredicate

The inital predicate for log messages, there are some pre-defined in Control.Eff.Log.Message

-> Eff (Logs ': (LogWriterReader IO ': e)) a 
-> Eff e a 

Enable logging to IO using the defaultIoLogWriter.

Example:

exampleWithIoLogging :: IO ()
exampleWithIoLogging =
    runLift
  $ withIoLogging debugTraceLogWriter
                  "my-app"
                  local7
                  (lmSeverityIsAtLeast informationalSeverity)
  $ logInfo "Oh, hi there"

defaultIoLogWriter Source #

Arguments

:: Text

The default application name to put into the lmAppName field.

-> Facility

The default RFC-5424 facility to put into the lmFacility field.

-> LogWriter IO

The IO based writer to decorate

-> LogWriter IO 

Decorate an IO based LogWriter to fill out these fields in LogMessages:

  • The messages will carry the given application name in the lmAppName field.
  • The lmTimestamp field contains the UTC time of the log event
  • The lmHostname field contains the FQDN of the current host
  • The lmFacility field contains the given Facility

It works by using mappingLogWriterM.

printLogMessage :: LogMessage -> IO () Source #

Render a LogMessage but set the timestamp and thread id fields.

withFileLogging Source #

Arguments

:: (Lifted IO e, MonadBaseControl IO (Eff e)) 
=> FilePath

Path to the log-file.

-> Text

The default application name to put into the lmAppName field.

-> Facility

The default RFC-5424 facility to put into the lmFacility field.

-> LogPredicate

The inital predicate for log messages, there are some pre-defined in Control.Eff.Log.Message

-> Eff (Logs ': (LogWriterReader IO ': e)) a 
-> Eff e a 

Enable logging to a file, with some LogMessage fields preset as described in withIoLogging.

If the file or its directory does not exist, it will be created.

Example:

exampleWithFileLogging :: IO ()
exampleWithFileLogging =
    runLift
  $ withFileLogging "/var/log/my-app.log" "my-app" local7 allLogMessages
  $ logInfo "Oh, hi there"

To vary the LogWriter use withIoLogging.

withFileLogWriter Source #

Arguments

:: (Lifted IO e, LogsTo IO e, MonadBaseControl IO (Eff e)) 
=> FilePath

Path to the log-file.

-> Eff e b 
-> Eff e b 

Enable logging to a file.

If the file or its directory does not exist, it will be created. Example:

exampleWithFileLogWriter :: IO ()
exampleWithFileLogWriter =
    runLift
  $ withSomeLogging @IO
  $ withFileLogWriter "test.log"
  $ logInfo "Oh, hi there"

withTraceLogging Source #

Arguments

:: Lifted IO e 
=> Text

The default application name to put into the lmAppName field.

-> Facility

The default RFC-5424 facility to put into the lmFacility field.

-> LogPredicate

The inital predicate for log messages, there are some pre-defined in Control.Eff.Log.Message

-> Eff (Logs ': (LogWriterReader IO ': e)) a 
-> Eff e a 

Enable logging via traceM using the debugTraceLogWriter, with some LogMessage fields preset as in withIoLogging.

Log messages are rendered using renderLogMessageConsoleLog.

Example:

exampleWithTraceLogging :: IO ()
exampleWithTraceLogging =
    runLift
  $ withTraceLogging "my-app" local7 allLogMessages
  $ logInfo "Oh, hi there"

withTraceLogWriter :: forall h e a. (Monad h, LogsTo h e) => Eff e a -> Eff e a Source #

Enable logging via traceM using the debugTraceLogWriter. The logging monad type can be any type with a Monad instance.

Log messages are rendered using renderLogMessageConsoleLog.

Example:

exampleWithTraceLogWriter :: IO ()
exampleWithTraceLogWriter =
    runLift
  $ withSomeLogging @IO
  $ withTraceLogWriter
  $ logInfo "Oh, hi there"

withConsoleLogging Source #

Arguments

:: Lifted IO e 
=> Text

The default application name to put into the lmAppName field.

-> Facility

The default RFC-5424 facility to put into the lmFacility field.

-> LogPredicate

The inital predicate for log messages, there are some pre-defined in Control.Eff.Log.Message

-> Eff (Logs ': (LogWriterReader IO ': e)) a 
-> Eff e a 

Enable logging to standard output using the consoleLogWriter, with some LogMessage fields preset as in withIoLogging.

Log messages are rendered using renderLogMessageConsoleLog.

Example:

exampleWithConsoleLogging :: IO ()
exampleWithConsoleLogging =
    runLift
  $ withConsoleLogging "my-app" local7 allLogMessages
  $ logInfo "Oh, hi there"

To vary the LogWriter use withIoLogging.

withConsoleLogWriter :: (LogsTo IO e, Lifted IO e) => Eff e a -> Eff e a Source #

Enable logging to standard output using the consoleLogWriter.

Log messages are rendered using renderLogMessageConsoleLog.

Example:

exampleWithConsoleLogWriter :: IO ()
exampleWithConsoleLogWriter =
    runLift
  $ withSomeLogging @IO
  $ withConsoleLogWriter
  $ logInfo "Oh, hi there"

withAsyncLogging Source #

Arguments

:: (Lifted IO e, MonadBaseControl IO (Eff e), Integral len) 
=> LogWriter IO 
-> len

Size of the log message input queue. If the queue is full, message are dropped silently.

-> Text

The default application name to put into the lmAppName field.

-> Facility

The default RFC-5424 facility to put into the lmFacility field.

-> LogPredicate

The inital predicate for log messages, there are some pre-defined in Control.Eff.Log.Message

-> Eff (Logs ': (LogWriterReader IO ': e)) a 
-> Eff e a 

This is a wrapper around withAsyncLogWriter and withIoLogging.

Example:

exampleWithAsyncLogging :: IO ()
exampleWithAsyncLogging =
    runLift
  $ withAsyncLogWriter consoleLogWriter (1000::Int) "my-app" local0 allLogMessages
  $ do logMsg "test 1"
       logMsg "test 2"
       logMsg "test 3"

withAsyncLogWriter Source #

Arguments

:: (LogsTo IO e, Lifted IO e, MonadBaseControl IO (Eff e), Integral len) 
=> len

Size of the log message input queue. If the queue is full, message are dropped silently.

-> Eff e a 
-> Eff e a 

Move the current LogWriter into its own thread.

A bounded queue is used to forward logs to the process.

If an exception is received, the logging process will be killed.

Log messages are deeply evaluated before being sent to the logger process, to prevent that lazy evaluation leads to heavy work being done in the logger process instead of the caller process.

Example:

exampleAsyncLogWriter :: IO ()
exampleAsyncLogWriter =
    runLift
  $ withLogging consoleLogWriter
  $ withAsyncLogWriter (1000::Int)
  $ do logMsg "test 1"
       logMsg "test 2"
       logMsg "test 3"

withUDPLogging Source #

Arguments

:: (HasCallStack, MonadBaseControl IO (Eff e), Lifted IO e) 
=> (LogMessage -> Text)

LogMessage rendering function

-> String

Hostname or IP

-> String

Port e.g. "514"

-> Text

The default application name to put into the lmAppName field.

-> Facility

The default RFC-5424 facility to put into the lmFacility field.

-> LogPredicate

The inital predicate for log messages, there are some pre-defined in Control.Eff.Log.Message

-> Eff (Logs ': (LogWriterReader IO ': e)) a 
-> Eff e a 

Enable logging to a remote host via UDP, with some LogMessage fields preset as in withIoLogging.

See exampleUdpRFC3164Logging

withUDPLogWriter Source #

Arguments

:: (Lifted IO e, LogsTo IO e, MonadBaseControl IO (Eff e), HasCallStack) 
=> (LogMessage -> Text)

LogMessage rendering function

-> String

Hostname or IP

-> String

Port e.g. "514"

-> Eff e b 
-> Eff e b 

Enable logging to a (remote-) host via UDP.

See exampleUdpRFC3164Logging

withUnixSocketLogging Source #

Arguments

:: (HasCallStack, MonadBaseControl IO (Eff e), Lifted IO e) 
=> LogMessageRenderer Text

LogMessage rendering function

-> FilePath

Path to the socket file

-> Text

The default application name to put into the lmAppName field.

-> Facility

The default RFC-5424 facility to put into the lmFacility field.

-> LogPredicate

The inital predicate for log messages, there are some pre-defined in Control.Eff.Log.Message

-> Eff (Logs ': (LogWriterReader IO ': e)) a 
-> Eff e a 

Enable logging to a unix domain socket, with some LogMessage fields preset as in withIoLogging.

See exampleDevLogSyslogLogging

withUnixSocketLogWriter Source #

Arguments

:: (Lifted IO e, LogsTo IO e, MonadBaseControl IO (Eff e), HasCallStack) 
=> LogMessageRenderer Text

LogMessage rendering function

-> FilePath

Path to the socket file

-> Eff e b 
-> Eff e b 

Enable logging to a (remote-) host via UnixSocket.

See exampleDevLogSyslogLogging

foreverCheap :: Monad m => m a -> m () Source #

A version of forever that hopefully tricks GHC into not creating a space leak. The intuition is, that we want to do something that is cheap, and hence should be recomputed instead of shared.

Since: 0.4.0.0

replicateCheapM_ :: Monad m => Int -> m a -> m () Source #

A version of replicateM_ that hopefully tricks GHC into not creating a space leak. The intuition is, that we want to do something that is cheap, and hence should be recomputed instead of shared.

Since: 0.4.0.0

Scheduler

schedule :: HasCallStack => LogWriter IO -> Eff Effects a -> IO (Either (Interrupt NoRecovery) a) Source #

Run the Effects using a single threaded, coroutine based, scheduler from Control.Eff.Concurrent.Process.SingleThreadedScheduler.

Since: 0.25.0

defaultMain :: HasCallStack => Eff EffectsIo () -> IO () Source #

Execute a Process using scheduleM on top of Lift IO. All logging is written to the console using consoleLogWriter.

To use another LogWriter use defaultMainWithLogWriter instead.

defaultMainWithLogWriter :: HasCallStack => LogWriter IO -> Eff EffectsIo () -> IO () Source #

Execute a Process using scheduleM on top of Lift IO. All logging is written using the given LogWriter.

Since: 0.25.0

type Effects = EffectsIo Source #

The effect list for Process effects in the single threaded scheduler.

See EffectsIo

Since: 0.25.0

type SafeEffects = SafeEffectsIo Source #

The effect list for Process effects in the single threaded scheduler. This is like SafeProcesses, no Interrupts are present.

See SafeEffectsIo

Since: 0.25.0

type BaseEffects = BaseEffectsIo Source #

The effect list for the underlying scheduler.

See BaseEffectsIo

Since: 0.25.0

type HasBaseEffects e = HasBaseEffectsIo e Source #

Constraint for the existence of the underlying scheduler effects.

See HasBaseEffectsIo

Since: 0.25.0

External Libraries