--------------------------------------------------------------------------------
module Patat.AutoAdvance
    ( autoAdvance
    ) where


--------------------------------------------------------------------------------
import           Control.Concurrent      (forkIO, threadDelay)
import qualified Control.Concurrent.Chan as Chan
import           Control.Monad           (forever)
import qualified Data.IORef              as IORef
import           Data.Time               (diffUTCTime, getCurrentTime)
import           Patat.Presentation      (PresentationCommand (..))


--------------------------------------------------------------------------------
-- | This function takes an existing channel for presentation commands
-- (presumably coming from human input) and creates a new one that /also/ sends
-- a 'Forward' command if nothing happens for N seconds.
autoAdvance
    :: Int
    -> Chan.Chan PresentationCommand
    -> IO (Chan.Chan PresentationCommand)
autoAdvance :: Int -> Chan PresentationCommand -> IO (Chan PresentationCommand)
autoAdvance Int
delaySeconds Chan PresentationCommand
existingChan = do
    let delay :: Int
delay = Int
delaySeconds forall a. Num a => a -> a -> a
* Int
1000  -- We are working with ms in this function

    Chan PresentationCommand
newChan         <- forall a. IO (Chan a)
Chan.newChan
    IORef UTCTime
latestCommandAt <- forall a. a -> IO (IORef a)
IORef.newIORef forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< IO UTCTime
getCurrentTime

    -- This is a thread that copies 'existingChan' to 'newChan', and writes
    -- whenever the latest command was to 'latestCommandAt'.
    ThreadId
_ <- IO () -> IO ThreadId
forkIO forall a b. (a -> b) -> a -> b
$ forall (f :: * -> *) a b. Applicative f => f a -> f b
forever forall a b. (a -> b) -> a -> b
$ do
        PresentationCommand
cmd <- forall a. Chan a -> IO a
Chan.readChan Chan PresentationCommand
existingChan
        IO UTCTime
getCurrentTime forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= forall a. IORef a -> a -> IO ()
IORef.writeIORef IORef UTCTime
latestCommandAt
        forall a. Chan a -> a -> IO ()
Chan.writeChan Chan PresentationCommand
newChan PresentationCommand
cmd

    -- This is a thread that waits around 'delay' seconds and then checks if
    -- there's been a more recent command.  If not, we write a 'Forward'.
    ThreadId
_ <- IO () -> IO ThreadId
forkIO forall a b. (a -> b) -> a -> b
$ forall (f :: * -> *) a b. Applicative f => f a -> f b
forever forall a b. (a -> b) -> a -> b
$ do
        UTCTime
current <- IO UTCTime
getCurrentTime
        UTCTime
latest  <- forall a. IORef a -> IO a
IORef.readIORef IORef UTCTime
latestCommandAt
        let elapsed :: Int
elapsed = forall a b. (RealFrac a, Integral b) => a -> b
floor forall a b. (a -> b) -> a -> b
$ NominalDiffTime
1000 forall a. Num a => a -> a -> a
* (UTCTime
current UTCTime -> UTCTime -> NominalDiffTime
`diffUTCTime` UTCTime
latest) :: Int
        if Int
elapsed forall a. Ord a => a -> a -> Bool
>= Int
delay
            then do
                forall a. Chan a -> a -> IO ()
Chan.writeChan Chan PresentationCommand
newChan PresentationCommand
Forward
                forall a. IORef a -> a -> IO ()
IORef.writeIORef IORef UTCTime
latestCommandAt UTCTime
current
                Int -> IO ()
threadDelay (Int
delay forall a. Num a => a -> a -> a
* Int
1000)
            else do
                let wait :: Int
wait = Int
delay forall a. Num a => a -> a -> a
- Int
elapsed
                Int -> IO ()
threadDelay (Int
wait forall a. Num a => a -> a -> a
* Int
1000)

    forall (m :: * -> *) a. Monad m => a -> m a
return Chan PresentationCommand
newChan