-
Notifications
You must be signed in to change notification settings - Fork 0
/
Copy pathUtil.hs
100 lines (89 loc) · 2.38 KB
/
Util.hs
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
69
70
71
72
73
74
75
76
77
78
79
80
81
82
83
84
85
86
87
88
89
90
91
92
93
94
95
96
97
98
99
100
{-# LANGUAGE FlexibleContexts #-}
module LndClient.Util
( retrySilent,
retryKatip,
safeFromIntegral,
spawnLink,
withSpawnLink,
readTChanTimeout,
maybeDeadlock,
MicroSecondsDelay (..),
)
where
import Control.Exception
import LndClient.Data.Type
import LndClient.Import.External
newtype MicroSecondsDelay = MicroSecondsDelay Int
retrySilent ::
MonadIO m => m (Either LndError a) -> m (Either LndError a)
retrySilent = this 0
where
this (attempt0 :: Integer) f = do
let attempt = attempt0 + 1
res <- f
case res of
Left (LndError _) ->
if attempt > 5
then pure res
else do
liftIO $ delay 300000
this attempt f
_ ->
pure res
retryKatip ::
KatipContext m => m (Either LndError a) -> m (Either LndError a)
retryKatip = this 0
where
this (attempt0 :: Integer) f = do
let attempt = attempt0 + 1
res <- f
case res of
Left (LndError _) ->
if attempt > 5
then pure res
else do
liftIO $ delay 300000
this attempt f
_ ->
pure res
safeFromIntegral ::
forall a b. (Integral a, Integral b, Bounded b) => a -> Maybe b
safeFromIntegral x =
if (intX >= intMin) && (intX <= intMax)
then Just $ fromIntegral x
else Nothing
where
intX = fromIntegral x :: Integer
intMin = fromIntegral (minBound :: b) :: Integer
intMax = fromIntegral (maxBound :: b) :: Integer
spawnLink :: (MonadUnliftIO m) => m a -> m (Async a)
spawnLink x =
withRunInIO $ \run -> do
pid <- async $ run x
link pid
return pid
withSpawnLink :: (MonadUnliftIO m) => m a -> (Async a -> m b) -> m b
withSpawnLink action inner =
withRunInIO $ \run ->
withAsync
(run action)
( \pid -> do
link pid
run $ inner pid
)
readTChanTimeout ::
MonadUnliftIO m => MicroSecondsDelay -> TChan a -> m (Maybe a)
readTChanTimeout t x = do
t0 <- liftIO . registerDelay $ coerce t
(join <$>) . maybeDeadlock . atomically $
Just <$> readTChan x
<|> Nothing <$ fini t0
maybeDeadlock :: MonadUnliftIO m => m a -> m (Maybe a)
maybeDeadlock x =
withRunInIO $ \run ->
(Just <$> run x)
`catches` [ Handler $
\BlockedIndefinitelyOnSTM -> return Nothing
]
fini :: TVar Bool -> STM ()
fini = check <=< readTVar