-{-# LANGUAGE CPP #-}
+{-# LANGUAGE CPP #-}
+{-# LANGUAGE OverloadedStrings #-}
-- generic AMQP publisher
import Control.Concurrent
X.catch
(if isDir
then do
+ setCurrentDirectory (inputFile args)
if (initialScan args)
- then getDirectoryContents (inputFile args) >>= mapM_ (\fn -> handleFile publishOneMsg (suffix args) ((inputFile args) ++ "/" ++ fn))
+ then getDirectoryContents "." >>= mapM_ (\fn -> handleFile publishOneMsg (suffix args) fn)
else return()
inotify <- initINotify
wd <-
addWatch
inotify
[CloseWrite, MoveIn]
-#if MIN_VERSION_hinotify(0,3,10)
- (BS.pack (inputFile args))
-#else
- (inputFile args)
-#endif
- (handleEvent publishOneMsg (suffix args) (inputFile args))
+ "."
+ (handleEvent publishOneMsg (suffix args))
hr $ "BEGIN watching " ++ (inputFile args)
_ <- forever $ threadDelay 1000000
removeWatch wd
handleEvent ::
(Maybe String -> BL.ByteString -> IO ())
-> [String]
- -> String
-> Event
-> IO ()
-- just handle closewrite and movedin events
#if MIN_VERSION_hinotify(0,3,10)
-handleEvent func suffixes path (Closed False (Just fileName) True) =
- handleFile func suffixes (path ++ "/" ++ (BS.unpack fileName))
-handleEvent func suffixes path (MovedIn False fileName _) =
- handleFile func suffixes (path ++ "/" ++ (BS.unpack fileName))
+handleEvent func suffixes (Closed False (Just fileName) True) =
+ handleFile func suffixes (BS.unpack fileName)
+handleEvent func suffixes (MovedIn False fileName _) =
+ handleFile func suffixes (BS.unpack fileName)
#else
-handleEvent func suffixes path (Closed False (Just fileName) True) = handleFile func suffixes (path ++ "/" ++ fileName)
-handleEvent func suffixes path (MovedIn False fileName _) = handleFile func suffixes (path ++ "/" ++ fileName)
+handleEvent func suffixes (Closed False (Just fileName) True) = handleFile func suffixes fileName
+handleEvent func suffixes (MovedIn False fileName _) = handleFile func suffixes fileName
#endif
-handleEvent _ _ _ _ = return ()
+handleEvent _ _ _ = return ()
-- | Hotfolder file handler
handleFile ::