rio-0.1.21.0: A standard library for Haskell
Safe HaskellNone
LanguageHaskell2010

RIO

Synopsis

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.

The RIO Monad

newtype RIO env a Source #

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.

Constructors

RIO 

Fields

Instances

Instances details
MonadReader env (RIO env) Source # 
Instance details

Defined in RIO.Prelude.RIO

Methods

ask :: RIO env env #

local :: (env -> env) -> RIO env a -> RIO env a #

reader :: (env -> a) -> RIO env a #

HasStateRef s env => MonadState s (RIO env) Source # 
Instance details

Defined in RIO.Prelude.RIO

Methods

get :: RIO env s #

put :: s -> RIO env () #

state :: (s -> (a, s)) -> RIO env a #

(Monoid w, HasWriteRef w env) => MonadWriter w (RIO env) Source # 
Instance details

Defined in RIO.Prelude.RIO

Methods

writer :: (a, w) -> RIO env a #

tell :: w -> RIO env () #

listen :: RIO env a -> RIO env (a, w) #

pass :: RIO env (a, w -> w) -> RIO env a #

Monad (RIO env) Source # 
Instance details

Defined in RIO.Prelude.RIO

Methods

(>>=) :: RIO env a -> (a -> RIO env b) -> RIO env b #

(>>) :: RIO env a -> RIO env b -> RIO env b #

return :: a -> RIO env a #

Functor (RIO env) Source # 
Instance details

Defined in RIO.Prelude.RIO

Methods

fmap :: (a -> b) -> RIO env a -> RIO env b #

(<$) :: a -> RIO env b -> RIO env a #

Applicative (RIO env) Source # 
Instance details

Defined in RIO.Prelude.RIO

Methods

pure :: a -> RIO env a #

(<*>) :: RIO env (a -> b) -> RIO env a -> RIO env b #

liftA2 :: (a -> b -> c) -> RIO env a -> RIO env b -> RIO env c #

(*>) :: RIO env a -> RIO env b -> RIO env b #

(<*) :: RIO env a -> RIO env b -> RIO env a #

MonadIO (RIO env) Source # 
Instance details

Defined in RIO.Prelude.RIO

Methods

liftIO :: IO a -> RIO env a #

MonadThrow (RIO env) Source # 
Instance details

Defined in RIO.Prelude.RIO

Methods

throwM :: Exception e => e -> RIO env a #

PrimMonad (RIO env) Source # 
Instance details

Defined in RIO.Prelude.RIO

Associated Types

type PrimState (RIO env) #

Methods

