Generalizing functions for batch processing

I’m new to Haskell and i recently learned about applicatives and monads.
Assume that i defined typical function in web service that

  1. recieves data
  2. validates it
  3. gets data from db
  4. processes it
  5. updates data in db
  6. maps result and returns it

Is it possible to generalize this function to batch process data in optimal way? Like validate batch, but if one element is invalid discard operation, fetch data for batch, not just for one element or in multiple calls, when updating db update everything with one call.

It feels like <$> should help with that, but i dont have enough experience to derive such generalization myself.

If such thing possible would like to find an example or an article describing the process

2 Likes

You’re right to be thinking about applicatives! The Haxl library is one approach to this kind of problem. It relies on the fact that the Applicative interface doesn’t allow data dependencies and hence effects can be re-ordered.

4 Likes

A vague sketch:

module Batch (
  Batch, batch,
  fetch, process, postprocess,
) where

import Control.Monad ((>=>))

data Batch u v w f a = MkBatch
  { fetch_       :: u -> f v
  , process_     :: v -> f w
  , postprocess_ :: w -> f a
  } deriving Functor

instance (Applicative f, Monoid v, Monoid w)
      => Applicative (Batch u v w f) where
  pure x = MkBatch
    { fetch_       = \_ -> pure mempty
    , process_     = \_ -> pure mempty
    , postprocess_ = \_ -> pure x
    }
  fs <*> xs = MkBatch
    { fetch_       = \u -> liftA2 (<>) (fetch_   fs u) (fetch_   xs u)
    , process_     = \v -> liftA2 (<>) (process_ fs v) (process_ xs v)
    , postprocess_ = \w -> postprocess_ fs w <*> postprocess_ xs w
    }

batch :: Monad f => Batch u v w f a -> u -> f a
batch MkBatch{fetch_,process_,postprocess_}
  = fetch_ >=> process_ >=> postprocess_

fetch
  :: (Applicative f, Monoid v, Monoid w)
  => (u -> f v) -> Batch u v w f ()
fetch fetch_ = (pure ()){fetch_}

process
  :: (Applicative f, Monoid v, Monoid w)
  => (v -> f w) -> Batch u v w f ()
process process_ = (pure ()){process_}

postprocess
  :: (Applicative f, Monoid v, Monoid w)
  => (w -> f a) -> Batch u v w f a
postprocess postprocess_ = (pure ()){postprocess_}