{-# LANGUAGE OverloadedStrings #-}
{-# OPTIONS_HADDOCK prune #-}
module Core.Program.Notify
( waitForChange
) where
import Control.Concurrent.MVar (newEmptyMVar, putMVar, readMVar)
import Control.Monad.IO.Class (liftIO)
import Core.Data.Structures
import Core.Program.Execute
import Core.Program.Logging
import Core.Program.Unlift
import Data.Foldable (foldrM)
import System.Directory (canonicalizePath)
import System.FSNotify (Event (..), eventPath, watchDir, withManager)
import System.FilePath (dropFileName)
waitForChange :: [FilePath] -> Program τ ()
waitForChange :: forall τ. [FilePath] -> Program τ ()
waitForChange [FilePath]
files =
let f :: FilePath -> Set FilePath -> Set FilePath
f :: FilePath -> Set FilePath -> Set FilePath
f FilePath
path Set FilePath
acc = forall ε. Key ε => ε -> Set ε -> Set ε
insertElement FilePath
path Set FilePath
acc
g :: FilePath -> Set FilePath -> Set FilePath
g :: FilePath -> Set FilePath -> Set FilePath
g FilePath
path Set FilePath
acc = forall ε. Key ε => ε -> Set ε -> Set ε
insertElement (FilePath -> FilePath
dropFileName FilePath
path) Set FilePath
acc
in do
forall τ. Rope -> Program τ ()
info Rope
"Watching for changes"
[FilePath]
canonical <- forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM (forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO forall b c a. (b -> c) -> (a -> b) -> a -> c
. FilePath -> IO FilePath
canonicalizePath) [FilePath]
files
let paths :: Set FilePath
paths = forall (t :: * -> *) a b.
Foldable t =>
(a -> b -> b) -> b -> t a -> b
foldr FilePath -> Set FilePath -> Set FilePath
f forall ε. Key ε => Set ε
emptySet [FilePath]
canonical
let dirs :: Set FilePath
dirs = forall (t :: * -> *) a b.
Foldable t =>
(a -> b -> b) -> b -> t a -> b
foldr FilePath -> Set FilePath -> Set FilePath
g forall ε. Key ε => Set ε
emptySet [FilePath]
files
forall τ α.
((forall β. Program τ β -> IO β) -> IO α) -> Program τ α
withContext forall a b. (a -> b) -> a -> b
$ \forall β. Program τ β -> IO β
runProgram -> do
MVar Bool
block <- forall a. IO (MVar a)
newEmptyMVar
forall a. (WatchManager -> IO a) -> IO a
withManager forall a b. (a -> b) -> a -> b
$ \WatchManager
manager -> do
[IO ()]
stoppers <-
forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
(a -> b -> m b) -> b -> t a -> m b
foldrM
( \FilePath
dir [IO ()]
acc -> do
forall β. Program τ β -> IO β
runProgram (forall α τ. Show α => Rope -> α -> Program τ ()
debugS Rope
"watching" FilePath
dir)
IO ()
stopper <-
WatchManager -> FilePath -> ActionPredicate -> Action -> IO (IO ())
watchDir
WatchManager
manager
FilePath
dir
( \Event
trigger -> case Event
trigger of
Modified FilePath
file UTCTime
_ EventIsDirectory
_ -> do
if forall ε. Key ε => ε -> Set ε -> Bool
containsElement FilePath
file Set FilePath
paths
then Bool
True
else Bool
False
Event
_ -> Bool
False
)
( \Event
trigger -> do
forall β. Program τ β -> IO β
runProgram (forall α τ. Show α => Rope -> α -> Program τ ()
debugS Rope
"trigger" (Event -> FilePath
eventPath Event
trigger))
forall a. MVar a -> a -> IO ()
putMVar MVar Bool
block Bool
False
)
forall (m :: * -> *) a. Monad m => a -> m a
return (IO ()
stopper forall a. a -> [a] -> [a]
: [IO ()]
acc)
)
[]
Set FilePath
dirs
Bool
_ <- forall a. MVar a -> IO a
readMVar MVar Bool
block
forall (t :: * -> *) (m :: * -> *) a.
(Foldable t, Monad m) =>
t (m a) -> m ()
sequence_ [IO ()]
stoppers
forall (m :: * -> *) a. Monad m => a -> m a
return ()
forall τ. Rational -> Program τ ()
sleepThread Rational
0.1