module System.Touched ( async
, cmd
, onChangeAny
, onChangeAll
, onChangeFile
, Procedure ()
) where
import Control.Concurrent
import Data.Time.Clock
import System.Directory
import System.Touched.Procedure
import System.Touched.OnlyOne
import Control.Applicative ((<$>), (<*>))
import Data.Maybe (isNothing, fromJust, isJust)
data Take = Any | All | First
toFn :: Take -> [UTCTime] -> UTCTime
toFn All = minimum
toFn Any = maximum
toFn First = head
ignoreHidden :: [String] -> [String]
ignoreHidden = filter (not . (=='.') . head)
modified :: File -> IO [Maybe UTCTime]
modified (File path) = (:[]) . Just <$> getModificationTime path
modified (Dir path) = getDirectoryContents path >>=
mapM (liftF . (path++) . ('/':)) . ignoreHidden >>=
concatMapM modified
modified _ = return [Nothing]
data File = File FilePath | Dir FilePath | NotFound FilePath
deriving (Show, Eq)
forceFile :: File -> File
forceFile (Dir x) = File x
forceFile x = x
liftF :: FilePath -> IO File
liftF path = do
f <- doesFileExist path
if f
then return $ File path
else do
d <- doesDirectoryExist path
if d
then return $ Dir path
else return $ NotFound path
liftF' :: FilePath -> IO File
liftF' = fmap forceFile . liftF
concatMapM f = fmap concat . mapM f
justs = map fromJust . filter isJust
onChange :: Take -> [File] -> OnlyOne a b -> IO ()
onChange sel files ot = do
threadDelay 100000
times <- concatMapM modified files
case map fst $ filter (isNothing . snd) (zip files times) of
[] -> restartOld ot (toFn sel $ justs times) >>=
onChange sel files
_ -> putStrLn "Missing files: "
onChange' :: Take -> Bool -> [FilePath] -> Procedure a b -> IO ()
onChange' sel recursive files procfn = do
files' <- sequence $ if recursive then map liftF files else map liftF' files
onChange sel files' (Inactive procfn)
onChangeAny :: Bool -> [FilePath] -> Procedure a b -> IO ()
onChangeAny = onChange' Any
onChangeAll :: Bool -> [FilePath] -> Procedure a b -> IO ()
onChangeAll = onChange' All
onChangeFile :: FilePath -> Procedure a b -> IO ()
onChangeFile file = onChange' First False [file]