{-# LANGUAGE CPP, Rank2Types #-} module TailTypes ( Interval, fromInterval, TailTarget(..), TailRuntime(..), TailMatch(..), TailAction(..), TailMatches, Tail(..), tailName, tailErrMsg ) where import qualified System.Posix.Types import qualified System.Posix.IO import qualified Text.Regex #ifdef INOTIFY import qualified System.INotify as INotify #endif import Display newtype Interval = Interval Int instance Show Interval where show (Interval x) = show (fromIntegral x / 1000000.0) instance Read Interval where readsPrec n s = map (\(x,s) -> (Interval $ floor (1000000.0 * x), s)) $ readsPrec n s fromInterval (Interval x) = x data TailTarget = TailPath !FilePath | TailFd !System.Posix.Types.Fd instance Show TailTarget where show (TailFd 0) = "-" show (TailFd x) = '&':(show x) show (TailPath path) = path instance Read TailTarget where readsPrec _ "-" = [(TailFd System.Posix.IO.stdInput, "")] readsPrec n ('&':s) = map (\(f,s) -> (TailFd f, s)) $ readsPrec n s readsPrec _ s = [(TailPath s, "")] data TailMatch = MatchAll | MatchRegex !Text.Regex.Regex | MatchNotRegex !Text.Regex.Regex data TailAction = ActionNone | ActionHide | ActionColor !TermColor | ActionSubst !String | ActionExecute !String type TailMatches = [(TailMatch, TailAction)] data Tail = Tail{ tailTarg :: TailTarget, tailPollInterval :: !Interval, tailReopenInterval :: !Interval, #ifdef INOTIFY tailPollINotify :: !Bool, tailReopenINotify :: !Bool, #endif tailBegin :: !Bool, tailTimeFmt :: !String, tailMatches :: !TailMatches } tailName = show . tailTarg tailErrMsg t msg = errMsg ("ztail " ++ tailName t ++ ": " ++ msg) data TailRuntime = TailRuntime { trUnlock :: forall a. IO a -> IO a , trText :: Tail -> String -> IO () #ifdef INOTIFY , trINotify :: Maybe INotify.INotify #endif }