fold-debounce-conduit-0.2.0.7: Regulate input traffic from conduit Source with Control.FoldDebounce
MaintainerToshio Ito <debug.ito@gmail.com>
Safe HaskellSafe-Inferred
LanguageHaskell2010

Data.Conduit.FoldDebounce

Description

module Main (main) where

import Data.Conduit (ConduitT, yield, runConduit, (.|))
import qualified Data.Conduit.List as CL
import Data.Void (Void)
import Control.Concurrent (threadDelay)
import Control.Monad.IO.Class (liftIO)
import Control.Monad.Trans.Resource (ResourceT, runResourceT)

import qualified Data.Conduit.FoldDebounce as F

fastSource :: Int -> ConduitT () Int (ResourceT IO) ()
fastSource max_num = fastStream' 0 where
  fastStream' count = do
    yield count
    if count >= max_num
      then return ()
      else do
        liftIO $ threadDelay 100000
        fastStream' (count + 1)

printSink :: Show a => ConduitT a Void (ResourceT IO) ()
printSink = CL.mapM_ (liftIO . putStrLn . show)

main :: IO ()
main = do
  putStrLn "-- Before debounce"
  runResourceT $ runConduit $ fastSource 10 .| printSink
  let debouncer = F.debounce F.Args { F.cb = undefined, -- anything will do
                                      F.fold = (\list num -> list ++ [num]),
                                      F.init = [] }
                             F.def { F.delay = 500000 }
  putStrLn "-- After debounce"
  runResourceT $ runConduit $ debouncer (fastSource 10) .| printSink

Result:

-- Before debounce
0
1
2
3
4
5
6
7
8
9
10
-- After debounce
[0,1,2,3,4]
[5,6,7,8,9]
[10]

This module regulates (slows down) data stream from conduit source using Control.FoldDebounce.

The data from the original source (type i) are pulled and folded together to create an output data (type o). The output data then comes out of the debounced source in a predefined interval (specified by delay option).

See Control.FoldDebounce for detail.

Synopsis

Documentation

debounce Source #

Arguments

:: (MonadResource m, MonadUnliftIO m) 
=> Args i o

mandatory argument for FoldDebounce. cb field is ignored, so you can set anything to that.

-> Opts i o

optional argument for FoldDebounce

-> ConduitT () i m ()

original source

-> ConduitT () o m ()

debounced source

Debounce conduit source with Control.FoldDebounce. The data stream from the original source (type i) is debounced and folded into the data stream of the type o.

Note that the original source is connected to a sink in another thread. You may need some synchronization if the original source has side-effects.

Re-exports

data Args i o #

Mandatory parameters for new.

Constructors

Args 

Fields

  • cb :: o -> IO ()

    The callback to be called when the output event is emitted. Note that this action is run in a different thread than the one calling send.

    The callback should not throw any exception. In this case, the Trigger is abnormally closed, causing UnexpectedClosedException when close.

  • fold :: o -> i -> o

    The binary operation of left-fold. The left-fold is evaluated strictly.

  • init :: o

    The initial value of the left-fold.

data Opts i o #

Optional parameters for new. You can get the default by def function.

Instances

Instances details
Default (Opts i o) 
Instance details

Defined in Control.FoldDebounce

Methods

def :: Opts i o #

def :: Default a => a #

The default value for this type.

Accessors for Opts

delay :: Opts i o -> Int #

The time (in microsecond) to wait after receiving an event before sending it, in case more events happen in the interim.

Default: 1 second (1000000)

alwaysResetTimer :: Opts i o -> Bool #

Normally, when an event is received and it's the first of a series, a timer is started, and when that timer expires, all events are sent. If you set this parameter to True, then the timer is reset after each event is received.

Default: False

Preset parameters

forStack :: Args i [i] Source #

Args for stacks. Input events are accumulated in a stack, i.e., the last event is at the head of the list.

forMonoid :: Monoid i => Args i i Source #

Args for monoids. Input events are appended to the tail.

forVoid :: Args i () Source #

Args that discards input events. The data stream from the debounced source indicates the presence of data from the original source.