module Slab.Watch
  ( run
  ) where

import Control.Concurrent (threadDelay)
import Control.Monad (forever)
import System.Directory (canonicalizePath)
import System.FSNotify
import System.FilePath (makeRelative, takeExtension, (</>))

--------------------------------------------------------------------------------
run :: FilePath -> (FilePath -> IO ()) -> IO ()
run :: String -> (String -> IO ()) -> IO ()
run String
srcDir String -> IO ()
update = do
  String -> IO ()
putStrLn String
"Watching..."
  (WatchManager -> IO ()) -> IO ()
forall a. (WatchManager -> IO a) -> IO a
withManager ((WatchManager -> IO ()) -> IO ())
-> (WatchManager -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \WatchManager
mgr -> do
    -- Start a watching job in the background.
    -- TODO We should debounce multiple Modified events occurring in a short
    -- amount of time on the same file. Typically saving a file with Vim will
    -- trigger two Modified events on a .slab file.
    IO ()
_ <-
      WatchManager -> String -> ActionPredicate -> Action -> IO (IO ())
watchTree
        WatchManager
mgr
        String
srcDir
        ( \Event
e -> do
            case Event
e of
              Modified String
path UTCTime
_ EventIsDirectory
_ | String -> String
takeExtension String
path String -> String -> Bool
forall a. Eq a => a -> a -> Bool
== String
".slab" -> Bool
True
              Event
_ -> Bool
False
        )
        ( \Event
e -> do
            String
srcDir' <- String -> IO String
canonicalizePath String
srcDir
            let path :: String
path = String
srcDir String -> String -> String
</> String -> String -> String
makeRelative String
srcDir' (Event -> String
eventPath Event
e)
            String -> IO ()
update String
path
        )

    -- Sleep forever (until interrupted).
    IO () -> IO ()
forall (f :: * -> *) a b. Applicative f => f a -> f b
forever (IO () -> IO ()) -> IO () -> IO ()
forall a b. (a -> b) -> a -> b
$ Int -> IO ()
threadDelay Int
1000000