nri-prelude-0.1.0.4: A Prelude inspired by the Elm programming language

Safe HaskellNone
LanguageHaskell2010

Platform

Contents

Description

This module is for running applications we build using this library, and for integrating external Haskell libraries into our code. You normally shouldn't need to use this module, unless you're building a library or creating a wrapper for an existing Haskell library.

Synopsis

Turning a IO type into a Task.

type DoAnythingHandler = Handler Source #

A value of this type allows you to turn an IO type into a Task using the doAnything function.

The intended use for this is creating other handlers for running specific types of effects. Suppose you're creating a library for making queries to a database. You might create a Handler type for it like this:

data Handler = Handler
   { doAnything :: DoAnythingHandler
   , host :: Text
   , port :: Text
   }

You create this handler in the root of your application and then pass it to wherever you need to perform database requests. Using the DoAnythingHandler available to it your library can perform the query, then wrap the resulting IO up in a Task.

doAnythingHandler :: IO Handler Source #

Get a key that allows you to run arbitrary IO in a Task. This key you can then pass to doAnything. See the documentation for DoAnythingHandler.

doAnything :: Handler -> IO (Result e a) -> Task e a Source #

Allow running arbitrary IO in Task, but only if you have a license for it.

Working with the log handler

data LogHandler Source #

Our Task type secretly passed a value of this type throughout our application. Anywhere in our application we can add context to the log handler. For example we might wrap our database queries in a tracingSpan called "query" and add some bits of context, such as the SQL operation the query is performing. These bits of metadata will then be used as much as possible in logging messages, tracing, and error reporting.

Note that we do not report recorded information anywhere (log it to file, or to an observability platform), until we completely finish a request. This gives us the option _not_ to report on a particular request. We might use this to report only on a subset of the succeeding requests, to save us money without loosing important signal. We'll only know whether a request succeeds after it completes though, so we have to hold off on any reporting for a request until it's done.

logHandler :: Task e LogHandler Source #

Access the log handler in a task.

requestId :: Task e Text Source #

Get the ID of the current request.

silentHandler :: IO LogHandler Source #

A log handler that doesn't log anything.

Creating custom tracingSpans in libraries

tracingSpan :: HasCallStack => Text -> Task e a -> Task e a Source #

Run a task in a tracingSpan.

tracingSpan "code dance" <| do waltzPassLeft clockwiseTurn 60

This will help provide better debugging information if something goes wrong inside the wrapped task.

tracingSpanIO :: HasCallStack => LogHandler -> Text -> (LogHandler -> IO a) -> IO a Source #

Like tracingSpan, but this one runs in IO instead of Task. We sometimes need this in libraries. Task has the concept of a LogHandler built in but IO does not, so we'll have to pass it around ourselves.

tracingSpanIO handler "code dance" childHandler - do waltzPassLeft childHandler clockwiseTurn childHandler 60

rootTracingSpanIO :: HasCallStack => Text -> (TracingSpan -> IO ()) -> Text -> (LogHandler -> IO a) -> IO a Source #

Special version of tracingSpanIO to call in the root of your application. Instead of taking a parent handler it takes a continuation that will be called with this root tracingSpan after it has run.

rootTracingSpanIO "request-23" Prelude.print "incoming request" handler - handleRequest |> Task.perform handler

setTracingSpanDetails :: TracingSpanDetails d => d -> Task e () Source #

Set the details for a tracingSpan created using the tracingSpan function. Like tracingSpan this is intended for use in writing libraries that define custom types of effects, such as database queries or http requests.

It's often a good idea to use this together with Platform.finally or Platform.bracketWithError, to ensure we record tracingSpan details even in the event of an exception cutting the execution of our tracingSpan short.

tracingSpan "holiday" do let bookPick = BookPick "The Stone Sky" Platform.finally (readBook bookPick) (setTracingSpanDetails bookPick)

newtype BookPick = BookPick Text deriving (Aeson.ToJSON)

instance TracingSpanDetails BookPick

setTracingSpanDetailsIO :: LogHandler -> forall d. TracingSpanDetails d => d -> IO () Source #

There's common fields all tracingSpans have such as a name and start and finish times. On top of that each tracingSpan can define a custom type containing useful custom data. This function allows us to set this custom data for the current tracingSpan. We could design it so this data is passed in as an extra argument when we create the tracingSpan, but then we'd miss out on useful details that only become known as the tracingSpan runs, for example the response code of an HTTP request.

markTracingSpanFailed :: Task e () Source #

Mark a tracingSpan created with the tracingSpan function as failed. Like tracingSpan this is intended for use in writing libraries that define custom types of effects, such as database queries or http requests.

tracingSpan "plane spotting" do spotPlanes |> Task.onError (GlobalPandemicError -> do markTracingSpanFailed Task.fail GlobalPandemicError )

