module System.Delta.Poll ( createPollWatcher
) where
import Control.Applicative ((<$>))
import Control.Concurrent
import Control.Monad (foldM)
import qualified Data.Map as M
import Data.Maybe (catMaybes)
import FRP.Sodium
import System.Delta.Base
import System.Delta.Class
import System.Directory
import System.FilePath
import Data.List (isPrefixOf)
createPollWatcher :: Int
-> FilePath
-> IO FileWatcher
createPollWatcher secs path = do
(changedEvent, pushChanged) <- sync $ newEvent
(deletedEvent, pushDeleted) <- sync $ newEvent
(newFileEvent, pushNewFile) <- sync $ newEvent
canonPath <- canonicalizePath path
watcherId <- startWatchThread canonPath pushNewFile pushDeleted pushChanged secs
return $ FileWatcher newFileEvent deletedEvent changedEvent (killThread watcherId)
recursiveDescent path =
M.filterWithKey (\_ -> not . fileInfoIsDir) <$>
recursiveDescent' M.empty path
recursiveDescent' :: M.Map FilePath FileInfo
-> FilePath
-> IO (M.Map FilePath FileInfo)
recursiveDescent' visited path | M.member path visited = return visited
recursiveDescent' visited path = do
isDir <- doesDirectoryExist path
inf <- mkFileInfo path
let visitedWithCurrent = M.insert path inf visited
if not isDir
then return $ visitedWithCurrent
else do
contentsUnfiltered <- getDirectoryContents path
let contentsFiltered = filter (\x -> x /= "." && x /= "..") contentsUnfiltered
contentsAbs = (combine path) <$> contentsFiltered
foldM recursiveDescent' visitedWithCurrent contentsAbs
diffChangedFiles :: M.Map FilePath FileInfo
-> M.Map FilePath FileInfo
-> [FileInfo]
diffChangedFiles before after =
catMaybes . M.elems $ M.intersectionWith f before after
where
f beforeInfo afterInfo =
if fileInfoTimestamp beforeInfo < fileInfoTimestamp afterInfo
then Just afterInfo
else Nothing
diffNewFiles :: M.Map FilePath FileInfo
-> M.Map FilePath FileInfo
-> [FileInfo]
diffNewFiles before after = M.elems $ M.difference after before
diffDeletedFiles :: M.Map FilePath FileInfo
-> M.Map FilePath FileInfo
-> [FileInfo]
diffDeletedFiles before after = M.elems $ M.difference before after
startWatchThread :: FilePath
-> (FilePath -> Reactive ())
-> (FilePath -> Reactive ())
-> (FilePath -> Reactive ())
-> Int
-> IO ThreadId
startWatchThread path pushNew pushDeleted pushChanged secs = do
curr <- recursiveDescent path
forkIO $ go curr
where
go last = do
threadDelay $ secs * 1000 * 1000
curr <- recursiveDescent path
sync $ mapM_ (pushChanged) (fileInfoPath <$> diffChangedFiles last curr)
sync $ mapM_ (pushNew ) (fileInfoPath <$> diffNewFiles last curr )
sync $ mapM_ (pushDeleted) (fileInfoPath <$> diffDeletedFiles last curr)
go curr