Recently, our production stack grinded to a halt. Three AWS Lambda functions, all of which are interdependent, were getting a timeout exception from the RDS data API because a single DB column was too large to download. None of them had any exponential backoff, so they basically froze the DB for all of the other services, which then promptly and repeatedly re-issued requests to their related services, which caused the stack to run at the speed of molasses for about 30m before the entropic system came to a halt.
Exponential backoff in serverless architecture is a big deal, especially when there are unpredictably-janky bottlenecks like the RDS Data API. So I set out this morning to fix the problem and wound up using indexed monads to solve it across several services. In this article, I'll briefly show what indexed monads are and then get into how they can help elegantly and concisely solve messy problems like exponential backdown.
Indexed monad
An indexed monad is a monad that has an input type i
and output type o
. Both are phantom types - they don't correspond to concrete values, but rather they are used to show on a type level what action can follow another action. Justin Woo wrote a great article on how to use indexed monads to build a burger in PureScript. The first "input type" corresponds to the bottom bun, and the first output type are fixings. It proceeds like this:
i |
o |
---|---|
Bottom bun | Potentially several fixings |
Fixings | Potentially more fixings |
Potentially more fixings | Patty |
Patty | Potentially cheese |
Potentially cheese | Top Bun |
Without using indexed monads, you could still pull this off with types like Burger BottomBun
, Burger (List Fixings)
, etc, but the problem is that you couldn't enforce the order
of these things. Indexed monads lets you enforce an order of your monadic binds. The order can be whatever you want - you can have loops back to the beginning, conditional branches, etc.
Enforcing index rules
In Justin's example, he enforces index rules using function signatures:
placeEmptyBun :: BurgerSpec -> IxBurgerBuilder EmptyPlate BottomBunOn BurgerSpec
placeEmptyBun = addIngredient "Bottom Bun"
Building up functions like this creates a nice DSL that will fail if one tries to follow a BottomBun
with an empty plate, which only the most savage, uncouth burger eaters would do (and I've never even seen someone just eat a bottom bun... I can't even imagine it... well I can... but I won't out of principle). However, one of these savage burger eaters could come along and write a new function eatEmptyBun
.
eatEmptyBun :: BurgerSpec -> IxBurgerBuilder BottomBunOn EmptyPlate BurgerSpec
eatEmptyBun = mempty
More generally, anyone can write any burger-building function they want as there's nothing to enforce how function signatures are written.
Back to backoff
In my exponential backoff example, I didn't want this. I wanted to enforce, through the type system, that the next request should always take more time than the previous one. Let's look at that as a table of i
o
types again.
i |
o |
---|---|
Wait a bit | Wait a bit longer |
Wait a bit longer | Wait even longer |
Wait even longer | Wait a small eternity |
Wait a small eternity | Give up |
I don't want anyone to ever go Wait a small eternity -> Wait a bit -> Wait a bit -> Wait a bit -> Wait a bit -> Give up
. It would potentially cause another AWS meltdown.
Typeclasses to the rescue
Typeclasses are just tables that live on a compiler where columns are types to be constrained and rows are constraints. It stands to reason, then, that we can use a typeclass to constrain our i
o
types. So if our indexed monad is Program i o a
, then our typeclass look like:
class ExponentialBackoff i t where
continue :: forall m a. m i i a -> m i t a
instance exponentialBackoff0 :: WaitABit GiveUp
continue :: ...
instance exponentialBackoff1 :: WaitABitLonger GiveUp
instance exponentialBackoff2 :: WaitEvenLonger GiveUp
There's a lot of boilerplate here, so I decided to use purescript-typelevel-peano
to express the recursive relationship in our actual codebase.
class ExponentialBackoff i where
continue :: forall m a. m i i a -> m i Z a
instance exponentialBackoff0 :: Z
continue :: ...
instance exponentialBackoff1 :: (Succ i)
The continue
function comes at the end of an I.do
bloc, which means that once our program finishes executing with a type m (Succ i) (Succ i) a
(where (Succ i) (Succ i)
is the step of backdown we're on - ie (Succ (Succ Z))
would be 2
in our peano-countdown), it will go down by one to m i i a
until i
is Z
(zero), at which point it will execute the continue
for Z
. In our code base, this is the program's termination and graceful cleanup.
The added advantage of using typelevel-representations of integers is that you can calculate the value of the exponential backoff directly from the type by using reflectNat
.
Full example
While our backend code base is (unfortunately) not open-sourced (yet), we've been using a small-ish service called S3Squirrel
to provide in anger examples of how this stuff is used in production. Across our services, we use the backoff
function from the Backoff
typeclass to grab the correct exponential backoff in a monadic context. Since we've pushed this (meaning in the past 18 hours) we've had no AWS meltdowns. w00t! 💯
data S3SquirrelProgramF a
= GetETagForResource String (Maybe String -> a)
| GetS3InfoFromDBOnCacheHit String (Maybe String) (Maybe S3Info -> a)
| DownloadResourceToFile String String (Unit -> a)
| ReadFileToBuffer String (Buffer -> a)
| GenerateUUID (String -> a)
| FreeDelay Number (Unit -> a)
| UploadObjectToS3 String String Buffer (Unit -> a)
| WriteEtagAndS3InfoToDb String (Maybe String) String String (Either Error Unit -> a)
| FreeLog String (Unit -> a)
| FreeThrow Error (Unit -> a)
derive instance functorS3SquirrelProgramF :: Functor S3SquirrelProgramF
derive instance genericS3SquirrelProgramF :: Generic (S3SquirrelProgramF a) _
f :: forall i. Constructors S3SquirrelProgramF (S3SquirrelProgram i i)
f = constructors (wrap <<< liftF :: S3SquirrelProgramF ~> (S3SquirrelProgram i i))
newtype S3SquirrelProgram i o a
= S3SquirrelProgram (Free S3SquirrelProgramF a)
derive instance newtypeS3SquirrelProgram :: Newtype (S3SquirrelProgram i o a) _
instance ixApplicativeS3SquirrelProgram :: IxApplicative S3SquirrelProgram where
ipure = wrap <<< pure
instance ixFunctorS3SquirrelProgram :: IxFunctor S3SquirrelProgram where
imap fx (S3SquirrelProgram x) = S3SquirrelProgram (map fx x)
instance ixApplyS3SquirrelProgram :: IxApply S3SquirrelProgram where
iapply (S3SquirrelProgram fx) (S3SquirrelProgram x) = S3SquirrelProgram (apply fx x)
instance ixBindS3SquirrelProgram :: IxBind S3SquirrelProgram where
ibind (S3SquirrelProgram x) fx = wrap (x >>= (unwrap <<< fx))
instance ixMonadS3SquirrelProgram :: IxMonad S3SquirrelProgram
type SProg (x :: Nat) (y :: Nat)
= S3SquirrelProgram (NProxy x) (NProxy y) Unit
class ProgramOutcome (i :: Nat) where
s3SquirrelNext :: Error -> ResourceInfo -> SProg i Z
class MaxRetries t (i :: Nat) | t -> i
instance maxRetriesS3SquirrelProgram :: MaxRetries (S3SquirrelProgram i i a) (Succ (Succ (Succ Z)))
class Backoff m where
backoff :: (Number -> m Unit) -> m Unit
instance backoffS3SquirrelProgram :: (IsNat x, IsNat i, MaxRetries (S3SquirrelProgram (NProxy i) (NProxy i) a) x) => Backoff (S3SquirrelProgram (NProxy i) (NProxy i)) where
backoff = (#) (2.0 `pow` (toNumber (maxRetries - currentPos)))
where
maxRetries = reflectNat (NProxy :: NProxy x)
currentPos = reflectNat (NProxy :: NProxy i)
instance programOutcomeZ :: ProgramOutcome Z where
s3SquirrelNext e _ = f.freeThrow e
instance programOutcomeSucc :: (IsNat x, ProgramOutcome x) => ProgramOutcome (Succ x) where
s3SquirrelNext e ri =
( Ix.do
S3SquirrelProgram $ pure unit :: SProg (Succ x) x
s3SquirrelProgram ri :: SProg x Z
)
downloadAndWriteToDb :: forall (i :: Nat). IsNat i => ProgramOutcome i => String -> Maybe String -> SProg i Z
downloadAndWriteToDb resourceUrl etag = Ix.do
uuid <- f.generateUUID
let
filename = "/tmp/" <> uuid
f.downloadResourceToFile resourceUrl filename
buffer <- f.readFileToBuffer filename
f.uploadObjectToS3 mknBucket uuid buffer
f.freeLog ("writing to db " <> resourceUrl <> " etag: " <> show etag)
res <-
f.writeEtagAndS3InfoToDb
resourceUrl
etag
mknBucket
uuid
case res of
Left err -> Ix.do
f.freeLog (show err)
backoff f.freeDelay
s3SquirrelNext err { resourceUrl }
Right _ -> S3SquirrelProgram (pure unit)
s3SquirrelProgram :: forall (i :: Nat). IsNat i => ProgramOutcome i => ResourceInfo -> SProg i Z
s3SquirrelProgram { resourceUrl } = Ix.do
etag <- f.getETagForResource resourceUrl
f.freeLog ("got etag " <> show etag <> " for resource " <> resourceUrl)
s3Info' <- f.getS3InfoFromDBOnCacheHit resourceUrl etag
f.freeLog ("got s3info " <> show s3Info')
case s3Info' of
Nothing -> downloadAndWriteToDb resourceUrl etag
Just { bucket, key } -> S3SquirrelProgram (pure unit)
Top comments (0)