auto-update-0.1.4: Efficiently run periodic, on-demand actions

Safe HaskellSafe
LanguageHaskell2010

Control.Reaper

Contents

Description

This module provides the ability to create reapers: dedicated cleanup threads. These threads will automatically spawn and die based on the presence of a workload to process on. Example uses include:

  • Killing long-running jobs
  • Closing unused connections in a connection pool
  • Pruning a cache of old items (see example below)

For real-world usage, search the WAI family of packages for imports of Control.Reaper.

Synopsis

Example: Regularly cleaning a cache

In this example code, we use a Map to cache fibonacci numbers, and a Reaper to prune the cache.

The main function first creates a Reaper, with fields to initialize the cache (reaperEmpty), add items to it (reaperCons), and prune it (reaperAction). The reaper will run every two seconds (reaperDelay), but will stop running while reaperNull is true.

main then loops infinitely (forever). Each second it calculates the fibonacci number for a value between 30 and 34, first trying the cache (reaperRead and lookup), then falling back to manually calculating it (fib) and updating the cache with the result (reaperAdd)

clean simply removes items cached for more than 10 seconds. This function is where you would perform IO-related cleanup, like killing threads or closing connections, if that was the purpose of your reaper.

module Main where

import Data.Time (UTCTime, getCurrentTime, diffUTCTime)
import Control.Reaper
import Control.Concurrent (threadDelay)
import Data.Map.Strict (Map)
import qualified Data.Map.Strict as Map
import Control.Monad (forever)
import System.Random (getStdRandom, randomR)

fib :: Int -> Int
fib 0 = 0
fib 1 = 1
fib n = fib (n-1) + fib (n-2)

type Cache = Map Int (Int, UTCTime)

main :: IO ()
main = do
  reaper <- mkReaper defaultReaperSettings
    { reaperEmpty = Map.empty
    , reaperCons = \(k, v, time) workload -> Map.insert k (v, time) workload
    , reaperAction = clean
    , reaperDelay = 1000000 * 2 -- Clean every 2 seconds
    , reaperNull = Map.null
    }
  forever $ do
    fibArg <- getStdRandom (randomR (30,34))
    cache <- reaperRead reaper
    let cachedResult = Map.lookup fibArg cache
    case cachedResult of
      Just (fibResult, _createdAt) -> putStrLn $ "Found in cache: `fib " ++ show fibArg ++ "` " ++ show fibResult
      Nothing -> do
        let fibResult = fib fibArg
        putStrLn $ "Calculating `fib " ++ show fibArg ++ "` " ++ show fibResult
        time <- getCurrentTime
        (reaperAdd reaper) (fibArg, fibResult, time)
    threadDelay 1000000 -- 1 second

-- Remove items > 10 seconds old
clean :: Cache -> IO (Cache -> Cache)
clean oldMap = do
  currentTime <- getCurrentTime
  let pruned = Map.filter (\(_, createdAt) -> currentTime `diffUTCTime` createdAt < 10.0) oldMap
  return (\newData -> Map.union pruned newData)

Settings

data ReaperSettings workload item Source #

Settings for creating a reaper. This type has two parameters: workload gives the entire workload, whereas item gives an individual piece of the queue. A common approach is to have workload be a list of items. This is encouraged by defaultReaperSettings and mkListAction.

Since: 0.1.1

defaultReaperSettings :: ReaperSettings [item] item Source #

Default ReaperSettings value, biased towards having a list of work items.

Since: 0.1.1

Accessors

reaperAction :: ReaperSettings workload item -> workload -> IO (workload -> workload) Source #

The action to perform on a workload. The result of this is a "workload modifying" function. In the common case of using lists, the result should be a difference list that prepends the remaining workload to the temporary workload. For help with setting up such an action, see mkListAction.

Default: do nothing with the workload, and then prepend it to the temporary workload. This is incredibly useless; you should definitely override this default.

Since: 0.1.1

reaperDelay :: ReaperSettings workload item -> Int Source #

Number of microseconds to delay between calls of reaperAction.

Default: 30 seconds.

Since: 0.1.1

reaperCons :: ReaperSettings workload item -> item -> workload -> workload Source #

Add an item onto a workload.

Default: list consing.

Since: 0.1.1

reaperNull :: ReaperSettings workload item -> workload -> Bool Source #

Check if a workload is empty, in which case the worker thread will shut down.

Default: null.

Since: 0.1.1

reaperEmpty :: ReaperSettings workload item -> workload Source #

An empty workload.

Default: empty list.

Since: 0.1.1

Type

data Reaper workload item Source #

A data structure to hold reaper APIs.

Constructors

Reaper 

Fields

  • reaperAdd :: item -> IO ()

    Adding an item to the workload

  • reaperRead :: IO workload

    Reading workload.

  • reaperStop :: IO workload

    Stopping the reaper thread if exists. The current workload is returned.

  • reaperKill :: IO ()

    Killing the reaper thread immediately if exists.

Creation

mkReaper :: ReaperSettings workload item -> IO (Reaper workload item) Source #

Create a reaper addition function. This function can be used to add new items to the workload. Spawning of reaper threads will be handled for you automatically.

Since: 0.1.1

Helper

mkListAction :: (item -> IO (Maybe item')) -> [item] -> IO ([item'] -> [item']) Source #

A helper function for creating reaperAction functions. You would provide this function with a function to process a single work item and return either a new work item, or Nothing if the work item is expired.

Since: 0.1.1