Building a monad on top of hedis, a haskell redis lib - haskell

I want to write a simple DSL on top of hedis, a redis lib. The goal is to write functions like:
iWantThis :: ByteString -> MyRedis ()
iWantThis bs = do
load bs -- :: MyRedis () It fetches a BS from Redis and puts it as
-- the state in a state monad
bs <- get -- :: MyRedis (Maybe ByteString) Gets the current state
put $ doSomethingPure bs -- :: MyMonad () Updates the state
commit -- :: MyRedis () Write to redis
The basic idea is to fetch data from redis, put it in a state monad, do some stuff with the state and then put the updated state back into redis.
Obviously, it should be atomic so load and put should happen in the same Redis transaction. Hedis permits that by wrapping calls to Redis in a RedisTx (Queued a). For example, we have get :: ByteString -> RedisTx (Queued a).
Queued is a monad and you then run multiExec on your Queued a to execute everything in the Queued a in the same transaction. So I tried to define my MyRedis as such:
import qualified Database.Redis as R
newtype MyRedis a = MyRedis { runMyRedis :: StateT MyState R.RedisTx a } -- deriving MonadState, MyState...
The run function calls multiExec so I'm sure that as long as I stay in MyRedis everything happens in the same transaction.
run :: MyRedis (R.Queued a) -> MyState -> IO (R.TxResult a)
run m s = R.runRedis (undefined :: R.Connection) (R.multiExec r)
where r = evalStateT (runMyRedis m) s
Furthermore, I can define commit as:
commit :: ByteString -> MyRedis (R.Queued R.Status)
commit bs = do
MyState new <- get
(MyRedis . lift) (R.set bs new)
And a computation would look like:
computation :: MyRedis (R.Queued R.Status)
computation = do
load gid
MyState bs <- get
put $ MyState (reverse bs)
commit gid
where gid = "123"
But I can't figure out how to write "load"
load :: ByteString -> MyRedis ()
load gid = undefined
Actually, I think that it is not possible to write load, because get is of type ByteString -> RedisTx (Queued (Maybe ByteString)) and I have no way to peek into the Queued monad without executing it.
Questions:
Is it correct that because of the type of Hedis's get, it doesn't make sense to define a load function with the semantics above?
Is it possible to change the MyRedis type definition to make it work?
Hedis doesn't define a RedisT monad transformer. If such a transformer existed, would it be of any help?
Hedis defines (but does not export to lib users) a MonadRedis typeclass; would making my monad an instance of that typeclass help?
Is it the right approach? I want to:
Abstract over Redis (I may switch someday to another DB)
Restrict the Redis functions available to my users (basically only lifting to MyRedis get and set)
Guarantee that when I run my monad everything happens in the same (redis) transaction
Put my redis abstraction at the same level as other functions in my monad
You can play with the code at http://pastebin.com/MRqMCr9Q. Sorry for the pastebin, lpaste.net is down at the moment.

