module Devel.Watch where
import Control.Monad.STM
import Control.Concurrent.STM.TVar
import System.FSNotify
import Control.Monad (forever)
import Control.Concurrent (threadDelay)
# if __GLASGOW_HASKELL__ < 710
import Data.Text (unpack)
import Filesystem.Path.CurrentOS (toText)
#endif
import System.Directory (getCurrentDirectory)
import System.FilePath (pathSeparator)
import Devel.Paths
watch :: TVar Bool -> [FilePath] -> IO ()
watch isDirty includeTargets = do
files <- getFilesToWatch includeTargets
dir <- getCurrentDirectory
let pathsToWatch = map (\fp -> dir ++ (pathSeparator: fp)) files
manager <- startManagerConf defaultConfig
_ <- watchTree manager "." (const True)
# if __GLASGOW_HASKELL__ >= 710
(\event -> do
let getPath :: Event -> FilePath
getPath (Added fp _) = fp
getPath (Modified fp _) = fp
getPath (Removed fp _) = fp
isModified = getPath event `elem` pathsToWatch
atomically $ writeTVar isDirty isModified)
#else
(\event -> do
pathMod' <- case toText $ eventPath event of
Right text -> return $ unpack text
Left text -> fail $ unpack text
let isModified = pathMod' `elem` pathsToWatch
atomically $ writeTVar isDirty isModified)
#endif
_ <- forever $ threadDelay maxBound
stopManager manager
checkForChange :: TVar Bool -> IO ()
checkForChange isDirty =
atomically $ do readTVar isDirty >>= check
writeTVar isDirty False