Skip to content

Commit

Permalink
Minor cleanup
Browse files Browse the repository at this point in the history
  • Loading branch information
ozataman committed Mar 18, 2015
1 parent 15f3219 commit e9a6d3c
Showing 1 changed file with 6 additions and 11 deletions.
17 changes: 6 additions & 11 deletions src/Control/Retry.hs
@@ -1,11 +1,6 @@
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE TypeSynonymInstances #-}
{-# LANGUAGE BangPatterns #-}
{-# LANGUAGE CPP #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE ViewPatterns #-}

Expand Down Expand Up @@ -72,11 +67,11 @@ import Prelude hiding (catch)


-------------------------------------------------------------------------------
-- | A 'RetryPolicy' is a function that takes an iteration number and
-- | A 'RetryPolicyM' is a function that takes an iteration number and
-- possibly returns a delay in microseconds. *Nothing* implies we have
-- reached the retry limit.
--
-- Please note that 'RetryPolicy' is a 'Monoid'. You can collapse
-- Please note that 'RetryPolicyM' is a 'Monoid'. You can collapse
-- multiple strategies into one using 'mappend' or '<>'. The semantics
-- of this combination are as follows:
--
Expand All @@ -102,17 +97,17 @@ import Prelude hiding (catch)
--
-- >> def = constantDelay 50000 <> limitRetries 5
--
-- For anything more complex, just define your own 'RetryPolicy':
-- For anything more complex, just define your own 'RetryPolicyM':
--
-- >> myPolicy = RetryPolicy $ \ n -> if n > 10 then Just 1000 else Just 10000
-- >> myPolicy = retryPolicy $ \ n -> if n > 10 then Just 1000 else Just 10000
--
-- Since 0.7.
newtype RetryPolicyM m = RetryPolicyM { getRetryPolicyM :: Int -> m (Maybe Int) }


-- | Simplified 'RetryPolicyM' without any use of the monadic context in
-- determining policy. Mostly maintains backwards compatitibility with
-- type signatures pre 0.7.
-- type signatures pre-0.7.
type RetryPolicy = forall m . Monad m => RetryPolicyM m


Expand All @@ -131,7 +126,7 @@ instance Monad m => Monoid (RetryPolicyM m) where
-------------------------------------------------------------------------------
-- | Helper for making simplified policies that don't use the monadic
-- context.
retryPolicy :: Monad m => (Int -> Maybe Int) -> RetryPolicyM m
retryPolicy :: (Int -> Maybe Int) -> RetryPolicy
retryPolicy f = RetryPolicyM $ \ i -> return (f i)


Expand Down

0 comments on commit e9a6d3c

Please sign in to comment.