What you want is not possible. In particular, you can't provide a monadic interface while a running a computation in one Redis transaction. Nothing to do with the library you're using - it's just not something Redis can do.
Redis transactions are rather different from the ACID transactions you may be used to from the world of relational databases. Redis transactions have batching semantics, which means that later commands cannot in any way depend on the result of earlier commands.
Look: here's something similar to your example, run at the Redis command line.
> set "foo" "bar"
OK
> multi
OK
> get "foo"
QUEUED -- I can't now set "baz" to the result of this command because there is no result!
> exec
1) "bar" -- I only get the result after running the whole tran
Anyway, that's the purpose of that library's slightly odd Queued type: the idea is to prevent you from accessing any of the results of a batched command until the end of the batch. (It seems that the author wanted to abstract over batched and non-batched commands but there are simpler ways to do that. See below for how I'd simplify the transactional interface.)
So there's no "choosing what to do next" when Redis transactions are involved, but the whole point of (>>=) :: m a -> (a -> m b) -> m b is that later effects can depend on earlier results. You have to choose between monads and transactions.
If you decide you want transactions, there's an alternative to Monad called Applicative which handlily supports purely-static effects. This is exactly what we need. Here's some (entirely untested) code illustrating how I'd cook an Applicative version of your idea.
newtype RedisBatch a = RedisBatch (R.RedisTx (R.Queued a))
-- being a transactional batch of commands to send to redis
instance Functor RedisBatch where
fmap = liftA
instance Applicative RedisBatch where
pure x = RedisBatch (pure (pure x))
(RedisBatch rf) <*> (RedisBatch rx) = RedisBatch $ (<*>) <$> rf <*> rx
-- no monad instance
get :: ByteString -> RedisBatch (Maybe ByteString)
get key = RedisBatch $ get key
set :: ByteString -> ByteString -> RedisBatch (R.Status)
set key val = RedisBatch $ set key val
runBatch :: R.Connection -> RedisBatch a -> IO (R.TxResult a)
runBatch conn (RedisBatch x) = R.runRedis conn (R.multiExec x)
If I wanted to abstract over transactional-or-not behaviour, as the library author has attempted to do, I'd write a second type RedisCmd exposing a monadic interface, and a class containing my primitive operations, with instances for my two RedisBatch and RedisCmd types.
class Redis f where
get :: ByteString -> f (Maybe ByteString)
set :: ByteString -> ByteString -> f (R.Status)
Now, computations with a type of (Applicative f, Redis f) => ... could work for either behaviour (transactional or not), but those which require a monad (Monad m, Redis m) => ... would only be able to run in non-transactional mode.
When all's said and done, I'm not convinced it's worth it. People seem to like building abstractions over libraries like this, invariably providing less functionality than the library did and writing more code for bugs to lurk in. Whenever someone says "I may want to switch databases" I sigh: the only sufficiently abstract abstraction for that purpose is one which provides no functionality. Worry about switching databases when the time comes that you need to (that is, never).
On the other hand, if your goal is not to abstract the database but just to clean up the interface, the best thing may be to fork the library.

Related

Monad and MonadIO for custom type

I have a Logger type of kind * -> * which can take any type and log the value in a file. I am trying to implement this in a monadic way so that I log and keep working the same. My code looks like
import Control.Applicative
import Control.Monad
import System.IO
import Control.Monad.IO.Class
instance Functor Logger where
fmap = liftM
instance Applicative Logger where
pure = return
(<*>) = ap
newtype Logger a = Logger a deriving (Show)
instance Monad (Logger) where
return = Logger
Logger logStr >>= f = f logStr
instance MonadIO (Logger) where
liftIO a = do
b <- liftIO a
return b
logContent :: (Show a) => a -> Logger a
logContent a = do
b <- liftIO $ logContent2 a
return b
logContent2 :: (Show a) => a -> IO a
logContent2 a = do
fHandle <- openFile "test.log" AppendMode
hPrint fHandle a
hClose fHandle
return (a)
The liftIO function goes on endless loop as it calls itself. I am not able to do b <- a either. Can someone help on getting MonadIO implementation right ?
As noted in the comments, I think you've misunderstood what MonadIO and liftIO do.
These typeclasses and functions come from mtl library. Rather unfortunately, mtl stands for "monad transformer library", but mtl is not a monad transformer library. Rather, mtl is a set of typeclasses that allow you to take a monad that --- and this is important --- already has a particular type of functionality and provide that monad with a consistent interface around that functionality. This ends up being really useful for working with actual monad transformers. That's because mtl allows you to use tell and ask and put to access the Writer, Reader, and State functionality of your monad transformer stack in a consistent way.
Separately from this transformer business, if you already have a custom monad, say that supports arbitrary IO and has State functionality, then you can define a MonadState instance to make the standard state operations (state, get, gets, put, modify) available for your custom monad, and you can define a MonadIO instance to allow an arbitrary IO action to be executed in your custom monad using liftIO. However, none of these typeclasses are capable of adding functionality to a monad that it doesn't already have. In particular, you can't transform an arbitrary monadic action m a into an IO a using a MonadIO instance.
Note that the transformers package contains types that are capable of adding functionality to a monad that it doesn't already have (e.g., adding reader or writer functionality), but there is no transformer to add IO to an arbitrary monad. Such a transformer would be impossible (without unsafe or nonterminating operations).
Also note that the signature for liftIO :: MonadIO m => IO a -> m a puts a MonadIO constraint on m, and this isn't just a trivial constraint. It actually indicates that liftIO only works for monads m that already have IO functionality, so either m is the IO monad, or it's a monad stack with IO at its base. Your Logger example doesn't have IO functionality and so can't have a (sensible) MonadIO instance.
Getting back to your specific problem, it's actually a little bit hard to steer you right here without knowing exactly what you're trying to do. If you just want to add file-based logging to an existing IO computation, then defining a new transformer stack will probably do the trick:
type LogIO = ReaderT Handle IO
logger :: (Show a) => a -> LogIO ()
logger a = do
h <- ask
liftIO $ hPrint h a
runLogIO :: LogIO a -> FilePath -> IO a
runLogIO act fp = withFile fp AppendMode $ \h -> runReaderT act h
and you can write things like:
main :: IO ()
main = runLogIO start "test.log"
start :: LogIO ()
start = do
logger "Starting program"
liftIO . putStrLn $ "Please enter your name:"
n <- liftIO $ getLine
logger n
liftIO . putStrLn $ "Hello, " ++ n
logger "Ending program"
The need to add liftIO calls when using IO actions within the LogIO monad is ugly but largely unavoidable.
This solution would also work for adding file-based logging to pure computations, with the understanding that you have to convert them to IO computations anyway if you want to safely log to a file.
The more general solution is to define your own monad transformer (not merely your own monad), like LoggerT m, together with an associated MonadLogger type class that will add file-based logging to to any IO-capable monad stack. The idea would be that you could then create arbitrary custom monad stacks:
type MyMonad = StateT Int (LoggerT IO)
and then write code that mixes monadic computations from different layers (like mixing state computations and file-based logging):
newSym :: String -> MyMonad String
newSym pfx = do
n <- get
logger (pfx, n)
put (n+1)
return $ pfx ++ show n
Is this what you what you're trying to do? If not, maybe you could describe, either here or in a new question, how you're trying to add logging to some example code.

How to limit code changes when introducing state?

I am a senior C/C++/Java/Assembler programmer and I have been always fascinated by the pure functional programming paradigm. From time to time, I try to implement something useful with it, e.g., a small tool, but often I quickly reach a point where I realize that I (and my tool, too) would be much faster in a non-pure language. It's probably because I have much more experience with imperative programming languages with thousands of idoms, patterns and typical solution approaches in my head.
Here is one of those situations. I have encountered it several times and I hope you guys can help me.
Let's assume I write a tool to simulate communication networks. One important task is the generation of network packets. The generation is quite complex, consisting of dozens of functions and configuration parameters, but at the end there is one master function and because I find it useful I always write down the signature:
generatePackets :: Configuration -> [Packet]
However, after a while I notice that it would be great if the packet generation would have some kind of random behavior deep down in one of the many sub-functions of the generation process. Since I need a random number generator for that (and I also need it at some other places in the code), this means to manually change dozens of signatures to something like
f :: Configuration -> RNGState [Packet]
with
type RNGState = State StdGen
I understand the "mathematical" necessity (no states) behind this. My question is on a higher (?) level: How would an experienced Haskell programmer have approached this situation? What kind of design pattern or work flow would have avoided the extra work later?
I have never worked with an experienced Haskell programmer. Maybe you will tell me that you never write signatures because you have to change them too often afterwards, or that you give all your functions a state monad, "just in case" :)
One approach that I've been fairly successful with is using a monad transformer stack. This lets you both add new effects when needed and also track the effects required by particular functions.
Here's a really simple example.
import Control.Monad.State
import Control.Monad.Reader
data Config = Config { v1 :: Int, v2 :: Int }
-- the type of the entire program describes all the effects that it can do
type Program = StateT Int (ReaderT Config IO) ()
runProgram program config startState =
runReaderT (runStateT program startState) config
-- doesn't use configuration values. doesn't do IO
step1 :: MonadState Int m => m ()
step1 = get >>= \x -> put (x+1)
-- can use configuration and change state, but can't do IO
step2 :: (MonadReader Config m, MonadState Int m) => m ()
step2 = do
x <- asks v1
y <- get
put (x+y)
-- can use configuration and do IO, but won't touch our internal state
step3 :: (MonadReader Config m, MonadIO m) => m ()
step3 = do
x <- asks v2
liftIO $ putStrLn ("the value of v2 is " ++ show x)
program :: Program
program = step1 >> step2 >> step3
main :: IO ()
main = do
let config = Config { v1 = 42, v2 = 123 }
startState = 17
result <- runProgram program config startState
return ()
Now if we want to add another effect:
step4 :: MonadWriter String m => m()
step4 = tell "done!"
program :: Program
program = step1 >> step2 >> step3 >> step4
Just adjust Program and runProgram
type Program = StateT Int (ReaderT Config (WriterT String IO)) ()
runProgram program config startState =
runWriterT $ runReaderT (runStateT program startState) config
To summarize, this approach lets us decompose a program in a way that tracks effects but also allows adding new effects as needed without a huge amount of refactoring.
edit:
It's come to my attention that I didn't answer the question about what to do for code that's already written. In many cases, it's not too difficult to change pure code into this style:
computation :: Double -> Double -> Double
computation x y = x + y
becomes
computation :: Monad m => Double -> Double -> m Double
computation x y = return (x + y)
This function will now work for any monad, but doesn't have access to any extra effects. Specifically, if we add another monad transformer to Program, then computation will still work.

