{-# LANGUAGE CPP #-}
module System.FSNotify.Types (
act
, ActionPredicate
, Action
, DebounceFn
, WatchConfig(..)
, WatchMode(..)
, ThreadingMode(..)
, Event(..)
, EventIsDirectory(..)
, EventCallback
, EventChannel
, EventAndActionChannel
, IOEvent
) where
import Control.Concurrent.Chan
import Control.Exception.Safe
import Data.IORef (IORef)
import Data.Time.Clock (UTCTime)
import Prelude hiding (FilePath)
import System.FilePath
data EventIsDirectory = IsFile | IsDirectory
deriving (Int -> EventIsDirectory -> ShowS
[EventIsDirectory] -> ShowS
EventIsDirectory -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [EventIsDirectory] -> ShowS
$cshowList :: [EventIsDirectory] -> ShowS
show :: EventIsDirectory -> String
$cshow :: EventIsDirectory -> String
showsPrec :: Int -> EventIsDirectory -> ShowS
$cshowsPrec :: Int -> EventIsDirectory -> ShowS
Show, EventIsDirectory -> EventIsDirectory -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: EventIsDirectory -> EventIsDirectory -> Bool
$c/= :: EventIsDirectory -> EventIsDirectory -> Bool
== :: EventIsDirectory -> EventIsDirectory -> Bool
$c== :: EventIsDirectory -> EventIsDirectory -> Bool
Eq)
data Event =
Added { Event -> String
eventPath :: FilePath, Event -> UTCTime
eventTime :: UTCTime, Event -> EventIsDirectory
eventIsDirectory :: EventIsDirectory }
| Modified { eventPath :: FilePath, eventTime :: UTCTime, eventIsDirectory :: EventIsDirectory }
| ModifiedAttributes { eventPath :: FilePath, eventTime :: UTCTime, eventIsDirectory :: EventIsDirectory }
| Removed { eventPath :: FilePath, eventTime :: UTCTime, eventIsDirectory :: EventIsDirectory }
| WatchedDirectoryRemoved { eventPath :: FilePath, eventTime :: UTCTime, eventIsDirectory :: EventIsDirectory }
| CloseWrite { eventPath :: FilePath, eventTime :: UTCTime, eventIsDirectory :: EventIsDirectory }
| Unknown { eventPath :: FilePath, eventTime :: UTCTime, eventIsDirectory :: EventIsDirectory, Event -> String
eventString :: String }
deriving (Event -> Event -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Event -> Event -> Bool
$c/= :: Event -> Event -> Bool
== :: Event -> Event -> Bool
$c== :: Event -> Event -> Bool
Eq, Int -> Event -> ShowS
[Event] -> ShowS
Event -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Event] -> ShowS
$cshowList :: [Event] -> ShowS
show :: Event -> String
$cshow :: Event -> String
showsPrec :: Int -> Event -> ShowS
$cshowsPrec :: Int -> Event -> ShowS
Show)
type EventChannel = Chan Event
type EventCallback = Event -> IO ()
type EventAndActionChannel = Chan (Event, Action)
data WatchMode =
WatchModePoll { WatchMode -> Int
watchModePollInterval :: Int }
#ifndef OS_BSD
| WatchModeOS
#endif
data ThreadingMode =
SingleThread
| ThreadPerWatch
| ThreadPerEvent
data WatchConfig = WatchConfig
{ WatchConfig -> WatchMode
confWatchMode :: WatchMode
, WatchConfig -> ThreadingMode
confThreadingMode :: ThreadingMode
, WatchConfig -> SomeException -> IO ()
confOnHandlerException :: SomeException -> IO ()
}
type IOEvent = IORef Event
type ActionPredicate = Event -> Bool
type Action = Event -> IO ()
type DebounceFn = Action -> IO Action
act :: ActionPredicate
act :: Event -> Bool
act Event
_ = Bool
True