module Watcher where -- Venzone level REPLer, requested by sm import Paths import Venzone import Terminal.Game hiding ( Event ) import System.FSNotify import qualified Control.Concurrent as CC import qualified Control.Monad as CM import qualified Data.Function as F import qualified System.FilePath as FP watchMode :: FilePath -> IO () watchMode fp = -- kill/launch venzone instance part CC.newChan >>= \chan -> CC.forkIO (levelSpawner fp chan) >> -- file watcher watcher fp chan -- watch file `fp` and sends events to chan `chan` watcher :: FilePath -> CC.Chan Event -> IO () watcher fp chan = withManagerConf conf repJob where -- debounces to 5/100 of a second, again to counter vim frenzy conf :: WatchConfig conf = defaultConfig { confDebounce = Debounce ( 5 / 100 ) } -- repeated IO action repJob :: WatchManager -> IO a repJob mgr = let oneSec = 10 ^ (6 :: Int) in watchChan mgr >> CM.forever (CC.threadDelay oneSec) watchChan :: WatchManager -> IO () watchChan mgr = () <$ watchDirChan mgr dir ff chan -- dir to watch dir :: FilePath dir = FP.dropFileName fp -- only match our specific file (and not vim crap) -- and only add/mod events ff :: Event -> Bool ff e = let ep = eventPath e in isAddMod e && F.on (==) FP.takeFileName ep fp isAddMod :: Event -> Bool isAddMod Modified {} = True isAddMod Added {} = True isAddMod _ = False levelSpawner :: FilePath -> CC.Chan Event -> IO () levelSpawner fp chan = instanceVenzone >>= \ti -> loop ti where instanceVenzone :: IO CC.ThreadId instanceVenzone = CC.forkIO (levelMode fp) loop :: CC.ThreadId -> IO () loop ti = CC.readChan chan >> -- blocks until. We don't care about the specific -- event since it is filtered above CC.killThread ti >> -- to counter vim CC.threadDelay 1000 >> instanceVenzone >>= \ti2 -> loop ti2 -- todo [refactor] [refactor] astrai con normalMode levelMode :: FilePath -> IO () levelMode fp = errorPress $ (bundleStories . (:[]) <$> findSingleStory fp) >>= \gv -> -- todo [refactor] astrarre questa keypress? let gv' = setupGame gv [KeyPress 'd'] in playGame gv' >> return ()