Is it possible to use IO inside State monad, without using StateT and ST

In the code below I manage a game, which owns a list of links.
At each step of the game, I change the game state updating the list of links modified.
As I am learning the State monad, I was trying to apply the State monad technique to this use case.
Nonetheless, at each turn, I need to get a piece of info from IO, using getLine
this gives such a code
{-# LANGUAGE NamedFieldPuns #-}
{-# LANGUAGE RecordWildCards #-}
import Control.Monad
import Control.Monad.State.Strict
import qualified Data.List as List
import qualified Control.Monad.IO.Class as IOClass
type Node = Int
type Link = (Node,Node)
type Links = [Link]
type Gateway = Node
type Gateways = [Gateway]
data Game = Game { nbNodes :: Int, links :: Links, gateways :: Gateways }
computeNextTurn :: State Game Link
computeNextTurn = do
g <- get
inputLine <- IOClass.liftIO getLine -- this line causes problem
let node = read inputLine :: Int
let game#(Game _ ls gs) = g
let linkToSever = computeLinkToSever game node
let ls' = List.delete linkToSever ls
let game' = game{links = ls'}
put game'
return linkToSever
computeAllTurns :: State Game Links
computeAllTurns = do
linkToSever <- computeNextTurn
nextGames <- computeAllTurns
return (linkToSever : nextGames)
computeLinkToSever :: Game -> Node -> Link
computeLinkToSever _ _ = (0,1) -- just a dummy value
-- this function doesnt compute really anything for the moment
-- but it will depend on the value of node i got from IO
However I get an error at compilation:
No instance for (MonadIO Data.Functor.Identity.Identity)
arising from a use of liftIO
and I get the same style of error, if I try to use liftM and lift.
I have read some questions that are suggesting StateT and ST, which I don't grasp yet.
I am wondering if my current techique with a simple State is doomed to fail, and that indeed I can not use State, but StateT / ST ?
Or is there a possible operation to simply get the value from getLine, inside the State monad ?
As #bheklilr said in his comment, you can't use IO from State. The reason for that, basically, is that State (which is just shorthand for StateT over Identity) is no magic, so it's not going to be able to use anything more than
What you can already do in its base monad, Identity
The new operations provided by State itself
However, that first point also hints at the solution: if you change the base monad from Identity to some other monad m, then you get the capability to use the effects provided by m. In your case, by setting m to IO, you're good to go.
Note that if you have parts of your computation that don't need to do IO, but require access to your state, you can still express this fact by making their type something like
foo :: (Monad m) => Bar -> StateT Game m Baz
You can then compose foo with computations in StateT Game IO, but its type also makes it apparent that it can't possibly do any IO (or anything else base monad-specific).
You also mentioned ST in your question as possible solution. ST is not a monad transformer and thus doesn't allow you to import effects from some base monad.

STM with fclabels

I built a small game engine to manage a board of squares (currently used for playing a Conway's game of life). All the data is accessed throught lenses from fclabels and State. The engine couples user input and graphic rendering (usual game loop).
The computations between frames can sometimes be slow and long to execute. So I would like to use concurrency to manage the squares, using STM's TVar.
My data is currently represented like this:
data World = World {
… -- window configuration, not important
, _squares :: TVar [Square]
}
mkLabels [''World] -- creates labels, similar to mkLenses
My functions run in the Game Monad, which is defined as follow:
type Game a = StateT World IO a
Using the monadic versions of labels. I use Getters & Setters inside my monad.
I would like to know if there is a way to somehow write new labels that behave like these:
gets :: MonadState f m => Lens (->) f o -> m o
…
puts :: MonadState f m => Lens (->) f o -> o -> m ()
But that takes care of STM (gets would involve readTVar, puts would involve writeTvar, etc.).
If I understand you correctly, you want to define a lens tlens s.t.:
gets tlens
is the same as:
do tvar <- gets squares
sqs <- liftIO $ atomically $ readTVar tvar
return sqs
and where puts tlens sqs is the same as:
do tvar <- gets squares
liftIO $ atomically $ writeTVar tvar sqs
I think this can be answered by looking at the type of gets:
gets :: MonadState f m => Lens (->) f o -> m o
The lens parameter is pure and not monadic. To get at the contents of the TVar you'll need to run code in the IO-monad.
Moreover, the definition of gets in Data.Label.Monadic is (link) is:
gets lens = State.gets (Total.get lens)
where State is Control.Monad.State and Total is Data.Label.Total.
But State.gets takes a pure function, so again you're not going to be able to create a lens which will work with gets.

Haskell: carry out an IO action wrapped in a Data.Dynamic

Suppose I have a Data.Dynamic.Dynamic object which wraps an IO action (that is, something of type IO a for some perhaps-unknown a). I feel like I should be able carry out this IO action and get its result, wrapped in a Dynamic (which will have type a). Is there a standard library function which does this? (Something like dynApply, but for IO action performance instead of function application.)
The implementation of the function would perhaps look something like
dynPerform :: Dynamic -> Maybe IO Dynamic
dynPerform (Dynamic typ act)
= if (typeRepTyCon typ) /= ioTyCon then Nothing else Just $
do result <- (unsafeCoerce act :: IO Any)
return Just . Dynamic (head $ typeRepArgs typ) $ result
exampleIOAction = putChar
typeOfIOAction = typeOf exampleIOAction
ioTyCon = typeRepTyCon typeOfIOAction
but obviously this is uses several unsafe operations, so I'd rather pull it in from a library. (In fact, what I've written wouldn't work outside Data.Dynamic because of the opacity of the type Data.Dynamic.Dynamic.)
I don't believe you can safely do what you are trying to do. Let me suggest an alternative approach.
Perhaps phantom types can help you here. Suppose you are providing some sort of cron job service, where the user has you perform an action every x microseconds, and the user can query at any time to see the result of the most recent run of that action.
Suppose you yourself have access to the following primitives:
freshKey :: IO Key
save :: Key -> Dynamic -> IO ()
load :: Key -> IO (Maybe Dynamic)
You should schedule the jobs and make a plan to store the results while you still "know" in the type system what type the action is.
-- do not export the internals of PhantomKey
data PhantomKey a = PhantomKey {
getKey :: Key
getThread :: Async ()
}
-- This is how your user acquires phantom keys;
-- their phantom type is tied to the type of the input action
schedule :: Typeable a => Int -> IO a -> IO (PhantomKey a)
schedule microseconds m = do
k <- freshKey
let go = do
threadDelay microseconds
a <- m
save k (toDyn a)
go
thread <- async go
return $ PhantomKey k thread
unschedule :: PhantomKey a -> IO ()
unschedule pk = cancel (getThread pk)
-- This is how your user uses phantom keys;
-- notice the function result type is tied to the phantom key type
peekLatest :: PhantomKey a -> IO (Maybe a)
peekLatest pk = load (getKey pk) >>= \md -> case md of
Nothing -> return Nothing -- Nothing stored at this key (yet?)
Just dyn -> case fromDynamic dyn of
Nothing -> return Nothing -- mismatched data type stored at this key
-- hitting this branch is probably a bug
Just a -> return (Just a)
Now if I'm a user of your API, I can use it with my own data types that you know nothing about, as long as they're Typeable:
refreshFoo :: IO Foo
main = do
fooKey <- schedule 1000000 refreshFoo
-- fooKey :: PhantomKey Foo
mfoo <- peekLatest fooKey
-- mfoo :: Maybe Foo
So what have we accomplished?
Your library is taking in a user IO action, and performing it at arbitrary points in time
Your library is saving your user's data via Dynamic blobs
Your library is loading your user's data via Dynamic blobs
All this without your library knowing anything about your user's data types.
It seems to me that if you are putting something which you know is an IO action into a Dynamic blob, you have lost information in the type system about that thing in a context when you should have instead made use of said type information. TypeRep can get you type information at the value level, but (as far as I know) cannot bubble that information back up into the type level.

Resources