Portability | non-portable |
---|---|
Stability | experimental |
Safe Haskell | None |
Data routing for time series analysis.
- data Config = Config {
- sketchSize :: Int
- sketchGroups :: Word8
- corrCutoff :: Double
- swSize :: Word64
- bwSize :: Word64
- randSeed :: Integer
- impls :: Implementation
- verbose :: Bool
- type BasicWindows = IntMap (Seq Window)
- data Summary = Summary {}
- data BWSummary = BWSummary {}
- data SysState = SysState {}
- data CorrResult = CorrResult {}
- data Implementation
- newtype Loop a = Loop {
- unLoop :: StateT SysState (Writer [Either String CorrResult]) a
- loop :: Handle -> Config -> [[Double]] -> IO ()
- runLoop :: Loop a -> SysState -> ((a, SysState), [Either String CorrResult])
- step :: Config -> [Double] -> Loop ()
- filterImpl :: Implementation -> Double -> (CorrResult, CorrResult) -> [CorrResult]
- corrPermute :: Word64 -> Word64 -> Word64 -> BasicWindows -> IntMap Summary -> [(CorrResult, CorrResult)]
- slidingWindow :: Word64 -> BasicWindows -> IntMap Window
- updateStates :: [Double] -> Loop ()
- consBW :: Seq Window -> Seq Window -> Seq Window
- updateSummariesAndShift :: Loop ()
- rotateSeq :: a -> Seq a -> Seq a
- initialSysState :: Config -> Int -> SysState
- initialSlidingWindows :: Size -> Int -> IntMap Window
- initialBasicWindows :: Size -> Size -> Int -> BasicWindows
- initialSummaries :: Config -> Int -> IntMap Summary
- initialBWSummary :: Size -> BWSummary
- randomVectors :: Integer -> Size -> Size -> Int -> IntMap RandomVector
- simpleCorrResult :: CorrResult -> String
Types
Configuration values for detecting correlations from uncooperative time series data.
This data type shall relate to bootstrapping in future, but at the moment, nothing related.
Config | |
|
type BasicWindows = IntMap (Seq Window)Source
Representing basic windows as IntMap
of Seq
of Window
s.
Key of outer IntMap
is ID for concurrent input stream, number of
keys matches to number of concurrent input stream. Inner Seq
is indexed basic window within sliding window, number of elements
matches to nb, where `nb = sw bw`, sw/ is sliding window size
and bw is basic window size.
Summary of sliding window.
We don't need to maintain whole basic windows when sketch implementation is the only concern. To show correlation values with direct function, preserving the whole basic window contents. From "3.5 The Issues in Implementation section":
... We need to maintain
- ∑i=0,nb-1(sum(Xbwⁱ))
- ∑i=0,nb-1(sum((Xbwⁱ)²))
for a sliding window ...
Summary | |
|
Summary of basic window.
From "3.5 The Issues in Implementation section":
... We need to maintain
- Xbwⁱ⋅R
- sum(Xbwⁱ)
- sum((Xbwⁱ)²)
for each basic window.
State stored in analysis system.
Later this shall relate to memory data in hardware implementation, but at the moment its 100% Haskell data type and values.
data CorrResult Source
Result of correlation analysis.
Inspired from output found in "statStream". See:
Eq CorrResult | |
Show CorrResult | |
MonadWriter [Either String CorrResult] Loop |
data Implementation Source
Implementations.
As for a prototype, used to analyse and compre resulting values for different implementations.
Loop for analysing correlation of input data and updating analysis results and windowed data.
Looping actions
Looping with State
and Writer
.
:: Handle | Where to show results. |
-> Config | Configuration values used for computation. |
-> [[Double]] | Input values. |
-> IO () |
The main loop of time series analysis.
Specifying number of concurrent time series data in this function. In hardware implementation, this may relates to fixed value, which possibly been configured at the time of code generation.
runLoop :: Loop a -> SysState -> ((a, SysState), [Either String CorrResult])Source
Unwrap Loop
, run internal State
and Writer
.
step :: Config -> [Double] -> Loop ()Source
Single step to take with new input data.
Handle state management and if found any, report analysis result.
:: Implementation | Which result to choose. |
-> Double | Cutoff value. |
-> (CorrResult, CorrResult) | (Direct correlation result, sketch correlation result). |
-> [CorrResult] |
Filter results with implementation and cutoff value.
:: Word64 | System current time. ... What is the time format used in hardware implementation? |
-> Word64 | Basic window size. |
-> Word64 | Sliding window size. |
-> BasicWindows | Basic windows. |
-> IntMap Summary |
|
-> [(CorrResult, CorrResult)] | Direct result and sketch result. |
Compute correlations.
slidingWindow :: Word64 -> BasicWindows -> IntMap WindowSource
Struct sliding windows from basic windows.
This function is not needed in hardware implementation, should used for direct calculation only.
updateStates :: [Double] -> Loop ()Source
Adding new elements to windows, removing old elements.
Append first argument to second argument.
updateSummariesAndShift :: Loop ()Source
Update sum of elements in sliding window, and sum of squared elements in sliding window, and shift contents of basic windows.
Initial values
initialSysState :: Config -> Int -> SysStateSource
Initial state.
Other than Config
, number of concurrent time series input data is
passed.
initialBasicWindows :: Size -> Size -> Int -> BasicWindowsSource
:: Integer | Random seed. |
-> Size | Basic window size. |
-> Size | Sliding window size. |
-> Int | Sketch size. |
-> IntMap RandomVector |
Initial random vectors.
Pretty printer
Actually, not much pretty.
simpleCorrResult :: CorrResult -> StringSource
Simplified string representation of CorrResult
.
>>>
simpleCorrResult (CorrResult 1 2 10 20 0.5)
"1, 2, 10, 20, 0.5"