Safe Haskell | None |
---|---|
Language | Haskell2010 |
Synopsis
- module RIO.Prelude
- module RIO.Prelude.Types
- newtype RIO env a = RIO {}
- runRIO :: MonadIO m => env -> RIO env a -> m a
- liftRIO :: (MonadIO m, MonadReader env m) => RIO env a -> m a
- module RIO.Prelude.Simple
- module Control.Monad.IO.Unlift
- withLogFunc :: MonadUnliftIO m => LogOptions -> (LogFunc -> m a) -> m a
- newLogFunc :: (MonadIO n, MonadIO m) => LogOptions -> n (LogFunc, m ())
- data LogFunc
- class HasLogFunc env where
- logOptionsHandle :: MonadIO m => Handle -> Bool -> m LogOptions
- data LogOptions
- setLogMinLevel :: LogLevel -> LogOptions -> LogOptions
- setLogMinLevelIO :: IO LogLevel -> LogOptions -> LogOptions
- setLogVerboseFormat :: Bool -> LogOptions -> LogOptions
- setLogVerboseFormatIO :: IO Bool -> LogOptions -> LogOptions
- setLogTerminal :: Bool -> LogOptions -> LogOptions
- setLogUseTime :: Bool -> LogOptions -> LogOptions
- setLogUseColor :: Bool -> LogOptions -> LogOptions
- setLogUseLoc :: Bool -> LogOptions -> LogOptions
- setLogFormat :: (Utf8Builder -> Utf8Builder) -> LogOptions -> LogOptions
- setLogLevelColors :: (LogLevel -> Utf8Builder) -> LogOptions -> LogOptions
- setLogSecondaryColor :: Utf8Builder -> LogOptions -> LogOptions
- setLogAccentColors :: (Int -> Utf8Builder) -> LogOptions -> LogOptions
- logDebug :: (MonadIO m, MonadReader env m, HasLogFunc env, HasCallStack) => Utf8Builder -> m ()
- logInfo :: (MonadIO m, MonadReader env m, HasLogFunc env, HasCallStack) => Utf8Builder -> m ()
- logWarn :: (MonadIO m, MonadReader env m, HasLogFunc env, HasCallStack) => Utf8Builder -> m ()
- logError :: (MonadIO m, MonadReader env m, HasLogFunc env, HasCallStack) => Utf8Builder -> m ()
- logOther :: (MonadIO m, MonadReader env m, HasLogFunc env, HasCallStack) => Text -> Utf8Builder -> m ()
- logSticky :: (MonadIO m, HasCallStack, MonadReader env m, HasLogFunc env) => Utf8Builder -> m ()
- logStickyDone :: (MonadIO m, HasCallStack, MonadReader env m, HasLogFunc env) => Utf8Builder -> m ()
- logDebugS :: (MonadIO m, MonadReader env m, HasLogFunc env, HasCallStack) => LogSource -> Utf8Builder -> m ()
- logInfoS :: (MonadIO m, MonadReader env m, HasLogFunc env, HasCallStack) => LogSource -> Utf8Builder -> m ()
- logWarnS :: (MonadIO m, MonadReader env m, HasLogFunc env, HasCallStack) => LogSource -> Utf8Builder -> m ()
- logErrorS :: (MonadIO m, MonadReader env m, HasLogFunc env, HasCallStack) => LogSource -> Utf8Builder -> m ()
- logOtherS :: (MonadIO m, MonadReader env m, HasLogFunc env, HasCallStack) => Text -> LogSource -> Utf8Builder -> m ()
- logGeneric :: (MonadIO m, MonadReader env m, HasLogFunc env, HasCallStack) => LogSource -> LogLevel -> Utf8Builder -> m ()
- mkLogFunc :: (CallStack -> LogSource -> LogLevel -> Utf8Builder -> IO ()) -> LogFunc
- logOptionsMemory :: MonadIO m => m (IORef Builder, LogOptions)
- data LogLevel
- type LogSource = Text
- data CallStack
- displayCallStack :: CallStack -> Utf8Builder
- noLogging :: (HasLogFunc env, MonadReader env m) => m a -> m a
- logFuncUseColorL :: HasLogFunc env => SimpleGetter env Bool
- logFuncLogLevelColorsL :: HasLogFunc env => SimpleGetter env (LogLevel -> Utf8Builder)
- logFuncSecondaryColorL :: HasLogFunc env => SimpleGetter env Utf8Builder
- logFuncAccentColorsL :: HasLogFunc env => SimpleGetter env (Int -> Utf8Builder)
- glog :: (MonadIO m, HasCallStack, HasGLogFunc env, MonadReader env m) => GMsg env -> m ()
- data GLogFunc msg
- gLogFuncClassic :: (HasLogLevel msg, HasLogSource msg, Display msg) => LogFunc -> GLogFunc msg
- mkGLogFunc :: (CallStack -> msg -> IO ()) -> GLogFunc msg
- contramapMaybeGLogFunc :: (a -> Maybe b) -> GLogFunc b -> GLogFunc a
- contramapGLogFunc :: (a -> b) -> GLogFunc b -> GLogFunc a
- class HasGLogFunc env where
- class HasLogLevel msg where
- getLogLevel :: msg -> LogLevel
- class HasLogSource msg where
- getLogSource :: msg -> LogSource
- newtype Utf8Builder = Utf8Builder {}
- class Display a where
- display :: a -> Utf8Builder
- textDisplay :: a -> Text
- displayShow :: Show a => a -> Utf8Builder
- utf8BuilderToText :: Utf8Builder -> Text
- utf8BuilderToLazyText :: Utf8Builder -> Text
- displayBytesUtf8 :: ByteString -> Utf8Builder
- writeFileUtf8Builder :: MonadIO m => FilePath -> Utf8Builder -> m ()
- view :: MonadReader s m => Getting a s a -> m a
- preview :: MonadReader s m => Getting (First a) s a -> m (Maybe a)
- type ASetter s t a b = (a -> Identity b) -> s -> Identity t
- type ASetter' s a = ASetter s s a a
- type Getting r s a = (a -> Const r a) -> s -> Const r s
- type Lens s t a b = forall (f :: Type -> Type). Functor f => (a -> f b) -> s -> f t
- type Lens' s a = Lens s s a a
- type SimpleGetter s a = forall r. Getting r s a
- lens :: (s -> a) -> (s -> b -> t) -> Lens s t a b
- over :: ASetter s t a b -> (a -> b) -> s -> t
- set :: ASetter s t a b -> b -> s -> t
- sets :: ((a -> b) -> s -> t) -> ASetter s t a b
- to :: (s -> a) -> SimpleGetter s a
- (^.) :: s -> Getting a s a -> a
- (^?) :: s -> Getting (First a) s a -> Maybe a
- (^..) :: s -> Getting (Endo [a]) s a -> [a]
- (%~) :: ASetter s t a b -> (a -> b) -> s -> t
- (.~) :: ASetter s t a b -> b -> s -> t
- data ThreadId
- myThreadId :: MonadIO m => m ThreadId
- isCurrentThreadBound :: MonadIO m => m Bool
- threadWaitRead :: MonadIO m => Fd -> m ()
- threadWaitWrite :: MonadIO m => Fd -> m ()
- threadDelay :: MonadIO m => Int -> m ()
- yieldThread :: MonadIO m => m ()
- module UnliftIO.Async
- module UnliftIO.STM
- module UnliftIO.Chan
- module UnliftIO.Timeout
- module UnliftIO.Exception
- throwM :: (MonadThrow m, Exception e) => e -> m a
- module UnliftIO.IO
- module UnliftIO.Temporary
- withLazyFile :: MonadUnliftIO m => FilePath -> (ByteString -> m a) -> m a
- withLazyFileUtf8 :: MonadUnliftIO m => FilePath -> (Text -> m a) -> m a
- readFileBinary :: MonadIO m => FilePath -> m ByteString
- writeFileBinary :: MonadIO m => FilePath -> ByteString -> m ()
- readFileUtf8 :: MonadIO m => FilePath -> m Text
- writeFileUtf8 :: MonadIO m => FilePath -> Text -> m ()
- hPutBuilder :: MonadIO m => Handle -> Builder -> m ()
- exitFailure :: MonadIO m => m a
- exitSuccess :: MonadIO m => m a
- exitWith :: MonadIO m => ExitCode -> m a
- data ExitCode
- class HasWriteRef w env | env -> w where
- class HasStateRef s env | env -> s where
- data SomeRef a
- mapRIO :: (outer -> inner) -> RIO inner a -> RIO outer a
- readSomeRef :: MonadIO m => SomeRef a -> m a
- writeSomeRef :: MonadIO m => SomeRef a -> a -> m ()
- modifySomeRef :: MonadIO m => SomeRef a -> (a -> a) -> m ()
- newSomeRef :: MonadIO m => a -> m (SomeRef a)
- newUnboxedSomeRef :: (MonadIO m, Unbox a) => a -> m (SomeRef a)
- data URef s a
- type IOURef = URef (PrimState IO)
- newURef :: (PrimMonad m, Unbox a) => a -> m (URef (PrimState m) a)
- readURef :: (PrimMonad m, Unbox a) => URef (PrimState m) a -> m a
- writeURef :: (PrimMonad m, Unbox a) => URef (PrimState m) a -> a -> m ()
- modifyURef :: (PrimMonad m, Unbox a) => URef (PrimState m) a -> (a -> a) -> m ()
- module UnliftIO.IORef
- module UnliftIO.MVar
- module UnliftIO.QSem
- module UnliftIO.QSemN
- module UnliftIO.Memoize
- module RIO.Deque
- trace :: Text -> a -> a
- traceId :: Text -> Text
- traceIO :: MonadIO m => Text -> m ()
- traceM :: Applicative f => Text -> f ()
- traceEvent :: Text -> a -> a
- traceEventIO :: MonadIO m => Text -> m ()
- traceMarker :: Text -> a -> a
- traceMarkerIO :: MonadIO m => Text -> m ()
- traceStack :: Text -> a -> a
- traceShow :: Show a => a -> b -> b
- traceShowId :: Show a => a -> a
- traceShowIO :: (Show a, MonadIO m) => a -> m ()
- traceShowM :: (Show a, Applicative f) => a -> f ()
- traceShowEvent :: Show a => a -> b -> b
- traceShowEventIO :: (Show a, MonadIO m) => a -> m ()
- traceShowMarker :: Show a => a -> b -> b
- traceShowMarkerIO :: (Show a, MonadIO m) => a -> m ()
- traceShowStack :: Show a => a -> b -> b
- traceDisplay :: Display a => a -> b -> b
- traceDisplayId :: Display a => a -> a
- traceDisplayIO :: (Display a, MonadIO m) => a -> m ()
- traceDisplayM :: (Display a, Applicative f) => a -> f ()
- traceDisplayEvent :: Display a => a -> b -> b
- traceDisplayEventIO :: (Display a, MonadIO m) => a -> m ()
- traceDisplayMarker :: Display a => a -> b -> b
- traceDisplayMarkerIO :: (Display a, MonadIO m) => a -> m ()
- traceDisplayStack :: Display a => a -> b -> b
Custom Prelude
One of the core features of rio
is that it can be used as a Prelude
replacement. Therefore it is best to disable the default Prelude
with:
NoImplicitPrelude
pragma:
{-# LANGUAGE NoImplicitPrelude #-} import RIO
Some functions not exported here can be found in RIO.Partial:
fromJust
, read
, toEnum
, pred
, succ
.
module RIO.Prelude
module RIO.Prelude.Types
The RIO
Monad
The Reader+IO monad. This is different from a ReaderT
because:
- It's not a transformer, it hardcodes IO for simpler usage and error messages.
- Instances of typeclasses like
MonadLogger
are implemented using classes defined on the environment, instead of using an underlying monad.
Instances
MonadReader env (RIO env) Source # | |
HasStateRef s env => MonadState s (RIO env) Source # | |
(Monoid w, HasWriteRef w env) => MonadWriter w (RIO env) Source # | |
Monad (RIO env) Source # | |
Functor (RIO env) Source # | |
Applicative (RIO env) Source # | |
MonadIO (RIO env) Source # | |
Defined in RIO.Prelude.RIO | |
MonadThrow (RIO env) Source # | |
Defined in RIO.Prelude.RIO | |
PrimMonad (RIO env) Source # | |
MonadUnliftIO (RIO env) Source # | |
Defined in RIO.Prelude.RIO | |
Semigroup a => Semigroup (RIO env a) Source # | |
Monoid a => Monoid (RIO env a) Source # | |
type PrimState (RIO env) Source # | |
Defined in RIO.Prelude.RIO |
runRIO :: MonadIO m => env -> RIO env a -> m a Source #
Using the environment run in IO the action that requires that environment.
Since: 0.0.1.0
liftRIO :: (MonadIO m, MonadReader env m) => RIO env a -> m a Source #
Abstract RIO
to an arbitrary MonadReader
instance, which can handle IO.
Since: 0.0.1.0
SimpleApp
If all you need is just some default environment that does basic logging and allows
spawning processes, then you can use SimpleApp
:
{-# LANGUAGE OverloadedStrings #-} module Main where main :: IO () main = runSimpleApp $ do logInfo "Hello World!"
Note the OverloadedStrings extension, which is enabled to simplify logging.
module RIO.Prelude.Simple
MonadIO
and MonadUnliftIO
module Control.Monad.IO.Unlift
Logger
The logging system in RIO is built upon "log functions", which are accessed in RIO's environment via a class like "has log function". There are two provided:
- In the common case: for logging plain text (via
Utf8Builder
) efficiently, there isLogFunc
, which can be created viawithLogFunc
, and is accessed viaHasLogFunc
. This provides all the classical logging facilities: timestamped text output with log levels and colors (if terminal-supported) to the terminal. We log output vialogInfo
,logDebug
, etc. - In the advanced case: where logging takes on a more semantic
meaning and the logs need to be digested, acted upon, translated
or serialized upstream (to e.g. a JSON logging server), we have
GLogFunc
(as in "generic log function"), and is accessed viaHasGLogFunc
. In this case, we log output viaglog
. See the Type-generic logger section for more information.
Running with logging
withLogFunc :: MonadUnliftIO m => LogOptions -> (LogFunc -> m a) -> m a Source #
Given a LogOptions
value, run the given function with the
specified LogFunc
. A common way to use this function is:
let isVerbose = False -- get from the command line instead logOptions' <- logOptionsHandle stderr isVerbose let logOptions = setLogUseTime True logOptions' withLogFunc logOptions $ \lf -> do let app = App -- application specific environment { appLogFunc = lf , appOtherStuff = ... } runRIO app $ do logInfo "Starting app" myApp
Since: 0.0.0.0
newLogFunc :: (MonadIO n, MonadIO m) => LogOptions -> n (LogFunc, m ()) Source #
Given a LogOptions
value, returns both a new LogFunc
and a sub-routine that
disposes it.
Intended for use if you want to deal with the teardown of LogFunc
yourself,
otherwise prefer the withLogFunc
function instead.
Since: 0.1.3.0
A logging function, wrapped in a newtype for better error messages.
An implementation may choose any behavior of this value it wishes, including printing to standard output or no action at all.
Since: 0.0.0.0
class HasLogFunc env where Source #
Environment values with a logging function.
Since: 0.0.0.0
Instances
:: MonadIO m | |
=> Handle | |
-> Bool | Verbose Flag |
-> m LogOptions |
Create a LogOptions
value from the given Handle
and whether
to perform verbose logging or not. Individiual settings can be
overridden using appropriate set
functions.
Logging output is guaranteed to be non-interleaved only for a
UTF-8 Handle
in a multi-thread environment.
When Verbose Flag is True
, the following happens:
setLogVerboseFormat
is called withTrue
setLogUseColor
is called withTrue
(except on Windows)setLogUseLoc
is called withTrue
setLogUseTime
is called withTrue
setLogMinLevel
is called withDebug
log level
Since: 0.0.0.0
Log options
data LogOptions Source #
Configuration for how to create a LogFunc
. Intended to be used
with the withLogFunc
function.
Since: 0.0.0.0
setLogMinLevel :: LogLevel -> LogOptions -> LogOptions Source #
Set the minimum log level. Messages below this level will not be printed.
Default: in verbose mode, LevelDebug
. Otherwise, LevelInfo
.
Since: 0.0.0.0
setLogMinLevelIO :: IO LogLevel -> LogOptions -> LogOptions Source #
Refer to setLogMinLevel
. This modifier allows to alter the verbose format
value dynamically at runtime.
Default: in verbose mode, LevelDebug
. Otherwise, LevelInfo
.
Since: 0.1.3.0
setLogVerboseFormat :: Bool -> LogOptions -> LogOptions Source #
Use the verbose format for printing log messages.
Default: follows the value of the verbose flag.
Since: 0.0.0.0
setLogVerboseFormatIO :: IO Bool -> LogOptions -> LogOptions Source #
Refer to setLogVerboseFormat
. This modifier allows to alter the verbose
format value dynamically at runtime.
Default: follows the value of the verbose flag.
Since: 0.1.3.0
setLogTerminal :: Bool -> LogOptions -> LogOptions Source #
Do we treat output as a terminal. If True
, we will enable
sticky logging functionality.
Default: checks if the Handle
provided to logOptionsHandle
is a
terminal with hIsTerminalDevice
.
Since: 0.0.0.0
setLogUseTime :: Bool -> LogOptions -> LogOptions Source #
setLogUseColor :: Bool -> LogOptions -> LogOptions Source #
setLogUseLoc :: Bool -> LogOptions -> LogOptions Source #
setLogFormat :: (Utf8Builder -> Utf8Builder) -> LogOptions -> LogOptions Source #
setLogLevelColors :: (LogLevel -> Utf8Builder) -> LogOptions -> LogOptions Source #
ANSI color codes for LogLevel
in the log output.
Default: LevelDebug
= "\ESC[32m" -- Green
LevelInfo
= "\ESC[34m" -- Blue
LevelWarn
= "\ESC[33m" -- Yellow
LevelError
= "\ESC[31m" -- Red
LevelOther
_ = "\ESC[35m" -- Magenta
Since: 0.1.18.0
setLogSecondaryColor :: Utf8Builder -> LogOptions -> LogOptions Source #
ANSI color codes for secondary content in the log output.
Default: "\ESC[90m" -- Bright black (gray)
Since: 0.1.18.0
:: (Int -> Utf8Builder) | This should be a total function. |
-> LogOptions | |
-> LogOptions |
Standard logging functions
logDebug :: (MonadIO m, MonadReader env m, HasLogFunc env, HasCallStack) => Utf8Builder -> m () Source #
Log a debug level message with no source.
Since: 0.0.0.0
logInfo :: (MonadIO m, MonadReader env m, HasLogFunc env, HasCallStack) => Utf8Builder -> m () Source #
Log an info level message with no source.
Since: 0.0.0.0
logWarn :: (MonadIO m, MonadReader env m, HasLogFunc env, HasCallStack) => Utf8Builder -> m () Source #
Log a warn level message with no source.
Since: 0.0.0.0
logError :: (MonadIO m, MonadReader env m, HasLogFunc env, HasCallStack) => Utf8Builder -> m () Source #
Log an error level message with no source.
Since: 0.0.0.0
:: (MonadIO m, MonadReader env m, HasLogFunc env, HasCallStack) | |
=> Text | level |
-> Utf8Builder | |
-> m () |
Log a message with the specified textual level and no source.
Since: 0.0.0.0
Advanced logging functions
Sticky logging
logSticky :: (MonadIO m, HasCallStack, MonadReader env m, HasLogFunc env) => Utf8Builder -> m () Source #
Write a "sticky" line to the terminal. Any subsequent lines will
overwrite this one, and that same line will be repeated below
again. In other words, the line sticks at the bottom of the output
forever. Running this function again will replace the sticky line
with a new sticky line. When you want to get rid of the sticky
line, run logStickyDone
.
Note that not all LogFunc
implementations will support sticky
messages as described. However, the withLogFunc
implementation
provided by this module does.
Since: 0.0.0.0
logStickyDone :: (MonadIO m, HasCallStack, MonadReader env m, HasLogFunc env) => Utf8Builder -> m () Source #
This will print out the given message with a newline and disable
any further stickiness of the line until a new call to logSticky
happens.
Since: 0.0.0.0
With source
There is a set of logging functions that take an extra LogSource
argument to provide context, typically detailing what part of an
application the message comes from.
For example, in verbose mode, infoLogS "database" "connected"
will
result in
[info] (database) connected
logDebugS :: (MonadIO m, MonadReader env m, HasLogFunc env, HasCallStack) => LogSource -> Utf8Builder -> m () Source #
Log a debug level message with the given source.
Since: 0.0.0.0
logInfoS :: (MonadIO m, MonadReader env m, HasLogFunc env, HasCallStack) => LogSource -> Utf8Builder -> m () Source #
Log an info level message with the given source.
Since: 0.0.0.0
logWarnS :: (MonadIO m, MonadReader env m, HasLogFunc env, HasCallStack) => LogSource -> Utf8Builder -> m () Source #
Log a warn level message with the given source.
Since: 0.0.0.0
logErrorS :: (MonadIO m, MonadReader env m, HasLogFunc env, HasCallStack) => LogSource -> Utf8Builder -> m () Source #
Log an error level message with the given source.
Since: 0.0.0.0
:: (MonadIO m, MonadReader env m, HasLogFunc env, HasCallStack) | |
=> Text | level |
-> LogSource | |
-> Utf8Builder | |
-> m () |
Log a message with the specified textual level and the given source.
Since: 0.0.0.0
Generic log function
logGeneric :: (MonadIO m, MonadReader env m, HasLogFunc env, HasCallStack) => LogSource -> LogLevel -> Utf8Builder -> m () Source #
Generic, basic function for creating other logging functions.
Since: 0.0.0.0
Advanced running functions
mkLogFunc :: (CallStack -> LogSource -> LogLevel -> Utf8Builder -> IO ()) -> LogFunc Source #
Create a LogFunc
from the given function.
Since: 0.0.0.0
logOptionsMemory :: MonadIO m => m (IORef Builder, LogOptions) Source #
Create a LogOptions
value which will store its data in
memory. This is primarily intended for testing purposes. This will
return both a LogOptions
value and an IORef
containing the
resulting Builder
value.
This will default to non-verbose settings and assume there is a
terminal attached. These assumptions can be overridden using the
appropriate set
functions.
Since: 0.0.0.0
Data types
The log level of a message.
Since: 0.0.0.0
type LogSource = Text Source #
Where in the application a log message came from. Used for display purposes only.
Since: 0.0.0.0
CallStack
s are a lightweight method of obtaining a
partial call-stack at any point in the program.
A function can request its call-site with the HasCallStack
constraint.
For example, we can define
putStrLnWithCallStack :: HasCallStack => String -> IO ()
as a variant of putStrLn
that will get its call-site and print it,
along with the string given as argument. We can access the
call-stack inside putStrLnWithCallStack
with callStack
.
putStrLnWithCallStack :: HasCallStack => String -> IO () putStrLnWithCallStack msg = do putStrLn msg putStrLn (prettyCallStack callStack)
Thus, if we call putStrLnWithCallStack
we will get a formatted call-stack
alongside our string.
>>>
putStrLnWithCallStack "hello"
hello CallStack (from HasCallStack): putStrLnWithCallStack, called at <interactive>:2:1 in interactive:Ghci1
GHC solves HasCallStack
constraints in three steps:
- If there is a
CallStack
in scope -- i.e. the enclosing function has aHasCallStack
constraint -- GHC will append the new call-site to the existingCallStack
. - If there is no
CallStack
in scope -- e.g. in the GHCi session above -- and the enclosing definition does not have an explicit type signature, GHC will infer aHasCallStack
constraint for the enclosing definition (subject to the monomorphism restriction). - If there is no
CallStack
in scope and the enclosing definition has an explicit type signature, GHC will solve theHasCallStack
constraint for the singletonCallStack
containing just the current call-site.
CallStack
s do not interact with the RTS and do not require compilation
with -prof
. On the other hand, as they are built up explicitly via the
HasCallStack
constraints, they will generally not contain as much
information as the simulated call-stacks maintained by the RTS.
A CallStack
is a [(String, SrcLoc)]
. The String
is the name of
function that was called, the SrcLoc
is the call-site. The list is
ordered with the most recently called function at the head.
NOTE: The intrepid user may notice that HasCallStack
is just an
alias for an implicit parameter ?callStack :: CallStack
. This is an
implementation detail and should not be considered part of the
CallStack
API, we may decide to change the implementation in the
future.
Since: base-4.8.1.0
Convenience functions
displayCallStack :: CallStack -> Utf8Builder Source #
Convert a CallStack
value into a Utf8Builder
indicating
the first source location.
TODO Consider showing the entire call stack instead.
Since: 0.0.0.0
noLogging :: (HasLogFunc env, MonadReader env m) => m a -> m a Source #
Disable logging capabilities in a given sub-routine
Intended to skip logging in general purpose implementations, where secrets might be logged accidently.
Since: 0.1.5.0
Accessors
logFuncUseColorL :: HasLogFunc env => SimpleGetter env Bool Source #
Is the log func configured to use color output?
Intended for use by code which wants to optionally add additional color to its log messages.
Since: 0.1.0.0
logFuncLogLevelColorsL :: HasLogFunc env => SimpleGetter env (LogLevel -> Utf8Builder) Source #
What color is the log func configured to use for each LogLevel
?
Intended for use by code which wants to optionally add additional color to its log messages.
Since: 0.1.18.0
logFuncSecondaryColorL :: HasLogFunc env => SimpleGetter env Utf8Builder Source #
What color is the log func configured to use for secondary content?
Intended for use by code which wants to optionally add additional color to its log messages.
Since: 0.1.18.0
logFuncAccentColorsL :: HasLogFunc env => SimpleGetter env (Int -> Utf8Builder) Source #
What accent colors, indexed by Int
, is the log func configured to use?
Intended for use by code which wants to optionally add additional color to its log messages.
Since: 0.1.18.0
Type-generic logger
When logging takes on a more semantic meaning and the logs need to
be digested, acted upon, translated or serialized upstream (to
e.g. a JSON logging server), we have GLogFunc
(as in "generic log
function"), and is accessed via HasGLogFunc
.
There is only one function to log in this system: the glog
function, which can log any message. You determine the log levels
or severity of messages when needed.
Using mapRIO
and contramapGLogFunc
(or
contramapMaybeGLogFunc
), you can build hierarchies of loggers.
Example:
import RIO data DatabaseMsg = Connected String | Query String | Disconnected deriving Show data WebMsg = Request String | Error String | DatabaseMsg DatabaseMsg deriving Show data AppMsg = InitMsg String | WebMsg WebMsg deriving Show main :: IO () main = runRIO (mkGLogFunc (stack msg -> print msg)) (do glog (InitMsg "Ready to go!") runWeb (do glog (Request "/foo") runDB (do glog (Connected "127.0.0.1") glog (Query "SELECT 1")) glog (Error "Oh noes!"))) runDB :: RIO (GLogFunc DatabaseMsg) () -> RIO (GLogFunc WebMsg) () runDB = mapRIO (contramapGLogFunc DatabaseMsg) runWeb :: RIO (GLogFunc WebMsg) () -> RIO (GLogFunc AppMsg) () runWeb = mapRIO (contramapGLogFunc WebMsg)
If we instead decided that we only wanted to log database queries,
and not bother the upstream with connect/disconnect messages, we
could simplify the constructor to DatabaseQuery String
:
data WebMsg = Request String | Error String | DatabaseQuery String deriving Show
And then runDB
could use contramapMaybeGLogFunc
to parse only queries:
runDB = mapRIO (contramapMaybeGLogFunc (msg -> case msg of Query string -> pure (DatabaseQuery string) _ -> Nothing))
This way, upstream only has to care about queries and not connect/disconnect constructors.
glog :: (MonadIO m, HasCallStack, HasGLogFunc env, MonadReader env m) => GMsg env -> m () Source #
Log a value generically.
Since: 0.1.13.0
A generic logger of some type msg
.
Your GLocFunc
can re-use the existing classical logging framework
of RIO, and/or implement additional transforms,
filters. Alternatively, you may log to a JSON source in a database,
or anywhere else as needed. You can decide how to log levels or
severities based on the constructors in your type. You will
normally determine this in your main app entry point.
Since: 0.1.13.0
Instances
Contravariant GLogFunc Source # | Use this instance to wrap sub-loggers via The Since: 0.1.13.0 |
Semigroup (GLogFunc msg) Source # | Perform both sets of actions per log entry. Since: 0.1.13.0 |
Monoid (GLogFunc msg) Source # |
Since: 0.1.13.0 |
HasGLogFunc (GLogFunc msg) Source # | Quick way to run a RIO that only has a logger in its environment. Since: 0.1.13.0 |
type GMsg (GLogFunc msg) Source # | |
Defined in RIO.Prelude.Logger |
gLogFuncClassic :: (HasLogLevel msg, HasLogSource msg, Display msg) => LogFunc -> GLogFunc msg Source #
mkGLogFunc :: (CallStack -> msg -> IO ()) -> GLogFunc msg Source #
Make a custom generic logger. With this you could, for example, write to a database or a log digestion service. For example:
mkGLogFunc (\stack msg -> send (Data.Aeson.encode (JsonLog stack msg)))
Since: 0.1.13.0
contramapMaybeGLogFunc :: (a -> Maybe b) -> GLogFunc b -> GLogFunc a Source #
A vesion of contramapMaybeGLogFunc
which supports filering.
Since: 0.1.13.0
contramapGLogFunc :: (a -> b) -> GLogFunc b -> GLogFunc a Source #
class HasGLogFunc env where Source #
An app is capable of generic logging if it implements this.
Since: 0.1.13.0
class HasLogLevel msg where Source #
Level, if any, of your logs. If unknown, use LogOther
. Use for
your generic log data types that want to sit inside the classic log
framework.
Since: 0.1.13.0
getLogLevel :: msg -> LogLevel Source #
class HasLogSource msg where Source #
Source of a log. This can be whatever you want. Use for your generic log data types that want to sit inside the classic log framework.
Since: 0.1.13.0
getLogSource :: msg -> LogSource Source #
Display
newtype Utf8Builder Source #
A builder of binary data, with the invariant that the underlying data is supposed to be UTF-8 encoded.
Since: 0.1.0.0
Instances
IsString Utf8Builder Source # | Since: 0.1.0.0 |
Defined in RIO.Prelude.Display fromString :: String -> Utf8Builder # | |
Semigroup Utf8Builder Source # | |
Defined in RIO.Prelude.Display (<>) :: Utf8Builder -> Utf8Builder -> Utf8Builder # sconcat :: NonEmpty Utf8Builder -> Utf8Builder # stimes :: Integral b => b -> Utf8Builder -> Utf8Builder # | |
Monoid Utf8Builder Source # | |
Defined in RIO.Prelude.Display mempty :: Utf8Builder # mappend :: Utf8Builder -> Utf8Builder -> Utf8Builder # mconcat :: [Utf8Builder] -> Utf8Builder # | |
Display Utf8Builder Source # | Since: 0.1.0.0 |
Defined in RIO.Prelude.Display display :: Utf8Builder -> Utf8Builder Source # textDisplay :: Utf8Builder -> Text Source # |
class Display a where Source #
A typeclass for values which can be converted to a
Utf8Builder
. The intention of this typeclass is to provide a
human-friendly display of the data.
Since: 0.1.0.0
display :: a -> Utf8Builder Source #
textDisplay :: a -> Text Source #
Instances
displayShow :: Show a => a -> Utf8Builder Source #
Use the Show
instance for a value to convert it to a
Utf8Builder
.
Since: 0.1.0.0
utf8BuilderToText :: Utf8Builder -> Text Source #
Convert a Utf8Builder
value into a strict Text
.
Since: 0.1.0.0
utf8BuilderToLazyText :: Utf8Builder -> Text Source #
Convert a Utf8Builder
value into a lazy Text
.
Since: 0.1.0.0
displayBytesUtf8 :: ByteString -> Utf8Builder Source #
Convert a ByteString
into a Utf8Builder
.
NOTE This function performs no checks to ensure that the data is, in fact, UTF8 encoded. If you provide non-UTF8 data, later functions may fail.
Since: 0.1.0.0
writeFileUtf8Builder :: MonadIO m => FilePath -> Utf8Builder -> m () Source #
Write the given Utf8Builder
value to a file.
Since: 0.1.0.0
Optics
microlens
-based Lenses, Traversals, etc.
view :: MonadReader s m => Getting a s a -> m a #
view
is a synonym for (^.
), generalised for MonadReader
(we are able to use it instead of (^.
) since functions are instances of the MonadReader
class):
>>>
view _1 (1, 2)
1
When you're using Reader
for config and your config type has lenses generated for it, most of the time you'll be using view
instead of asks
:
doSomething :: (MonadReader
Config m) => m Int doSomething = do thingy <-view
setting1 -- same as “asks
(^.
setting1)” anotherThingy <-view
setting2 ...
preview :: MonadReader s m => Getting (First a) s a -> m (Maybe a) #
preview
is a synonym for (^?
), generalised for MonadReader
(just like view
, which is a synonym for (^.
)).
>>>
preview each [1..5]
Just 1
type ASetter s t a b = (a -> Identity b) -> s -> Identity t #
ASetter s t a b
is something that turns a function modifying a value into a function modifying a structure. If you ignore Identity
(as Identity a
is the same thing as a
), the type is:
type ASetter s t a b = (a -> b) -> s -> t
The reason Identity
is used here is for ASetter
to be composable with other types, such as Lens
.
Technically, if you're writing a library, you shouldn't use this type for setters you are exporting from your library; the right type to use is Setter
, but it is not provided by this package (because then it'd have to depend on distributive). It's completely alright, however, to export functions which take an ASetter
as an argument.
type Getting r s a = (a -> Const r a) -> s -> Const r s #
Functions that operate on getters and folds – such as (^.
), (^..
), (^?
) – use Getter r s a
(with different values of r
) to describe what kind of result they need. For instance, (^.
) needs the getter to be able to return a single value, and so it accepts a getter of type Getting a s a
. (^..
) wants the getter to gather values together, so it uses Getting (Endo [a]) s a
(it could've used Getting [a] s a
instead, but it's faster with Endo
). The choice of r
depends on what you want to do with elements you're extracting from s
.
type Lens s t a b = forall (f :: Type -> Type). Functor f => (a -> f b) -> s -> f t #
Lens s t a b
is the lowest common denominator of a setter and a getter, something that has the power of both; it has a Functor
constraint, and since both Const
and Identity
are functors, it can be used whenever a getter or a setter is needed.
a
is the type of the value inside of structureb
is the type of the replaced values
is the type of the whole structuret
is the type of the structure after replacinga
in it withb
type Lens' s a = Lens s s a a #
This is a type alias for monomorphic lenses which don't change the type of the container (or of the value inside).
type SimpleGetter s a = forall r. Getting r s a #
A SimpleGetter s a
extracts a
from s
; so, it's the same thing as (s -> a)
, but you can use it in lens chains because its type looks like this:
type SimpleGetter s a = forall r. (a -> Const r a) -> s -> Const r s
Since Const r
is a functor, SimpleGetter
has the same shape as other lens types and can be composed with them. To get (s -> a)
out of a SimpleGetter
, choose r ~ a
and feed Const :: a -> Const a a
to the getter:
-- the actual signature is more permissive: --view
::Getting
a s a -> s -> aview
::SimpleGetter
s a -> s -> aview
getter =getConst
. getterConst
The actual Getter
from lens is more general:
type Getter s a = forall f. (Contravariant f, Functor f) => (a -> f a) -> s -> f s
I'm not currently aware of any functions that take lens's Getter
but won't accept SimpleGetter
, but you should try to avoid exporting SimpleGetter
s anyway to minimise confusion. Alternatively, look at microlens-contra, which provides a fully lens-compatible Getter
.
Lens users: you can convert a SimpleGetter
to Getter
by applying to . view
to it.
lens :: (s -> a) -> (s -> b -> t) -> Lens s t a b #
lens
creates a Lens
from a getter and a setter. The resulting lens isn't the most effective one (because of having to traverse the structure twice when modifying), but it shouldn't matter much.
A (partial) lens for list indexing:
ix :: Int ->Lens'
[a] a ix i =lens
(!!
i) -- getter (\s b -> take i s ++ b : drop (i+1) s) -- setter
Usage:
>>> [1..9]^.
ix 3 4 >>> [1..9] & ix 3%~
negate [1,2,3,-4,5,6,7,8,9]
When getting, the setter is completely unused; when setting, the getter is unused. Both are used only when the value is being modified. For instance, here we define a lens for the 1st element of a list, but instead of a legitimate getter we use undefined
. Then we use the resulting lens for setting and it works, which proves that the getter wasn't used:
>>>
[1,2,3] & lens undefined (\s b -> b : tail s) .~ 10
[10,2,3]
over :: ASetter s t a b -> (a -> b) -> s -> t #
Getting fmap
in a roundabout way:
over
mapped
::Functor
f => (a -> b) -> f a -> f bover
mapped
=fmap
Applying a function to both components of a pair:
over
both
:: (a -> b) -> (a, a) -> (b, b)over
both
= \f t -> (f (fst t), f (snd t))
Using
as a replacement for over
_2
second
:
>>>
over _2 show (10,20)
(10,"20")
to :: (s -> a) -> SimpleGetter s a #
to
creates a getter from any function:
a^.
to
f = f a
It's most useful in chains, because it lets you mix lenses and ordinary functions. Suppose you have a record which comes from some third-party library and doesn't have any lens accessors. You want to do something like this:
value ^. _1 . field . at 2
However, field
isn't a getter, and you have to do this instead:
field (value ^. _1) ^. at 2
but now value
is in the middle and it's hard to read the resulting code. A variant with to
is prettier and more readable:
value ^. _1 . to field . at 2
(^.) :: s -> Getting a s a -> a infixl 8 #
(^.
) applies a getter to a value; in other words, it gets a value out of a structure using a getter (which can be a lens, traversal, fold, etc.).
Getting 1st field of a tuple:
(^.
_1
) :: (a, b) -> a (^.
_1
) =fst
When (^.
) is used with a traversal, it combines all results using the Monoid
instance for the resulting type. For instance, for lists it would be simple concatenation:
>>>
("str","ing") ^. each
"string"
The reason for this is that traversals use Applicative
, and the Applicative
instance for Const
uses monoid concatenation to combine “effects” of Const
.
A non-operator version of (^.
) is called view
, and it's a bit more general than (^.
) (it works in MonadReader
). If you need the general version, you can get it from microlens-mtl; otherwise there's view
available in Lens.Micro.Extras.
(^?) :: s -> Getting (First a) s a -> Maybe a infixl 8 #
s ^? t
returns the 1st element t
returns, or Nothing
if t
doesn't return anything. It's trivially implemented by passing the First
monoid to the getter.
Safe head
:
>>>
[] ^? each
Nothing
>>>
[1..3] ^? each
Just 1
>>>
Left 1 ^? _Right
Nothing
>>>
Right 1 ^? _Right
Just 1
A non-operator version of (^?
) is called preview
, and – like view
– it's a bit more general than (^?
) (it works in MonadReader
). If you need the general version, you can get it from microlens-mtl; otherwise there's preview
available in Lens.Micro.Extras.
(^..) :: s -> Getting (Endo [a]) s a -> [a] infixl 8 #
s ^.. t
returns the list of all values that t
gets from s
.
A Maybe
contains either 0 or 1 values:
>>>
Just 3 ^.. _Just
[3]
Gathering all values in a list of tuples:
>>>
[(1,2),(3,4)] ^.. each.each
[1,2,3,4]
(%~) :: ASetter s t a b -> (a -> b) -> s -> t infixr 4 #
(%~
) applies a function to the target; an alternative explanation is that it is an inverse of sets
, which turns a setter into an ordinary function.
is the same thing as mapped
%~
reverse
.fmap
reverse
See over
if you want a non-operator synonym.
Negating the 1st element of a pair:
>>>
(1,2) & _1 %~ negate
(-1,2)
Turning all Left
s in a list to upper case:
>>>
(mapped._Left.mapped %~ toUpper) [Left "foo", Right "bar"]
[Left "FOO",Right "bar"]
Concurrency
A ThreadId
is an abstract type representing a handle to a thread.
ThreadId
is an instance of Eq
, Ord
and Show
, where
the Ord
instance implements an arbitrary total ordering over
ThreadId
s. The Show
instance lets you convert an arbitrary-valued
ThreadId
to string form; showing a ThreadId
value is occasionally
useful when debugging or diagnosing the behaviour of a concurrent
program.
Note: in GHC, if you have a ThreadId
, you essentially have
a pointer to the thread itself. This means the thread itself can't be
garbage collected until you drop the ThreadId
.
This misfeature will hopefully be corrected at a later date.
Instances
Eq ThreadId | Since: base-4.2.0.0 |
Ord ThreadId | Since: base-4.2.0.0 |
Defined in GHC.Conc.Sync | |
Show ThreadId | Since: base-4.2.0.0 |
NFData ThreadId | Since: deepseq-1.4.0.0 |
Defined in Control.DeepSeq | |
Hashable ThreadId | |
Defined in Data.Hashable.Class |
myThreadId :: MonadIO m => m ThreadId #
Lifted version of myThreadId
.
Since: unliftio-0.1.1.0
isCurrentThreadBound :: MonadIO m => m Bool #
Lifted version of isCurrentThreadBound
.
Since: unliftio-0.1.1.0
threadWaitRead :: MonadIO m => Fd -> m () #
Lifted version of threadWaitRead
.
Since: unliftio-0.1.1.0
threadWaitWrite :: MonadIO m => Fd -> m () #
Lifted version of threadWaitWrite
.
Since: unliftio-0.1.1.0
threadDelay :: MonadIO m => Int -> m () #
Lifted version of threadDelay
.
Since: unliftio-0.1.1.0
yieldThread :: MonadIO m => m () Source #
Async
module UnliftIO.Async
STM
module UnliftIO.STM
Chan
module UnliftIO.Chan
Timeout
module UnliftIO.Timeout
Exceptions
module UnliftIO.Exception
Re-exported from Control.Monad.Catch:
throwM :: (MonadThrow m, Exception e) => e -> m a #
Throw an exception. Note that this throws when this action is run in
the monad m
, not when it is applied. It is a generalization of
Control.Exception's throwIO
.
Should satisfy the law:
throwM e >> f = throwM e
Files and handles
module UnliftIO.IO
module UnliftIO.Temporary
withLazyFile :: MonadUnliftIO m => FilePath -> (ByteString -> m a) -> m a Source #
Lazily get the contents of a file. Unlike readFile
, this
ensures that if an exception is thrown, the file handle is closed
immediately.
withLazyFileUtf8 :: MonadUnliftIO m => FilePath -> (Text -> m a) -> m a Source #
Lazily read a file in UTF8 encoding.
Since: 0.1.13
readFileBinary :: MonadIO m => FilePath -> m ByteString Source #
writeFileBinary :: MonadIO m => FilePath -> ByteString -> m () Source #
readFileUtf8 :: MonadIO m => FilePath -> m Text Source #
Read a file in UTF8 encoding, throwing an exception on invalid character encoding.
This function will use OS-specific line ending handling.
writeFileUtf8 :: MonadIO m => FilePath -> Text -> m () Source #
Write a file in UTF8 encoding
This function will use OS-specific line ending handling.
Exit
exitFailure :: MonadIO m => m a Source #
Lifted version of "System.Exit.exitFailure".
@since 0.1.9.0.
exitSuccess :: MonadIO m => m a Source #
Lifted version of "System.Exit.exitSuccess".
@since 0.1.9.0.
exitWith :: MonadIO m => ExitCode -> m a Source #
Lifted version of "System.Exit.exitWith".
@since 0.1.9.0.
Defines the exit codes that a program can return.
ExitSuccess | indicates successful termination; |
ExitFailure Int | indicates program failure with an exit code. The exact interpretation of the code is operating-system dependent. In particular, some values may be prohibited (e.g. 0 on a POSIX-compliant system). |
Instances
Eq ExitCode | |
Ord ExitCode | |
Defined in GHC.IO.Exception | |
Read ExitCode | |
Show ExitCode | |
Generic ExitCode | |
Exception ExitCode | Since: base-4.1.0.0 |
Defined in GHC.IO.Exception toException :: ExitCode -> SomeException # fromException :: SomeException -> Maybe ExitCode # displayException :: ExitCode -> String # | |
NFData ExitCode | Since: deepseq-1.4.2.0 |
Defined in Control.DeepSeq | |
type Rep ExitCode | |
Defined in GHC.IO.Exception type Rep ExitCode = D1 ('MetaData "ExitCode" "GHC.IO.Exception" "base" 'False) (C1 ('MetaCons "ExitSuccess" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "ExitFailure" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int))) |
Mutable Variables
SomeRef
class HasWriteRef w env | env -> w where Source #
Environment values with writing capabilities to SomeRef
Since: 0.1.4.0
class HasStateRef s env | env -> s where Source #
Environment values with stateful capabilities to SomeRef
Since: 0.1.4.0
Abstraction over how to read from and write to a mutable reference
Since: 0.1.4.0
Instances
HasWriteRef a (SomeRef a) Source # | Identity write reference where the SomeRef is the env Since: 0.1.4.0 |
HasStateRef a (SomeRef a) Source # | Identity state reference where the SomeRef is the env Since: 0.1.4.0 |
mapRIO :: (outer -> inner) -> RIO inner a -> RIO outer a Source #
Lift one RIO env to another.
Since: 0.1.13.0
readSomeRef :: MonadIO m => SomeRef a -> m a Source #
Read from a SomeRef
Since: 0.1.4.0
writeSomeRef :: MonadIO m => SomeRef a -> a -> m () Source #
Write to a SomeRef
Since: 0.1.4.0
modifySomeRef :: MonadIO m => SomeRef a -> (a -> a) -> m () Source #
Modify a SomeRef This function is subject to change due to the lack of atomic operations
Since: 0.1.4.0
newSomeRef :: MonadIO m => a -> m (SomeRef a) Source #
create a new boxed SomeRef
Since: 0.1.4.0
newUnboxedSomeRef :: (MonadIO m, Unbox a) => a -> m (SomeRef a) Source #
create a new unboxed SomeRef
Since: 0.1.4.0
URef
An unboxed reference. This works like an IORef
, but the data is
stored in a bytearray instead of a heap object, avoiding
significant allocation overhead in some cases. For a concrete
example, see this Stack Overflow question:
https://stackoverflow.com/questions/27261813/why-is-my-little-stref-int-require-allocating-gigabytes.
The first parameter is the state token type, the same as would be
used for the ST
monad. If you're using an IO
-based monad, you
can use the convenience IOURef
type synonym instead.
Since: 0.0.2.0
newURef :: (PrimMonad m, Unbox a) => a -> m (URef (PrimState m) a) Source #
Create a new URef
Since: 0.0.2.0
readURef :: (PrimMonad m, Unbox a) => URef (PrimState m) a -> m a Source #
Read the value in a URef
Since: 0.0.2.0
writeURef :: (PrimMonad m, Unbox a) => URef (PrimState m) a -> a -> m () Source #
Write a value into a URef
. Note that this action is strict, and
will force evalution of the value.
Since: 0.0.2.0
modifyURef :: (PrimMonad m, Unbox a) => URef (PrimState m) a -> (a -> a) -> m () Source #
Modify a value in a URef
. Note that this action is strict, and
will force evaluation of the result value.
Since: 0.0.2.0
IORef
module UnliftIO.IORef
MVar
module UnliftIO.MVar
QSem
module UnliftIO.QSem
QSemN
module UnliftIO.QSemN
Memoize
module UnliftIO.Memoize
Deque
module RIO.Deque
Debugging
Trace
Text
traceM :: Applicative f => Text -> f () Source #
Warning: Trace statement left in code
Since: 0.1.0.0
traceEvent :: Text -> a -> a Source #
Warning: Trace statement left in code
Since: 0.1.0.0
traceEventIO :: MonadIO m => Text -> m () Source #
Warning: Trace statement left in code
Since: 0.1.0.0
traceMarker :: Text -> a -> a Source #
Warning: Trace statement left in code
Since: 0.1.0.0
traceMarkerIO :: MonadIO m => Text -> m () Source #
Warning: Trace statement left in code
Since: 0.1.0.0
traceStack :: Text -> a -> a Source #
Warning: Trace statement left in code
Since: 0.1.0.0
Show
traceShowId :: Show a => a -> a Source #
Warning: Trace statement left in code
Since: 0.1.0.0
traceShowIO :: (Show a, MonadIO m) => a -> m () Source #
Warning: Trace statement left in code
Since: 0.1.0.0
traceShowM :: (Show a, Applicative f) => a -> f () Source #
Warning: Trace statement left in code
Since: 0.1.0.0
traceShowEvent :: Show a => a -> b -> b Source #
Warning: Trace statement left in code
Since: 0.1.0.0
traceShowEventIO :: (Show a, MonadIO m) => a -> m () Source #
Warning: Trace statement left in code
Since: 0.1.0.0
traceShowMarker :: Show a => a -> b -> b Source #
Warning: Trace statement left in code
Since: 0.1.0.0
traceShowMarkerIO :: (Show a, MonadIO m) => a -> m () Source #
Warning: Trace statement left in code
Since: 0.1.0.0
traceShowStack :: Show a => a -> b -> b Source #
Warning: Trace statement left in code
Since: 0.1.0.0
Display
traceDisplay :: Display a => a -> b -> b Source #
Warning: Trace statement left in code
Since: 0.1.0.0
traceDisplayId :: Display a => a -> a Source #
Warning: Trace statement left in code
Since: 0.1.0.0
traceDisplayIO :: (Display a, MonadIO m) => a -> m () Source #
Warning: Trace statement left in code
Since: 0.1.0.0
traceDisplayM :: (Display a, Applicative f) => a -> f () Source #
Warning: Trace statement left in code
Since: 0.1.0.0
traceDisplayEvent :: Display a => a -> b -> b Source #
Warning: Trace statement left in code
Since: 0.1.0.0
traceDisplayEventIO :: (Display a, MonadIO m) => a -> m () Source #
Warning: Trace statement left in code
Since: 0.1.0.0
traceDisplayMarker :: Display a => a -> b -> b Source #
Warning: Trace statement left in code
Since: 0.1.0.0
traceDisplayMarkerIO :: (Display a, MonadIO m) => a -> m () Source #
Warning: Trace statement left in code
Since: 0.1.0.0
traceDisplayStack :: Display a => a -> b -> b Source #
Warning: Trace statement left in code
Since: 0.1.0.0