{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
module Control.Watchdog
( watchdog
, watchdogBlank
, watch
, watchImpatiently
, setInitialDelay
, setMaximumDelay
, setMaximumRetries
, setResetDuration
, setLoggingAction
, defaultLogger
, showLogger
, silentLogger
, formatWatchdogError
, WatchdogLogger
, WatchdogAction
) where
import Control.Applicative
import Control.Concurrent
import Control.Monad.State.Strict
import Data.Semigroup (Semigroup, (<>))
import Data.String (IsString, fromString)
import Data.Time
data WatchdogState e = WatchdogState { forall e. WatchdogState e -> Int
wcInitialDelay :: Int
, forall e. WatchdogState e -> Int
wcMaximumDelay :: Int
, forall e. WatchdogState e -> Int
wcResetDuration :: Int
, forall e. WatchdogState e -> Integer
wcMaximumRetries :: Integer
, forall e. WatchdogState e -> WatchdogLogger e
wcLoggingAction :: WatchdogLogger e
}
data WatchdogTaskStatus e a = FailedImmediately e
| FailedAfterAWhile e
| CompletedSuccessfully a
newtype WatchdogAction e a = WA { forall e a. WatchdogAction e a -> StateT (WatchdogState e) IO a
runWA :: StateT (WatchdogState e) IO a }
deriving ( forall a b. a -> WatchdogAction e b -> WatchdogAction e a
forall a b. (a -> b) -> WatchdogAction e a -> WatchdogAction e b
forall e a b. a -> WatchdogAction e b -> WatchdogAction e a
forall e a b. (a -> b) -> WatchdogAction e a -> WatchdogAction e b
forall (f :: * -> *).
(forall a b. (a -> b) -> f a -> f b)
-> (forall a b. a -> f b -> f a) -> Functor f
<$ :: forall a b. a -> WatchdogAction e b -> WatchdogAction e a
$c<$ :: forall e a b. a -> WatchdogAction e b -> WatchdogAction e a
fmap :: forall a b. (a -> b) -> WatchdogAction e a -> WatchdogAction e b
$cfmap :: forall e a b. (a -> b) -> WatchdogAction e a -> WatchdogAction e b
Functor, forall e. Functor (WatchdogAction e)
forall a. a -> WatchdogAction e a
forall e a. a -> WatchdogAction e a
forall a b.
WatchdogAction e a -> WatchdogAction e b -> WatchdogAction e a
forall a b.
WatchdogAction e a -> WatchdogAction e b -> WatchdogAction e b
forall a b.
WatchdogAction e (a -> b)
-> WatchdogAction e a -> WatchdogAction e b
forall e a b.
WatchdogAction e a -> WatchdogAction e b -> WatchdogAction e a
forall e a b.
WatchdogAction e a -> WatchdogAction e b -> WatchdogAction e b
forall e a b.
WatchdogAction e (a -> b)
-> WatchdogAction e a -> WatchdogAction e b
forall a b c.
(a -> b -> c)
-> WatchdogAction e a -> WatchdogAction e b -> WatchdogAction e c
forall e a b c.
(a -> b -> c)
-> WatchdogAction e a -> WatchdogAction e b -> WatchdogAction e c
forall (f :: * -> *).
Functor f
-> (forall a. a -> f a)
-> (forall a b. f (a -> b) -> f a -> f b)
-> (forall a b c. (a -> b -> c) -> f a -> f b -> f c)
-> (forall a b. f a -> f b -> f b)
-> (forall a b. f a -> f b -> f a)
-> Applicative f
<* :: forall a b.
WatchdogAction e a -> WatchdogAction e b -> WatchdogAction e a
$c<* :: forall e a b.
WatchdogAction e a -> WatchdogAction e b -> WatchdogAction e a
*> :: forall a b.
WatchdogAction e a -> WatchdogAction e b -> WatchdogAction e b
$c*> :: forall e a b.
WatchdogAction e a -> WatchdogAction e b -> WatchdogAction e b
liftA2 :: forall a b c.
(a -> b -> c)
-> WatchdogAction e a -> WatchdogAction e b -> WatchdogAction e c
$cliftA2 :: forall e a b c.
(a -> b -> c)
-> WatchdogAction e a -> WatchdogAction e b -> WatchdogAction e c
<*> :: forall a b.
WatchdogAction e (a -> b)
-> WatchdogAction e a -> WatchdogAction e b
$c<*> :: forall e a b.
WatchdogAction e (a -> b)
-> WatchdogAction e a -> WatchdogAction e b
pure :: forall a. a -> WatchdogAction e a
$cpure :: forall e a. a -> WatchdogAction e a
Applicative, forall e. Applicative (WatchdogAction e)
forall a. WatchdogAction e a
forall a. WatchdogAction e a -> WatchdogAction e [a]
forall a.
WatchdogAction e a -> WatchdogAction e a -> WatchdogAction e a
forall e a. WatchdogAction e a
forall e a. WatchdogAction e a -> WatchdogAction e [a]
forall e a.
WatchdogAction e a -> WatchdogAction e a -> WatchdogAction e a
forall (f :: * -> *).
Applicative f
-> (forall a. f a)
-> (forall a. f a -> f a -> f a)
-> (forall a. f a -> f [a])
-> (forall a. f a -> f [a])
-> Alternative f
many :: forall a. WatchdogAction e a -> WatchdogAction e [a]
$cmany :: forall e a. WatchdogAction e a -> WatchdogAction e [a]
some :: forall a. WatchdogAction e a -> WatchdogAction e [a]
$csome :: forall e a. WatchdogAction e a -> WatchdogAction e [a]
<|> :: forall a.
WatchdogAction e a -> WatchdogAction e a -> WatchdogAction e a
$c<|> :: forall e a.
WatchdogAction e a -> WatchdogAction e a -> WatchdogAction e a
empty :: forall a. WatchdogAction e a
$cempty :: forall e a. WatchdogAction e a
Alternative
, forall e. Applicative (WatchdogAction e)
forall a. a -> WatchdogAction e a
forall e a. a -> WatchdogAction e a
forall a b.
WatchdogAction e a -> WatchdogAction e b -> WatchdogAction e b
forall a b.
WatchdogAction e a
-> (a -> WatchdogAction e b) -> WatchdogAction e b
forall e a b.
WatchdogAction e a -> WatchdogAction e b -> WatchdogAction e b
forall e a b.
WatchdogAction e a
-> (a -> WatchdogAction e b) -> WatchdogAction e b
forall (m :: * -> *).
Applicative m
-> (forall a b. m a -> (a -> m b) -> m b)
-> (forall a b. m a -> m b -> m b)
-> (forall a. a -> m a)
-> Monad m
return :: forall a. a -> WatchdogAction e a
$creturn :: forall e a. a -> WatchdogAction e a
>> :: forall a b.
WatchdogAction e a -> WatchdogAction e b -> WatchdogAction e b
$c>> :: forall e a b.
WatchdogAction e a -> WatchdogAction e b -> WatchdogAction e b
>>= :: forall a b.
WatchdogAction e a
-> (a -> WatchdogAction e b) -> WatchdogAction e b
$c>>= :: forall e a b.
WatchdogAction e a
-> (a -> WatchdogAction e b) -> WatchdogAction e b
Monad, forall e. Monad (WatchdogAction e)
forall a. IO a -> WatchdogAction e a
forall e a. IO a -> WatchdogAction e a
forall (m :: * -> *).
Monad m -> (forall a. IO a -> m a) -> MonadIO m
liftIO :: forall a. IO a -> WatchdogAction e a
$cliftIO :: forall e a. IO a -> WatchdogAction e a
MonadIO, MonadState (WatchdogState e))
type WatchdogLogger e = e
-> Maybe Int
-> IO ()
defaultConf :: WatchdogState String
defaultConf :: WatchdogState String
defaultConf = forall e. WatchdogState e
blankConf { wcLoggingAction :: WatchdogLogger String
wcLoggingAction = WatchdogLogger String
defaultLogger }
blankConf :: WatchdogState e
blankConf :: forall e. WatchdogState e
blankConf = WatchdogState { wcInitialDelay :: Int
wcInitialDelay = Int
1 forall a. Num a => a -> a -> a
* Int
10 forall a b. (Num a, Integral b) => a -> b -> a
^ (Integer
6::Integer)
, wcMaximumDelay :: Int
wcMaximumDelay = Int
300 forall a. Num a => a -> a -> a
* Int
10 forall a b. (Num a, Integral b) => a -> b -> a
^ (Integer
6::Integer)
, wcMaximumRetries :: Integer
wcMaximumRetries = Integer
10
, wcResetDuration :: Int
wcResetDuration = Int
30 forall a. Num a => a -> a -> a
* Int
10 forall a b. (Num a, Integral b) => a -> b -> a
^ (Integer
6::Integer)
, wcLoggingAction :: WatchdogLogger e
wcLoggingAction = forall e. WatchdogLogger e
silentLogger
}
watchdog :: WatchdogAction String a -> IO a
watchdog :: forall a. WatchdogAction String a -> IO a
watchdog = forall e a. WatchdogState e -> WatchdogAction e a -> IO a
watchdogWith WatchdogState String
defaultConf
watchdogBlank :: WatchdogAction e a -> IO a
watchdogBlank :: forall e a. WatchdogAction e a -> IO a
watchdogBlank = forall e a. WatchdogState e -> WatchdogAction e a -> IO a
watchdogWith forall e. WatchdogState e
blankConf
watchdogWith :: WatchdogState e -> WatchdogAction e a -> IO a
watchdogWith :: forall e a. WatchdogState e -> WatchdogAction e a -> IO a
watchdogWith WatchdogState e
conf WatchdogAction e a
action = forall (m :: * -> *) s a. Monad m => StateT s m a -> s -> m a
evalStateT (forall e a. WatchdogAction e a -> StateT (WatchdogState e) IO a
runWA WatchdogAction e a
action) WatchdogState e
conf
setInitialDelay :: Int -> WatchdogAction e ()
setInitialDelay :: forall e. Int -> WatchdogAction e ()
setInitialDelay Int
delay = forall s (m :: * -> *). MonadState s m => (s -> s) -> m ()
modify (\WatchdogState e
conf -> WatchdogState e
conf { wcInitialDelay :: Int
wcInitialDelay = Int
delay })
setMaximumDelay :: Int -> WatchdogAction e ()
setMaximumDelay :: forall e. Int -> WatchdogAction e ()
setMaximumDelay Int
delay = forall s (m :: * -> *). MonadState s m => (s -> s) -> m ()
modify (\WatchdogState e
conf -> WatchdogState e
conf { wcMaximumDelay :: Int
wcMaximumDelay = Int
delay })
setResetDuration :: Int -> WatchdogAction e ()
setResetDuration :: forall e. Int -> WatchdogAction e ()
setResetDuration Int
duration = forall s (m :: * -> *). MonadState s m => (s -> s) -> m ()
modify (\WatchdogState e
conf -> WatchdogState e
conf { wcResetDuration :: Int
wcResetDuration = Int
duration })
setMaximumRetries :: Integer -> WatchdogAction e ()
setMaximumRetries :: forall e. Integer -> WatchdogAction e ()
setMaximumRetries Integer
retries = forall s (m :: * -> *). MonadState s m => (s -> s) -> m ()
modify (\WatchdogState e
conf -> WatchdogState e
conf { wcMaximumRetries :: Integer
wcMaximumRetries = Integer
retries })
setLoggingAction :: WatchdogLogger e -> WatchdogAction e ()
setLoggingAction :: forall e. WatchdogLogger e -> WatchdogAction e ()
setLoggingAction WatchdogLogger e
f = forall s (m :: * -> *). MonadState s m => (s -> s) -> m ()
modify (\WatchdogState e
conf -> WatchdogState e
conf { wcLoggingAction :: WatchdogLogger e
wcLoggingAction = WatchdogLogger e
f })
watch :: IO (Either e a) -> WatchdogAction e a
watch :: forall e a. IO (Either e a) -> WatchdogAction e a
watch IO (Either e a)
task = do
WatchdogState e
conf <- forall s (m :: * -> *). MonadState s m => m s
get
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO forall a b. (a -> b) -> a -> b
$ WatchdogState e -> Int -> IO a
go WatchdogState e
conf (forall e. WatchdogState e -> Int
wcInitialDelay WatchdogState e
conf)
where
go :: WatchdogState e -> Int -> IO a
go WatchdogState e
conf Int
errorDelay = do
WatchdogTaskStatus e a
status <- forall e a. Int -> IO (Either e a) -> IO (WatchdogTaskStatus e a)
timeTask (forall e. WatchdogState e -> Int
wcResetDuration WatchdogState e
conf) IO (Either e a)
task
case WatchdogTaskStatus e a
status of
CompletedSuccessfully a
result -> forall (m :: * -> *) a. Monad m => a -> m a
return a
result
FailedAfterAWhile e
err -> do
let errorDelay' :: Int
errorDelay' = forall e. WatchdogState e -> Int
wcInitialDelay WatchdogState e
conf
loggingAction :: WatchdogLogger e
loggingAction = forall e. WatchdogState e -> WatchdogLogger e
wcLoggingAction WatchdogState e
conf
WatchdogLogger e
loggingAction e
err forall a. Maybe a
Nothing
WatchdogState e -> Int -> IO a
go WatchdogState e
conf Int
errorDelay'
FailedImmediately e
err -> do
let errorDelay' :: Int
errorDelay' =
forall a. Ord a => a -> a -> a
min (Int
errorDelay forall a. Num a => a -> a -> a
* Int
2) (forall e. WatchdogState e -> Int
wcMaximumDelay WatchdogState e
conf)
loggingAction :: WatchdogLogger e
loggingAction = forall e. WatchdogState e -> WatchdogLogger e
wcLoggingAction WatchdogState e
conf
WatchdogLogger e
loggingAction e
err (forall a. a -> Maybe a
Just Int
errorDelay)
Int -> IO ()
threadDelay Int
errorDelay
WatchdogState e -> Int -> IO a
go WatchdogState e
conf Int
errorDelay'
watchImpatiently :: IO (Either e b) -> WatchdogAction e (Either e b)
watchImpatiently :: forall e b. IO (Either e b) -> WatchdogAction e (Either e b)
watchImpatiently IO (Either e b)
task = do
WatchdogState e
conf <- forall s (m :: * -> *). MonadState s m => m s
get
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO forall a b. (a -> b) -> a -> b
$ WatchdogState e -> Integer -> Int -> IO (Either e b)
go WatchdogState e
conf Integer
0 (forall e. WatchdogState e -> Int
wcInitialDelay WatchdogState e
conf)
where
go :: WatchdogState e -> Integer -> Int -> IO (Either e b)
go WatchdogState e
conf Integer
retries Int
errorDelay = do
WatchdogTaskStatus e b
status <- forall e a. Int -> IO (Either e a) -> IO (WatchdogTaskStatus e a)
timeTask (forall e. WatchdogState e -> Int
wcResetDuration WatchdogState e
conf) IO (Either e b)
task
case WatchdogTaskStatus e b
status of
CompletedSuccessfully b
result -> forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ forall a b. b -> Either a b
Right b
result
FailedAfterAWhile e
err ->
if Integer
retries forall a. Ord a => a -> a -> Bool
>= forall e. WatchdogState e -> Integer
wcMaximumRetries WatchdogState e
conf
then forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ forall a b. a -> Either a b
Left e
err
else do
let errorDelay' :: Int
errorDelay' = forall e. WatchdogState e -> Int
wcInitialDelay WatchdogState e
conf
loggingAction :: WatchdogLogger e
loggingAction = forall e. WatchdogState e -> WatchdogLogger e
wcLoggingAction WatchdogState e
conf
WatchdogLogger e
loggingAction e
err forall a. Maybe a
Nothing
WatchdogState e -> Integer -> Int -> IO (Either e b)
go WatchdogState e
conf (Integer
retries forall a. Num a => a -> a -> a
+ Integer
1) Int
errorDelay'
FailedImmediately e
err ->
if Integer
retries forall a. Ord a => a -> a -> Bool
>= forall e. WatchdogState e -> Integer
wcMaximumRetries WatchdogState e
conf
then forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ forall a b. a -> Either a b
Left e
err
else do
let errorDelay' :: Int
errorDelay' =
forall a. Ord a => a -> a -> a
min (Int
errorDelay forall a. Num a => a -> a -> a
* Int
2) (forall e. WatchdogState e -> Int
wcMaximumDelay WatchdogState e
conf)
loggingAction :: WatchdogLogger e
loggingAction = forall e. WatchdogState e -> WatchdogLogger e
wcLoggingAction WatchdogState e
conf
WatchdogLogger e
loggingAction e
err (forall a. a -> Maybe a
Just Int
errorDelay)
Int -> IO ()
threadDelay Int
errorDelay
WatchdogState e -> Integer -> Int -> IO (Either e b)
go WatchdogState e
conf (Integer
retries forall a. Num a => a -> a -> a
+ Integer
1) Int
errorDelay'
defaultLogger :: WatchdogLogger String
defaultLogger :: WatchdogLogger String
defaultLogger String
taskErr Maybe Int
delay = String -> IO ()
putStrLn forall a b. (a -> b) -> a -> b
$ forall str.
(IsString str, Semigroup str) =>
str -> Maybe Int -> str
formatWatchdogError String
taskErr Maybe Int
delay
showLogger :: (Show e) => WatchdogLogger e
showLogger :: forall e. Show e => WatchdogLogger e
showLogger e
err = WatchdogLogger String
defaultLogger (forall a. Show a => a -> String
show e
err)
silentLogger :: WatchdogLogger e
silentLogger :: forall e. WatchdogLogger e
silentLogger e
_ Maybe Int
_ = forall (m :: * -> *) a. Monad m => a -> m a
return ()
formatWatchdogError :: (IsString str, Semigroup str)
=> str
-> Maybe Int
-> str
formatWatchdogError :: forall str.
(IsString str, Semigroup str) =>
str -> Maybe Int -> str
formatWatchdogError str
taskErr Maybe Int
Nothing =
str
"Watchdog: Error executing task (" forall a. Semigroup a => a -> a -> a
<> str
taskErr forall a. Semigroup a => a -> a -> a
<> str
") - trying again immediately."
formatWatchdogError str
taskErr (Just Int
delay) =
let asNominalDiffTime :: NominalDiffTime
asNominalDiffTime :: NominalDiffTime
asNominalDiffTime = forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
delay forall a. Fractional a => a -> a -> a
/ NominalDiffTime
10 forall a b. (Num a, Integral b) => a -> b -> a
^ (Integer
6 :: Integer)
in str
"Watchdog: Error executing task (" forall a. Semigroup a => a -> a -> a
<> str
taskErr forall a. Semigroup a => a -> a -> a
<> str
") - waiting"
forall a. Semigroup a => a -> a -> a
<> str
" " forall a. Semigroup a => a -> a -> a
<> forall a. IsString a => String -> a
fromString (forall a. Show a => a -> String
show NominalDiffTime
asNominalDiffTime) forall a. Semigroup a => a -> a -> a
<> str
" before trying again."
timeTask :: Int -> IO (Either e a) -> IO (WatchdogTaskStatus e a)
timeTask :: forall e a. Int -> IO (Either e a) -> IO (WatchdogTaskStatus e a)
timeTask Int
resetDuration IO (Either e a)
task = do
UTCTime
start <- IO UTCTime
getCurrentTime
Either e a
status <- IO (Either e a)
task
UTCTime
stop <- IO UTCTime
getCurrentTime
case Either e a
status of
Right a
result -> forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ forall e a. a -> WatchdogTaskStatus e a
CompletedSuccessfully a
result
Left e
err ->
let cutOff :: NominalDiffTime
cutOff = forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
resetDuration forall a. Fractional a => a -> a -> a
/ NominalDiffTime
10 forall a b. (Num a, Integral b) => a -> b -> a
^ (Integer
6 :: Integer)
in if UTCTime -> UTCTime -> NominalDiffTime
diffUTCTime UTCTime
stop UTCTime
start forall a. Ord a => a -> a -> Bool
< NominalDiffTime
cutOff
then forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ forall e a. e -> WatchdogTaskStatus e a
FailedImmediately e
err
else forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ forall e a. e -> WatchdogTaskStatus e a
FailedAfterAWhile e
err