markTracingSpanFailedIO :: LogHandler -> IO () Source #

Mark the current tracingSpan as failed. Some reporting backends will use this to decide whether a particular request is worth reporting on.

Interpreting tracingSpans for reporting to monitoring platforms

data TracingSpan Source #

A TracingSpan contains debugging information related to a section of the program. TracingSpans can be nested inside other tracingSpans to form a tree, each tracingSpan representing part of the execution of the program. This format is a typical way to store tracing data. Check out this section of the documentation on the open tracing standard for a good introduction on tracing data and tracingSpans:

https://github.com/opentracing/specification/blob/master/specification.md#the-opentracing-data-model

From tracingSpans we can derive many other formats of debugging information:

  • Logs are tracingSpans flattened into a series of events ordered by time. For example, consider the following tracingSpans:

    do the laundry 11:00-12:15 wash clothes 11:00-12:00 hang clothes to dry 12:00-12:15

we could recover the following logs from this:

11:00 starting do the laundry 11:00 wash clothes 12:00 hang clothes to dry 12:15 finishing do the laundry

  • Metrics are rolling statistics on tracingSpans. For example, we can increment a counter every time we see a particular tracingSpan pass by.

So whether we're looking for tracing data, logs, or metrics, tracingSpans got us covered.

Constructors

TracingSpan 

Fields

  • name :: Text

    A description of this tracingSpan. This should not contain any dynamically generated strings to make grouping tracingSpans easy. Any contextual info should go into details.

  • started :: MonotonicTime

    The time this tracingSpan started.

  • finished :: MonotonicTime

    The time this tracingSpan finished.

  • frame :: Maybe (Text, SrcLoc)

    The source code location of this tracingSpan. The first Text is the name of the function getting called.

  • details :: Maybe SomeTracingSpanDetails

    Unique information for this tracingSpan.

  • succeeded :: Succeeded

    Whether this tracingSpan succeeded. If any of the children of this tracingSpan failed, so will this tracingSpan. This will create a path to the tracingSpan closest to the failure from the root tracingSpan.

  • children :: [TracingSpan]

    Any subtracingSpans nested inside this tracingSpan. These are ordered in reverse chronological order, so most recent tracingSpan first, because it's cheaper to append new tracingSpans onto the left of the list.

Instances
Show TracingSpan Source # 
Instance details

Defined in Platform.Internal

data Succeeded Source #

The Succeeded type is used to indicate whether or not a particular TracingSpan ran without encountering user-facing problems.

Constructors

Succeeded

A tracingSpan that didn't fail with an unexpected exception, or was explicitly marked as failed by the user.

When a tracingSpan returns a failed task we do not count that as Failed here, because a failed task might be part of normal program operation. We wouldn't want to log those kinds of failures as errors.

Failed

A tracingSpan marked as failed by a user, for example by logging with a high severity to indicate a user is in pain.

FailedWith SomeException

A tracingSpan that failed with an unhandled exception thrown by the Haskell runtime or a library.

Instances
Show Succeeded Source # 
Instance details

Defined in Platform.Internal

Semigroup Succeeded Source #

If the first bit of code succeeded and the second failed, the combination of the two has failed as well. The SemiGroup and Monoid type instances for Succeeded allow us to combine Succeeded values in such a fashion.

The rule expressed here is that the Succeeded value of a combination of computations if the same as the worst thing that happened to any of the individual computations.

Instance details

Defined in Platform.Internal

Monoid Succeeded Source # 
Instance details

Defined in Platform.Internal

class (Typeable e, ToJSON e) => TracingSpanDetails e where Source #

Every type we want to use as tracingSpan metadata needs a TracingSpanDetails instance. The TracingSpanDetails class fulfills these roles:

  • It allows for conversion between the custom details type and the SomeTracingSpanDetails type stored in a TracingSpan.
  • It requires the custom details type to also have a ToJSON instance.

This gives a logger two options for rendering a SomeTracingSpanDetails value into a format understood by a monitoring tool:

  • It can try fromTracingSpanDetails to try to recover one of the custom tracingSpan details types it has implemented custom rendering logic for.
  • If this particular tracingSpan details type is unknown to this particular logger, it can obtain always obtain a generic JSON blob of the information instead.

Minimal complete definition

Nothing

data SomeTracingSpanDetails Source #

A wrapper around the various types that specify details for different kinds of tracingSpans.

Depending on what happens within a tracingSpan we want to log different information for debugging. A tracingSpan for a database query might include the SQL of the query, and a tracingSpan for an HTTP request the URL the request is addressed to.

We could define a single SomeTracingSpanDetails type that can represent all of these different types of details. One way would be to write a union:

data SomeTracingSpanDetails = Sql SqlDetails | Http HttpDetails | ...

