
On Fri, Aug 31, 2012 at 05:45:27AM +0100, Richard O'Keefe wrote:
Consider the following interface
type Ord k => Sliding_Window k v
entries :: Sliding_Window k v -> [(k,v)] The cost is expected to be linear in the length of the result. The pairs are listed in increasing order of k.
add :: Ord k => k -> v -> Sliding_Window k v -> Sliding_Window k v precondition: all (< k) [k' | (k',_) <- entries q] The cost should be at most O((log . length . entries) q). post: entries (add k v q) = entries q ++ [(k,v)]
since :: Ord k => k -> Sliding_Window k v -> [(k,v)] answers [(k',v) | (k',v) <- entries q, k' > k] The cost should be at most O((log . length . entries) q + length result)
purge :: Ord k => k -> Sliding_Window k v -> Sliding_Window k v answers q' such that entries q' = [(k',v) | (k',v) <- entries q, k' > k] The cost should be at most O((log . length . entries) q + length [k' | (k',v) <- entries q, k' <= k])
Any search tree implementation will do add and purge in O(log n) time. A finger tree will do add in O(1) and purge in O(log(min(r, n-r))) time, where r in the length of the result. {-# LANGUAGE MultiParamTypeClasses #-} module SlidingWindow where import Data.FingerTree import Data.Foldable import Data.Monoid data Entry k v = Entry k v data Max k = Bot | Lift k deriving (Eq, Ord) instance Ord k => Monoid (Max k) where mempty = Bot mappend = max instance Ord k => Measured (Max k) (Entry k v) where measure (Entry k _) = Lift k newtype SlidingWindow k v = SW (FingerTree (Max k) (Entry k v)) entries :: SlidingWindow k v -> [(k,v)] entries (SW t) = [(k, v) | Entry k v <- toList t] emptySW :: Ord k => SlidingWindow k v emptySW = SW empty add :: Ord k => k -> v -> SlidingWindow k v -> SlidingWindow k v add k v (SW t) = SW (t |> Entry k v) since :: Ord k => k -> SlidingWindow k v -> [(k,v)] since k = entries . purge k purge :: Ord k => k -> SlidingWindow k v -> SlidingWindow k v purge k (SW t) = SW (dropUntil (> Lift k) t)