Composing State and State transformer actions - haskell

I have several State monad actions. Some of the actions make decisions based on the current state and other input optionally generating result. The two types of actions invoke each other.
I have modeled these two action types with State and StateT Maybe. The following (contrived) example shows my current approach.
{-# LANGUAGE MultiWayIf #-}
import Control.Monad (guard)
import Control.Monad.Identity (runIdentity)
import Control.Monad.Trans.State
type Producer = Int -> State [Int] Int
type MaybeProducer = Int -> StateT [Int] Maybe Int
produce :: Producer
produce n
| n <= 0 = return 0
| otherwise = do accum <- get
let mRes = runStateT (maybeProduce n) accum
if | Just res <- mRes -> StateT $ const (return res)
| otherwise -> do res <- produce (n - 1)
return $ res + n
maybeProduce :: MaybeProducer
maybeProduce n = do guard $ odd n
modify (n:)
mapStateT (return . runIdentity) $
do res <- produce (n - 1)
return $ res + n
I have factored out separating the checks from the actions (thus transforming them into simple State actions) because the check itself is very involved (80% of the work) and provides the bindings needed in the action. I don't want to promote the State actions to StateT Maybe either, because it poses an inaccurate model.
Is there a better or more elegan way that I'm missing? In particular I don't like the mapStateT/runStateT duo, but it seems necessary.
PS: I know the example is actually a Writer, but I used State to better reflect the real case

I don't want to promote the State actions to StateT Maybe either, because it poses an inaccurate model.
What do you mean by "promote"? I can't tell which of these you mean:
Rewrite the definitions of the State actions so that their type is now StateT Maybe, even though they don't rely on Maybe at all;
Use an adapter function that transforms State s a into StateT s Maybe a.
I agree with rejecting (1), but to me that mean either:
Go for (2). One useful tool for this is to use the mmorph library (blog entry).
Rewrite the actions from State s a to use Monad m => StateT s m a.
In the second case, the type is compatible with any Monad m but does not allow the code to assume any specific base monad, so you get the same purity as State s a.
I'd give mmorph a shot. Note that:
State s a = StateT s Identity a;
hoist generalize :: (MFunctor t, Monad m) => t Identity a -> t m a;
And that specializes to hoist generalize :: State s a -> StateT s Maybe a.
EDIT: It's worth nothing that there is an isomorphism between the State s a and forall m. StateT s m a types, given by these inverse functions:
{-# LANGUAGE RankNTypes #-}
import Control.Monad.Morph
import Control.Monad.Trans
import Control.Monad.Trans.State
import Control.Monad.Identity
fwd :: (MFunctor t, Monad m) => t Identity a -> t m a
fwd = hoist generalize
-- The `forall` in the signature forbids callers from demanding any
-- specific choice of type for `m`, which allows *us* to choose
-- `Identity` for `m` here.
bck :: MFunctor t => (forall m. t m a) -> t Identity a
bck = hoist generalize
So the Monad m => StateT s m a and mmorph solutions are, effectively, the same. I prefer using mmorph here, though.

Related

How to create an interface for a stateful component where the state type is opaque?

-- InternalComponent.hs
data ComponentState = ComponentState ...
instance Default ComponentState where ...
componentFunction :: (MonadState InternalComponentState m) => a -> m a
-- Program.hs
data ProgramState = forall cs. ProgramState {
componentState :: cs,
...
}
newtype MyMonad a = MyMonad { runMyMonad :: StateT ProgramState IO a }
myFunction a = do
s <- get
let cs = componentState s
let (r, cs') = runState (componentFunction a) cs
put $ s { componentState = cs' }
return r
What I want is to be able to use the componentFunction inside of MyMonad (in myFunction, as presented in the example), without being particularly interested in the actual type of the state the component requires. Keeping the component state inside of my own state isn't a requirement, but that's as far as my ability to use state in Haskell goes.
This can really be viewed as an equivalent of an implementation of a stateful interface in another programming language: instantiation of the interface with some implementation provides default state value, and every function called through that interface can modify that state. In any point isn't the user presented with implementation details.
In case it's not clear, the above example fails because the implementation of myFunction can't prove that the record selector provides an appropriate type (because it's an existential); at least that's how I understand it.
You can parametrize ProgramState by the type of the component state(s), e.g. have
data ProgramState cs = ProgramState { componentState :: cs }
This would mean you'll also have to expose the ComponentState type from InternalComponent.hs, but not the constructors. This way you give the type checker something to play with, but don't expose any internals to the users of InternalComponent.
First, I'd suggest to read Combining multiple states in StateT, just to see other available options.
Since in the case of nested states we need to update values inside more complex objects, using lens can make life a lot easier (see also this tutorial). A value of type Lens' s a knows how to reach a particular value of type a inside s and how to modify it (that is, creating a new value of type s that is the same, except for a modified a). Then we can define a helper function
runInside :: (MonadState s m) => Lens' s a -> State a r -> m r
runInside lens s = lens %%= (runState s)
Given a lens and a stateful computation on a, we can lift such a computation to a stateful computation parametrized by s. The library allows us to generate lenses using Template Haskell, for example:
{-# LANGUAGE RankNTypes, TemplateHaskell #-}
import Control.Lens.TH
data ProgramState cs = ProgramState { _componentState :: cs }
$(makeLenses ''ProgramState)
will generate componentState :: Lens' ProgramState cs (actually the generated function will be slightly more more generic). Combining them together we get
runInside componentState :: MonadState (ProgramState a) m => State a r -> m r
Using Typeable we could go even further and create a map that automatically creates or keeps a state for whatever type it is asked for. I'd not recommend this approach in general, as it sort-of avoids Haskell's strong type system checks, but it might be useful in some cases.
{-# LANGUAGE ExistentialQuantification, ScopedTypeVariables, RankNTypes #-}
import Control.Lens
import Control.Lens.TH
import Control.Monad.State
import Data.Map (Map)
import qualified Data.Map as Map
import Data.Typeable
data Something = forall a . Typeable a => Something a
type TypeMap = Map TypeRep Something
We defined a generic untyped container that can hold whatever is Typeable and a map that maps representation of types to their values.
We'll need some class to provide default/starting values:
class Default a where
getDefault :: a
-- just an example
instance Default Int where
getDefault = 0
Finally, we can create a lens that given an arbitrary Typeable type, it focuses on its value in the map by looking up its type representation:
typeLens :: forall t . (Typeable t, Default t) => Lens' TypeMap t
typeLens = lens get set
where
set map v = Map.insert (typeOf v) (Something v) map
get map = case Map.lookup (typeRep (Proxy :: Proxy t)) map of
Just (Something v) | Just r <- cast v -> r
_ -> getDefault
So you could have TypeMap somewhere in your state and let all stateful computations use it, regardless of what state they need.
However, there is a big warning: If two unrelated computations happen to use the same type for their state, they'll share the value with very likely disastrous results! So using explicit records for states of different parts of your computations is going to be much safer.

Making Read-Only functions for a State in Haskell

I often end up in a situation where it's very convenient to be using the State monad, due to having a lot of related functions that need to operate on the same piece of data in a semi-imperative way.
Some of the functions need to read the data in the State monad, but will never need to change it. Using the State monad as usual in these functions works just fine, but I can't help but feel that I've given up Haskell's inherent safety and replicated a language where any function can mutate anything.
Is there some type-level thing that I can do to ensure that these functions can only read from the State, and never write to it?
Current situation:
iWriteData :: Int -> State MyState ()
iWriteData n = do
state <- get
put (doSomething n state)
-- Ideally this type would show that the state can't change.
iReadData :: State MyState Int
iReadData = do
state <- get
return (getPieceOf state)
bigFunction :: State MyState ()
bigFunction = do
iWriteData 5
iWriteData 10
num <- iReadData -- How do we know that the state wasn't modified?
iWRiteData num
Ideally iReadData would probably have the type Reader MyState Int, but then it doesn't play nicely with the State. Having iReadData be a regular function seems to be the best bet, but then I have to go through the gymnastics of explicitly extracting and passing it the state every time it's used. What are my options?
It's not hard to inject the Reader monad into State:
read :: Reader s a -> State s a
read a = gets (runReader a)
then you could say
iReadData :: Reader MyState Int
iReadData = do
state <- ask
return (getPieceOf state)
and call it as
x <- read $ iReadData
this would allow you to build up Readers into larger read-only sub-programs and inject them into State only where you need to combine them with mutators.
It's not hard to extend this to a ReaderT and StateT at the top of your monad transformer stack (in fact, the definition above works exactly for this case, just change the type). Extending it to a ReaderT and StateT in the middle of the stack is harder. You basically need a function
lift1 :: (forall a. m0 a -> m1 a) -> t m0 a -> t m1 a
for every monad transformer t in the stack above the ReaderT/StateT, which isn't part of the standard library.
I would recommend wrapping up the State monad in a newtype and defining a MonadReader instance for it:
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE FlexibleContexts #-}
import Control.Applicative
import Control.Monad.State
import Control.Monad.Reader
data MyState = MyState Int deriving Show
newtype App a = App
{ runApp' :: State MyState a
} deriving
( Functor
, Applicative
, Monad
, MonadState MyState
)
runApp :: App a -> MyState -> (a, MyState)
runApp app = runState $ runApp' app
instance MonadReader MyState App where
ask = get
local f m = App $ fmap (fst . runApp m . f) $ get
iWriteData :: MonadState MyState m => Int -> m ()
iWriteData n = do
MyState s <- get
put $ MyState $ s + n
iReadData :: MonadReader MyState m => m Int
iReadData = do
MyState s <- ask
return $ s * 2
bigFunction :: App ()
bigFunction = do
iWriteData 5
iWriteData 10
num <- iReadData
iWriteData num
This is certainly more code that #jcast's solution, but it follows the the tradition of implementing your transformer stack as a newtype wrapper, and by sticking with constraints instead of solidified types you can make strong guarantees about the use of your code while providing maximum flexibility for re-use. Anyone using your code would be able to extend your App with transformers of their own while still using iReadData and iWriteData as intended. You also don't have to wrap every call to a Reader monad with a read function, the MonadReader MyState functions are seamlessly integrated with functions in the App monad.
Excellent answers by jcast and bhelkir, with exactly the first idea I thought of—embedding Reader inside State.
I think it's worthwhile to address this semi-side point of your question:
Using the State monad as usual in these functions works just fine, but I can't help but feel that I've given up Haskell's inherent safety and replicated a language where any function can mutate anything.
That's a potential red flag, indeed. I've always found that State works best for code with "small" states that can be contained within the lifetime of a single, brief application of runState. My go-to example is numbering the elements of a Traversable data structure:
import Control.Monad.State
import Data.Traversable (Traversable, traverse)
tag :: (Traversable t, Enum s) => s -> t a -> t (s, a)
tag i ta = evalState (traverse step ta) init
where step a = do s <- postIncrement
return (s, a)
postIncrement :: Enum s => State s s
postIncrement = do result <- get
put (succ result)
return result
You don't directly say so, but you make it sound you may have a big state value, with many different fields being used in many different ways within a long-lived runState call. And perhaps it does need to be that way for your program at this point. But one technique for coping with this might be to write your smaller State actions so that they only use narrower state types than the "big" one and then embed these into the larger State type with a function like this:
-- | Extract a piece of the current state and run an action that reads
-- and modifies only that piece.
substate :: (s -> s') -> (s' -> s -> s) -> State s' a -> State s a
substate extract replace action =
do s <- get
let (s', a) = runState action (extract s)
put (replace s' s)
return a
Schematic example
example :: State (A, B) Whatever
example = do foo <- substate fst (,b) action1
bar <- substate snd (a,) action2
return $ makeWhatever foo bar
-- Can only touch the `A` component of the state
action1 :: State A Foo
action1 = ...
-- Can only touch the `B` component of the state
action2 :: State B Bar
action2 = ...
Note that the extract and replace functions constitute a lens, and there are libraries for that, which may even already include a function like this.

How to separate components with side effects?

I'm trying to create an agent based system in Haskell. For this I need to logically separate the agent and environment parts, for example to run using different test and real environments.
Both component types, agent and environment will have lots of stateful stuff going on, so I opted to use monad transformer stacks to build each one. I moved the component interface to a type class, which is implemented by the environment. Monads implementing this type class can be used to complete the whole transformer stack by plugging them into the agent transformer.
I created a working proof of concept, which is posted below.
{-# LANGUAGE MultiParamTypeClasses, FunctionalDependencies, FlexibleContexts,
GeneralizedNewtypeDeriving #-}
module MonadComponents where
import Control.Monad
import Control.Monad.Reader
import Control.Monad.Trans
class Monad m => Environment m v | m -> v where
envAction :: v -> m v
newtype AgentT r v m a = AgentT {unAgentT :: ReaderT r m a}
deriving (Monad, MonadTrans, MonadReader r)
runAgentT :: (Environment m v) => AgentT r v m a -> r -> m a
runAgentT = runReaderT . unAgentT
instance Environment IO Int where
envAction x = do
putStrLn $ "action performed in IO environment " ++ (show x)
return $ x * 2
agentAction :: (Environment m Int) => AgentT Int Int m Int
agentAction = do
x <- ask
lift $ envAction (x+10)
ioAction :: Int -> IO Int
ioAction = runAgentT agentAction
Although this kind of works, I see two problems with my code. First, AgentT itself cannot say that it only accepts Monads which are instances of Environment. That is only forced by the type signature of runAgentT. Second, the deeper a transformer stack gets, the complexer its resultant type after full evaluation can become. For example you need to collect and handle every result of StateT, WriterT, MaybeT, EitherT when they are in the stack at a single point at the end. So there is a location in the resulting program where the separation of components does not exist anymore.
I bet there are many different ways to do this. So, of which other ways can you think to separate side-effecting components via a well defined interface in Haskell?

State monad with Predicates

I'm attempting to create something that looks a lot like the State monad, but also carries a list of predicates and accompanying transition functions over the state. The basic steps for computation I'm envisioning are like follows:
Foo (state, [(pred, t)]) >>= f. Apply f to s, yielding s'. Then apply each predicate to s'. For each predicate that matches, apply the associated transition function to the state in sequence. E.g. suppose [(p1, t1), (p2, t2), (p3, t3)], f, and s. If after f s yields s', p1 s' and p3 s' both return True, you would perform t1 s' yielding s'' and then perform t3 s'' yielding s''', the result of the computation.
There's a lot of moving parts here, and I feel as if the correct approach would be to build this on top of the StateT transformer or the State monad, however I can't figure out where to start.
I feel as if this isn't terribly clear. Any clarifications that would make this clearer are much appreciated.
I don't think you can make the monad you're asking for. As I was mentioning in my discussion with jozefg, we have two monad laws that say
f >=> return = f
return >=> f = f
which means that nothing "interesting" can happen at a binding location. In particular, we can't run a state-transition function at each binding, because then f >=> return will run that transition function and f won't, and these laws will be broken.
However, that doesn't stop us from making a monadic action that runs the state transitions on our behalf. So I'll sketch the idea for how to design a monad that tracks such transitions and runs them on demand. You'll surely need to flesh out the API some if you want it to be useful. The basic idea is that instead of just an s as state, we'll store both an s and a transition table. First, some boilerplate.
{-# LANGUAGE FlexibleInstances, GeneralizedNewtypeDeriving, MultiParamTypeClasses #-}
import Control.Arrow
import Control.Applicative
import Control.Monad.State
For now, let's just work with s -> s transitions. You can implement them however you like -- including looking in a list of predicates and transitions and picking out the ones you want to run, if that's your cup of tea. But that's orthogonal to getting the rest of the idea right. We'll define our new type and give it a Monad instance that just dispatches to the underlying type.
newtype TStateT s m a = TStateT { unTStateT :: StateT (s, s -> s) m a }
deriving (Functor, Applicative, Monad)
The MonadState instance is a bit trickier than just using deriving, but still pretty straightforward. Presumably publically we want to pretend that only s is part of the state, so we need to focus our attention a bit. We'll also give the runStateT analog, and pick a sane initial transition function. (We'll give a way to modify this choice later.)
instance Monad m => MonadState s (TStateT s m) where
state f = TStateT (state (\(s, t) -> let (v, s') = f s in (v, (s', t))))
runTStateT :: Functor m => TStateT s m a -> s -> m (a, s)
runTStateT m s = second fst <$> runStateT (unTStateT m) (s, id)
Now comes the interesting bit. The superpower of TStateT is that it has some transitions it can run at any time. So let's provide a way to run them and a way to modify the transition table.
step :: Monad m => TStateT s m ()
step = TStateT (gets snd) >>= modify
modifyTransitions :: Monad m => ((s -> s) -> (s -> s)) -> TStateT s m ()
modifyTransitions = TStateT . modify . second
And that's pretty much everything!

Combining multiple states in StateT

I am writing a program that runs as a daemon.
To create the daemon, the user supplies a set of
implementations for each of the required classes (one of them is a database)
All of these classes have functions have
type signatures of the form StateT s IO a,
but s is different for each class.
Suppose each of the classes follows this pattern:
import Control.Monad (liftM)
import Control.Monad.State (StateT(..), get)
class Hammer h where
driveNail :: StateT h IO ()
data ClawHammer = MkClawHammer Int -- the real implementation is more complex
instance Hammer ClawHammer where
driveNail = return () -- the real implementation is more complex
-- Plus additional classes for wrenches, screwdrivers, etc.
Now I can define a record that represents the implementation chosen by
the user for each "slot".
data MultiTool h = MultiTool {
hammer :: h
-- Plus additional fields for wrenches, screwdrivers, etc.
}
And the daemon does most of its work in the StateT (MultiTool h ...) IO ()
monad.
Now, since the multitool contains a hammer, I can use it in any situation
where a hammer is needed. In other words, the MultiTool type
can implement any of the classes it contains, if I write code like this:
stateMap :: Monad m => (s -> t) -> (t -> s) -> StateT s m a -> StateT t m a
stateMap f g (StateT h) = StateT $ liftM (fmap f) . h . g
withHammer :: StateT h IO () -> StateT (MultiTool h) IO ()
withHammer runProgram = do
t <- get
stateMap (\h -> t {hammer=h}) hammer runProgram
instance Hammer h => Hammer (MultiTool h) where
driveNail = withHammer driveNail
But the implementations of withHammer, withWrench, withScrewdriver, etc.
are basically identical. It would be nice to be able to write something
like this...
--withMember accessor runProgram = do
-- u <- get
-- stateMap (\h -> u {accessor=h}) accessor runProgram
-- instance Hammer h => Hammer (MultiTool h) where
-- driveNail = withMember hammer driveNail
But of course that won't compile.
I suspect my solution is too object-oriented.
Is there a better way?
Monad transformers, maybe?
Thank you in advance for any suggestions.
If you want to go with a large global state like in your case, then what you want to use is lenses, as suggested by Ben. I too recommend Edward Kmett's lens library. However, there is another, perhaps nicer way.
Servers have the property that the program runs continuously and performs the same operation over a state space. The trouble starts when you want to modularize your server, in which case you want more than just some global state. You want modules to have their own state.
Let's think of a module as something that transforms a Request to a Response:
Module :: (Request -> m Response) -> Module m
Now if it has some state, then this state becomes noticable in that the module might give a different answer the next time. There are a number of ways to do this, for example the following:
Module :: s -> ((Request, s) -> m (Response s)) -> Module m
But a much nicer and equivalent way to express this is the following constructor (we will build a type around it soon):
Module :: (Request -> m (Response, Module m)) -> Module m
This module maps a request to a response, but along the way also returns a new version of itself. Let's go further and make requests and responses polymorphic:
Module :: (a -> m (b, Module m a b)) -> Module m a b
Now if the output type of a module matches another module's input type, then you can compose them like regular functions. This composition is associative and has a polymorphic identity. This sounds a lot like a category, and in fact it is! It is a category, an applicative functor and an arrow.
newtype Module m a b =
Module (a -> m (b, Module m a b))
instance (Monad m) => Applicative (Module m a)
instance (Monad m) => Arrow (Module m)
instance (Monad m) => Category (Module m)
instance (Monad m) => Functor (Module m a)
We can now compose two modules that have their own individual local state without even knowing about it! But that's not sufficient. We want more. How about modules that can be switched among? Let's extend our little module system such that modules can actually choose not to give an answer:
newtype Module m a b =
Module (a -> m (Maybe b, Module m a b))
This allows another form of composition that is orthogonal to (.): Now our type is also a family of Alternative functors:
instance (Monad m) => Alternative (Module m a)
Now a module can choose whether to respond to a request, and if not, the next module will be tried. Simple. You have just reinvented the wire category. =)
Of course you don't need to reinvent this. The Netwire library implements this design pattern and comes with a large library of predefined "modules" (called wires). See the Control.Wire module for a tutorial.
Here's a concrete example of how to use lens like everybody else is talking about. In the following code example, Type1 is the local state (i.e. your hammer), and Type2 is the global state (i.e. your multitool). lens provides the zoom function which lets you run a localized state computation that zooms in on any field defined by a lens:
import Control.Lens
import Control.Monad.Trans.Class (lift)
import Control.Monad.Trans.State
data Type1 = Type1 {
_field1 :: Int ,
_field2 :: Double}
field1 :: SimpleLens Type1 Int
field1 = lens _field1 (\x a -> x { _field1 = a})
field2 :: SimpleLens Type1 Double
field2 = lens _field2 (\x a -> x { _field2 = a})
data Type2 = Type2 {
_type1 :: Type1 ,
_field3 :: String}
type1 :: SimpleLens Type2 Type1
type1 = lens _type1 (\x a -> x { _type1 = a})
field3 :: SimpleLens Type2 String
field3 = lens _field3 (\x a -> x { _field3 = a})
localCode :: StateT Type1 IO ()
localCode = do
field1 += 3
field2 .= 5.0
lift $ putStrLn "Done!"
globalCode :: StateT Type2 IO ()
globalCode = do
f1 <- zoom type1 $ do
localCode
use field1
field3 %= (++ show f1)
f3 <- use field3
lift $ putStrLn f3
main = runStateT globalCode (Type2 (Type1 9 4.0) "Hello: ")
zoom is not limited to immediate sub-fields of a type. Since lenses are composable, you can zoom as deep as you want in a single operation just by doing something like:
zoom (field1a . field2c . field3b . field4j) $ do ...
This sounds very much like an application of lenses.
Lenses are a specification of a sub-field of some data. The idea is you have some value toolLens and functions view and set so that view toolLens :: MultiTool h -> h fetches the tool and set toolLens :: MultiTool h -> h -> MultiTool h replaces it with a new value. Then you can easily define your withMember as a function just accepting a lens.
Lens technology has advanced a great deal recently, and they are now incredibly capable. The most powerful library around at the time of writing is Edward Kmett's lens library, which is a bit much to swallow, but pretty simple once you find the features you want. You can also search for more questions about lenses here on SO, e.g. Functional lenses which links to lenses, fclabels, data-accessor - which library for structure access and mutation is better, or the lenses tag.
I created a lensed extensible record library called data-diverse-lens which allows combining multiple ReaderT (or StateT) like this gist:
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE TypeApplications #-}
module Main where
import Control.Lens
import Control.Monad.Reader
import Control.Monad.State
import Data.Diverse.Lens
import Data.Semigroup
foo :: (MonadReader r m, HasItem' Int r, HasItem' String r) => m (Int, String)
foo = do
i <- view (item' #Int) -- explicitly specify type
s <- view item' -- type can also be inferred
pure (i + 10, s <> "bar")
bar :: (MonadState s m, HasItem' Int s, HasItem' String s) => m ()
bar = do
(item' #Int) %= (+10) -- explicitly specify type
item' %= (<> "bar") -- type can also be inferred
pure ()
main :: IO ()
main = do
-- example of running ReaderT with multiple items
(i, s) <- runReaderT foo ((2 :: Int) ./ "foo" ./ nil)
putStrLn $ show i <> s -- prints out "12foobar"
-- example of running StateT with multiple items
is <- execStateT bar ((2 :: Int) ./ "foo" ./ nil)
putStrLn $ show (view (item #Int) is) <> (view (item #String) is) -- prints out "12foobar"
Data.Has is a simpler library that does the same with tuples. Example from the library front page:
{-# LANGUAGE FlexibleContexts #-}
-- in some library code
...
logInAnyReaderHasLogger :: (Has Logger r, MonadReader r m) => LogString -> m ()
logInAnyReaderHasLogger s = asks getter >>= logWithLogger s
queryInAnyReaderHasSQL :: (Has SqlBackEnd r, MonadReader r m) => Query -> m a
queryInAnyReaderHasSQL q = asks getter >>= queryWithSQL q
...
-- now you want to use these effects together
...
logger <- initLogger ...
sql <- initSqlBackEnd ...
(`runReader` (logger, sql)) $ do
...
logInAnyReaderHasLogger ...
...
x <- queryInAnyReaderHasSQL ...
...

Resources