The disadvantage of this is that nri-prelude will have to know about every possible type of tracingSpan. If a library wanted to log new information it would have to change nri-prelude first to support this. That's a barrier to adding useful logging information we'd prefer not to have.

Another approach is to have the details field take arbitrary JSON:

type SomeTracingSpanDetails = Data.Aeson.Value

This allows any library to log what it wants without requiring any changes in nri-prelude. However, unless we parse that JSON back into the original types (which is wasteful and can fail) we have lost the ability to render specific bits of information in special ways. If we provide Bugsnag with the stack trace of an error it will present it nicely in its UI. NewRelic can treat SQL strings of queries in a special way. But we don't have stack traces or SQL strings to give, just opaque JSON blobs.

We'd like to both let libraries define custom detail types _and_ be able to read specific fields from those types in loggers that present certain bits of information in nice ways. To do that we allow a bit of type magic here. Analogous to Haskell's SomeException type and Exception type class, we define a SomeTracingSpanDetails type and TracingSpanDetails type class.

The SomeTracingSpanDetails type can wrap any custom type, as long as it has TracingSpanDetails instance. The TracingSpanDetails instance allows us to recover the original details type if we want to treat it special in a custom logger.

data Renderer a where Source #

A helper type used for renderTracingSpanDetails. Used to wrap rendering functions so they have the same type and can be put in a list together.

Constructors

Renderer :: TracingSpanDetails s => (s -> a) -> Renderer a 

renderTracingSpanDetails :: [Renderer a] -> SomeTracingSpanDetails -> Maybe a Source #

In reporting logic we'd like to case on the different types a SomeTracingSpanDetails can contain and write logic for each one. This helper allows us to do so.

newtype ImportantFact = ImportantFact Text
instance ToJSON ImportantFact
instance SpanDetails ImportantFact

newtype KeyStatistic = KeyStatistic Int
instance ToJSON KeyStatistic
instance SpanDetails KeyStatistic

toTracingSpanDetails (ImportantFact "Koala's are adorable")
  |> renderTracingSpanDetails
       [ Renderer (\ImportantFact fact -> fact)
       , Renderer (\KeyStatistic stat -> Text.fromInt stat)
       ]
  |> Maybe.withDefault (\details -> show (Data.Aeson.encode details))

Remember that SomeTracingSpanDetails are always JSON-serializable, so you can use that if you need to render a span of a type you didn't prepare for.

data MonotonicTime Source #

You might expect a timestamp here, but timestamps are unreliable for measuring how long a bit of code runs. For example: events like leap seconds can cause them to move backards. This might result in us measuring the duration of an operation and finding it to be minus 200 milliseconds.

We use GHC.Clock.getMonotonicTimeNSec to let the OS tell us how much time has passed since an arbitrary but constant moment in the past. That might not seem all that useful, but if we 'sync watches' at one moment by getting the monotonic and "regular" time in the same moment then we'll able to convert any monotonic time to real timestamps. Conversion is not our concern here though, we just store these monotonic times and let code that reporters that use these tracingSpans convert the monotonic times into whatever format they need.

inMicroseconds :: MonotonicTime -> Word64 Source #

The number of microseconds that have passed since an arbitrary but constant moment in the past.

Ensuring cleanup logic gets ran in case of exceptions.

bracketWithError :: Task e a -> (Succeeded -> a -> Task e c) -> (a -> Task e b) -> Task e b Source #

bracket allows us to acquire a resource (the first argument), use it (the third argument), and release it afterward (the second argument). Critically, the release phase always runs, even if the use phase fails with an error.

bracket is defined in the exceptions package for all types implementing the MonadMask type class. We could acquire it for Task by deriving MonadMask for it, but this would require us to implement super classes MonadThrow and MonadCatch for Task as well.

We don't want to implement MonadThrow for Task because it would allow us to throw exceptions directly in the IO monad hidden in Task. These types of exceptions disappear from the types: IO does not have a type parameter indicating possible errors. We want to ensure our own errors end up in the error argument of the Task type, so we don't implement MonadThrow.

The implementation below is mostly taken from the implementation of generalBracket for ExceptT e m a in the Control.Monad.Catch module.

finally :: Task e a -> Task e b -> Task e a Source #

Ensure some cleanup logic always run, regardless of whether the task it runs after failed with an exception.

finally doSomeWork (Log.info "Finished doing work." [])

Exception throwing, in rare cases we need it.

unsafeThrowException :: HasCallStack => Text -> Task e a Source #

Throw a runtime exception that cannot be caught. This function, like Debug.todo, breaks type level guarantees and should be avoided. Where possible use a type like Result or Task that explicitly handlers errors.

Some external libraries and API depend on sometimes require us to throw errors. When that is the case prefer this function over different ways to throw an exception in Control.Exception, because it results in better logs for those who'll need to investigate these problems.