{-# LANGUAGE RecordWildCards #-}
module FRP.Rhine.ResamplingBuffer.FIFO where
import Prelude hiding (length, take)
import Data.Sequence
import FRP.Rhine.ResamplingBuffer
import FRP.Rhine.ResamplingBuffer.Timeless
fifoUnbounded :: Monad m => ResamplingBuffer m cl1 cl2 a (Maybe a)
fifoUnbounded = timelessResamplingBuffer AsyncMealy {..} empty
where
amPut as a = return $ a <| as
amGet as = case viewr as of
EmptyR -> return (Nothing, empty)
as' :> a -> return (Just a , as' )
fifoBounded :: Monad m => Int -> ResamplingBuffer m cl1 cl2 a (Maybe a)
fifoBounded threshold = timelessResamplingBuffer AsyncMealy {..} empty
where
amPut as a = return $ take threshold $ a <| as
amGet as = case viewr as of
EmptyR -> return (Nothing, empty)
as' :> a -> return (Just a , as' )
fifoWatch :: Monad m => ResamplingBuffer m cl1 cl2 a (Maybe a, Int)
fifoWatch = timelessResamplingBuffer AsyncMealy {..} empty
where
amPut as a = return $ a <| as
amGet as = case viewr as of
EmptyR -> return ((Nothing, 0 ), empty)
as' :> a -> return ((Just a , length as'), as' )