primitive :: (State# (PrimState (RIO env)) -> (# State# (PrimState (RIO env)), a #)) -> RIO env a #

MonadUnliftIO (RIO env) Source # 
Instance details

Defined in RIO.Prelude.RIO

Methods

withRunInIO :: ((forall a. RIO env a -> IO a) -> IO b) -> RIO env b #

Semigroup a => Semigroup (RIO env a) Source # 
Instance details

Defined in RIO.Prelude.RIO

Methods

(<>) :: RIO env a -> RIO env a -> RIO env a #

sconcat :: NonEmpty (RIO env a) -> RIO env a #

stimes :: Integral b => b -> RIO env a -> RIO env a #

Monoid a => Monoid (RIO env a) Source # 
Instance details

Defined in RIO.Prelude.RIO

Methods

mempty :: RIO env a #

mappend :: RIO env a -> RIO env a -> RIO env a #

mconcat :: [RIO env a] -> RIO env a #

type PrimState (RIO env) Source # 
Instance details

Defined in RIO.Prelude.RIO

type PrimState (RIO env) = PrimState IO

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.

MonadIO and MonadUnliftIO

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 is LogFunc, which can be created via withLogFunc, and is accessed via HasLogFunc. This provides all the classical logging facilities: timestamped text output with log levels and colors (if terminal-supported) to the terminal. We log output via logInfo, 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 via HasGLogFunc. In this case, we log output via glog. 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

data LogFunc Source #

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

Instances

Instances details
Semigroup LogFunc Source #

Perform both sets of actions per log entry.

Since: 0.0.0.0

Instance details

Defined in RIO.Prelude.Logger

Monoid LogFunc Source #

mempty peforms no logging.

Since: 0.0.0.0

Instance details

Defined in RIO.Prelude.Logger

HasLogFunc LogFunc Source # 
Instance details

Defined in RIO.Prelude.Logger

class HasLogFunc env where Source #

Environment values with a logging function.

Since: 0.0.0.0

Methods

logFuncL :: Lens' env LogFunc Source #

Instances

Instances details
HasLogFunc LogFunc Source # 
Instance details

Defined in RIO.Prelude.Logger

HasLogFunc LoggedProcessContext Source # 
Instance details

Defined in RIO.Process

HasLogFunc SimpleApp Source # 
Instance details

Defined in RIO.Prelude.Simple

logOptionsHandle Source #

Arguments

:: 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 with True
  • setLogUseColor is called with True (except on Windows)
  • setLogUseLoc is called with True
  • setLogUseTime is called with True
  • setLogMinLevel is called with Debug 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 enabled 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 #

Include the time when printing log messages.

Default: True in debug mode, False otherwise.

Since: 0.0.0.0

setLogUseColor :: Bool -> LogOptions -> LogOptions Source #

Use ANSI color codes in the log output.

Default: True if in verbose mode and the Handle is a terminal device.

Since: 0.0.0.0

setLogUseLoc :: Bool -> LogOptions -> LogOptions Source #

Use code location in the log output.

Default: True if in verbose mode, False otherwise.

Since: 0.1.2.0

setLogFormat :: (Utf8Builder -> Utf8Builder) -> LogOptions -> LogOptions Source #

Set format method for messages

Default: id

Since: 0.1.13.0

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

setLogAccentColors Source #

Arguments

:: (Int -> Utf8Builder)

This should be a total function.

-> LogOptions 
-> LogOptions 

ANSI color codes for accents in the log output. Accent colors are indexed by Int.

Default: const "\ESC[92m" -- Bright green, for all indicies

Since: 0.1.18.0

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

logOther Source #

Arguments

:: (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

logOtherS Source #

Arguments

:: (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

data LogLevel Source #

The log level of a message.

Since: 0.0.0.0

Instances

Instances details
Eq LogLevel Source # 
Instance details

Defined in RIO.Prelude.Logger

Ord LogLevel Source # 
Instance details

Defined in RIO.Prelude.Logger

Read LogLevel Source # 
Instance details

Defined in RIO.Prelude.Logger

Show LogLevel Source # 
Instance details

Defined in RIO.Prelude.Logger

type LogSource = Text Source #

Where in the application a log message came from. Used for display purposes only.

Since: 0.0.0.0

data CallStack #

CallStacks 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:

  1. If there is a CallStack in scope -- i.e. the enclosing function has a HasCallStack constraint -- GHC will append the new call-site to the existing CallStack.
  2. 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 a HasCallStack constraint for the enclosing definition (subject to the monomorphism restriction).
  3. If there is no CallStack in scope and the enclosing definition has an explicit type signature, GHC will solve the HasCallStack constraint for the singleton CallStack containing just the current call-site.

CallStacks 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

Instances

Instances details
IsList CallStack

Be aware that 'fromList . toList = id' only for unfrozen CallStacks, since toList removes frozenness information.

Since: base-4.9.0.0

Instance details

Defined in GHC.Exts

Associated Types

type Item CallStack #

Show CallStack

Since: base-4.9.0.0

Instance details

Defined in GHC.Show

NFData CallStack

Since: deepseq-1.4.2.0

Instance details

Defined in Control.DeepSeq

Methods

rnf :: CallStack -> () #

type Item CallStack 
Instance details

Defined in GHC.Exts

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

data GLogFunc msg Source #

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

Instances details
Contravariant GLogFunc Source #

Use this instance to wrap sub-loggers via mapRIO.

The Contravariant class is available in base 4.12.0.

Since: 0.1.13.0

Instance details

Defined in RIO.Prelude.Logger

Methods

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

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

Semigroup (GLogFunc msg) Source #

Perform both sets of actions per log entry.

Since: 0.1.13.0

Instance details

Defined in RIO.Prelude.Logger

Methods

(<>) :: GLogFunc msg -> GLogFunc msg -> GLogFunc msg #

sconcat :: NonEmpty (GLogFunc msg) -> GLogFunc msg #

stimes :: Integral b => b -> GLogFunc msg -> GLogFunc msg #

Monoid (GLogFunc msg) Source #

mempty peforms no logging.

Since: 0.1.13.0

Instance details

Defined in RIO.Prelude.Logger

Methods

mempty :: GLogFunc msg #

mappend :: GLogFunc msg -> GLogFunc msg -> GLogFunc msg #

mconcat :: [GLogFunc msg] -> GLogFunc msg #

HasGLogFunc (GLogFunc msg) Source #

Quick way to run a RIO that only has a logger in its environment.

Since: 0.1.13.0

Instance details

Defined in RIO.Prelude.Logger

Associated Types

type GMsg (GLogFunc msg) Source #

Methods

gLogFuncL :: Lens' (GLogFunc msg) (GLogFunc (GMsg (GLogFunc msg))) Source #

type GMsg (GLogFunc msg) Source # 
Instance details

Defined in RIO.Prelude.Logger

type GMsg (GLogFunc msg) = msg

gLogFuncClassic :: (HasLogLevel msg, HasLogSource msg, Display msg) => LogFunc -> GLogFunc msg Source #

Make a GLogFunc via classic LogFunc. Use this if you'd like to log your generic data type via the classic RIO terminal logger.

Since: 0.1.13.0

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 #

A contramap. Use this to wrap sub-loggers via mapRIO.

If you are on base > 4.12.0, you can just use contramap.

Since: 0.1.13.0

class HasGLogFunc env where Source #

An app is capable of generic logging if it implements this.

Since: 0.1.13.0

Associated Types

type GMsg env Source #

Methods

gLogFuncL :: Lens' env (GLogFunc (GMsg env)) Source #

Instances

Instances details
HasGLogFunc (GLogFunc msg) Source #

Quick way to run a RIO that only has a logger in its environment.

Since: 0.1.13.0

Instance details

Defined in RIO.Prelude.Logger

Associated Types

type GMsg (GLogFunc msg) Source #

Methods

gLogFuncL :: Lens' (GLogFunc msg) (GLogFunc (GMsg (GLogFunc msg))) Source #

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

Methods

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

Methods

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

Constructors

Utf8Builder 

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

Minimal complete definition

display | textDisplay

Methods

display :: a -> Utf8Builder Source #

textDisplay :: a -> Text Source #

Display data as Text, which will also be used for display if it is not overriden.

Since: 0.1.7.0

Instances

Instances details
Display Char Source #

Since: 0.1.0.0

Instance details

Defined in RIO.Prelude.Display

Display Double Source # 
Instance details

Defined in RIO.Prelude.Display

Display Float Source #

Since: 0.1.0.0

Instance details

Defined in RIO.Prelude.Display

Display Int Source #

Since: 0.1.0.0

Instance details

Defined in RIO.Prelude.Display

Display Int8 Source #

Since: 0.1.0.0

Instance details

Defined in RIO.Prelude.Display

Display Int16 Source #

Since: 0.1.0.0

Instance details

Defined in RIO.Prelude.Display

Display Int32 Source #

Since: 0.1.0.0

Instance details

Defined in RIO.Prelude.Display

Display Int64 Source #

Since: 0.1.0.0

Instance details

Defined in RIO.Prelude.Display

Display Integer Source #

Since: 0.1.0.0

Instance details

Defined in RIO.Prelude.Display

Display Word Source #

Since: 0.1.0.0

Instance details

Defined in RIO.Prelude.Display

Display Word8 Source #

Since: 0.1.0.0

Instance details

Defined in RIO.Prelude.Display

Display Word16 Source #

Since: 0.1.0.0

Instance details

Defined in RIO.Prelude.Display

Display Word32 Source #

Since: 0.1.0.0

Instance details

Defined in RIO.Prelude.Display

Display Word64 Source #

Since: 0.1.0.0

Instance details

Defined in RIO.Prelude.Display

Display IOException Source #

Since: 0.1.0.0

Instance details

Defined in RIO.Prelude.Display

Display SomeException Source #

Since: 0.1.0.0

Instance details

Defined in RIO.Prelude.Display

Display Text Source #

Since: 0.1.0.0

Instance details

Defined in RIO.Prelude.Display

Display Text Source #

Since: 0.1.0.0

Instance details

Defined in RIO.Prelude.Display

Display Utf8Builder Source #

Since: 0.1.0.0

Instance details

Defined in RIO.Prelude.Display

Display (ProcessConfig a b c) Source #

Since: 0.1.0.0

Instance details

Defined in RIO.Prelude.Display

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 ASetter' s a = ASetter s s a a #

This is a type alias for monomorphic setters which don't change the type of the container (or of the value inside). It's useful more often than the same type in lens, because we can't provide real setters and so it does the job of both ASetter' and Setter'.

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 structure
  • b is the type of the replaced value
  • s is the type of the whole structure
  • t is the type of the structure after replacing a in it with b

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 -> a
view :: SimpleGetter s a -> s -> a
view getter = getConst . getter Const

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 SimpleGetters 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 #

over is a synonym for (%~).

Getting fmap in a roundabout way:

over mapped :: Functor f => (a -> b) -> f a -> f b
over 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 over _2 as a replacement for second:

>>> over _2 show (10,20)
(10,"20")

set :: ASetter s t a b -> b -> s -> t #

set is a synonym for (.~).

Setting the 1st component of a pair:

set _1 :: x -> (a, b) -> (x, b)
set _1 = \x t -> (x, snd t)

Using it to rewrite (<$):

set mapped :: Functor f => a -> f b -> f a
set mapped = (<$)

sets :: ((a -> b) -> s -> t) -> ASetter s t a b #

sets creates an ASetter from an ordinary function. (The only thing it does is wrapping and unwrapping Identity.)

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

Converting Either to Maybe:

>>> 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. mapped %~ reverse is the same thing as 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 Lefts in a list to upper case:

>>> (mapped._Left.mapped %~ toUpper) [Left "foo", Right "bar"]
[Left "FOO",Right "bar"]

(.~) :: ASetter s t a b -> b -> s -> t infixr 4 #

(.~) assigns a value to the target. It's the same thing as using (%~) with const:

l .~ x = l %~ const x

See set if you want a non-operator synonym.

Here it is used to change 2 fields of a 3-tuple:

>>> (0,0,0) & _1 .~ 1 & _3 .~ 3
(1,0,3)

Concurrency

data ThreadId #

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 ThreadIds. 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

Instances details
Eq ThreadId

Since: base-4.2.0.0

Instance details

Defined in GHC.Conc.Sync

Ord ThreadId

Since: base-4.2.0.0

Instance details

Defined in GHC.Conc.Sync

Show ThreadId

Since: base-4.2.0.0

Instance details

Defined in GHC.Conc.Sync

NFData ThreadId

Since: deepseq-1.4.0.0

Instance details

Defined in Control.DeepSeq

Methods

rnf :: ThreadId -> () #

Hashable ThreadId 
Instance details

Defined in Data.Hashable.Class

Methods

hashWithSalt :: Int -> ThreadId -> Int #

hash :: ThreadId -> Int #

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

Async

STM

Chan

Timeout

Exceptions

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

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 #

Same as readFile, but generalized to MonadIO

writeFileBinary :: MonadIO m => FilePath -> ByteString -> m () Source #

Same as writeFile, but generalized to MonadIO

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.

data ExitCode #

Defines the exit codes that a program can return.

Constructors

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

Instances details
Eq ExitCode 
Instance details

Defined in GHC.IO.Exception

Ord ExitCode 
Instance details

Defined in GHC.IO.Exception

Read ExitCode 
Instance details

Defined in GHC.IO.Exception

Show ExitCode 
Instance details

Defined in GHC.IO.Exception

Generic ExitCode 
Instance details

Defined in GHC.IO.Exception

Associated Types

type Rep ExitCode :: Type -> Type #

Methods

from :: ExitCode -> Rep ExitCode x #

to :: Rep ExitCode x -> ExitCode #

Exception ExitCode

Since: base-4.1.0.0

Instance details

Defined in GHC.IO.Exception

NFData ExitCode

Since: deepseq-1.4.2.0

Instance details

Defined in Control.DeepSeq

Methods

rnf :: ExitCode -> () #

type Rep ExitCode 
Instance details

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

Methods

writeRefL :: Lens' env (SomeRef w) Source #

Instances

Instances details
HasWriteRef a (SomeRef a) Source #

Identity write reference where the SomeRef is the env

Since: 0.1.4.0

Instance details

Defined in RIO.Prelude.RIO

class HasStateRef s env | env -> s where Source #

Environment values with stateful capabilities to SomeRef

Since: 0.1.4.0

Methods

stateRefL :: Lens' env (SomeRef s) Source #

Instances

Instances details
HasStateRef a (SomeRef a) Source #

Identity state reference where the SomeRef is the env

Since: 0.1.4.0

Instance details

Defined in RIO.Prelude.RIO

data SomeRef a Source #

Abstraction over how to read from and write to a mutable reference

Since: 0.1.4.0

Instances

Instances details
HasWriteRef a (SomeRef a) Source #

Identity write reference where the SomeRef is the env

Since: 0.1.4.0

Instance details

Defined in RIO.Prelude.RIO

HasStateRef a (SomeRef a) Source #

Identity state reference where the SomeRef is the env

Since: 0.1.4.0

Instance details

Defined in RIO.Prelude.RIO

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

data URef s a Source #

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

type IOURef = URef (PrimState IO) Source #

Helpful type synonym for using a URef from an IO-based stack.

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

MVar

QSem

QSemN

Memoize

Deque

module RIO.Deque

Debugging

Trace

Text

trace :: Text -> a -> a Source #

Warning: Trace statement left in code

Since: 0.1.0.0

traceId :: Text -> Text Source #

Warning: Trace statement left in code

Since: 0.1.0.0

traceIO :: MonadIO m => Text -> m () Source #

Warning: Trace statement left in code

Since: 0.1.0.0

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

traceShow :: Show a => a -> b -> b Source #

Warning: Trace statement left in code

Since: 0.1.0.0

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