How to pass HTTP request parameter to quickQuery? - haskell

I'm using Happstack to receive some parameters from an HTTP request then pass these parameters to a function that will retrieve data from the database and return this data in the HTTP response as follow:
myFunc :: IO String
myFunc = do r <- look "personId"
conn <- connectODBC "... my connection string ...";
vals <- quickQuery conn ("SELECT Name FROM Person where Id = ?") [(toSql r)];
return (processData vals)
handlers :: ServerPartT IO Response
handlers = do
x <- liftIO (myFunc);
decodeBody (defaultBodyPolicy "/tmp/" 0 1000 1000)
msum [
dir "getData" $ ok $ toResponse x
, ... other handlers ...
]
mainFunc = simpleHTTP nullConf handlers
But when I build the above code I get the following error:
No instance for (HasRqData IO) arising from a use of `look'
In a stmt of a 'do' block: r <- look "personId"
After reading questions on similar issues (like this one) I think I have to include HasRqData constraint somewhere, but I couldn't learn where and how.

As you may have guessed, this is too an issue with monads. There are a handful of them in happstack (HasRqData, among others), so you may well consider it a complicated case.
Let us begin with the innocent-looking look function.
look :: (Functor m, Monad m, HasRqData m) => String -> m String
Indeed, there is a non-trivial constraint HasRqData. Let us ask ourselves: what monads HaveRqData? (It so happens that IO has not!)
class HasRqData m where
...
Instances
HasRqData RqData
(MonadIO m, MonadPlus m) => HasRqData (ServerPartT m)
...
The other instances are derivative of these first two, so, it looks like we have to consider these two options first.
The RqData has limited effects — you can only do look and its derivatives, extracting information from the request at hand. As we want to also have other effects — querying the database, for one, — this is not enough for us.
The ServerPartT m is the general form of the same old friend of ours, ServerPart ≡ ServerPartT IO. It happens that it also HasRqData. This is not a coincidence, but rather an implication of the design of happstack — looks like the authors meant us to use this single monad everywhere, unless we need particular granularity. So, let's give it a try.
myFunc :: ServerPart String
myFunc = do r <- look "personId"
return undefined
This compiles.
Now, we don't even need to lift myFunc in handlers — our previous predicament solved itself. We will need to lift our access to the database though, by the same jar logic we discussed before.
I believe you can figure the details by yourself. In any case, let me know how it works out!

Related

Answer a request with 200 or 404 based on the content of `Maybe` using Servant

I'm currently trying to implement a simple web server with servant. At the moment, I have a IO (Maybe String) that I want to expose via a GET endpoint (this might be a database lookup that may or may not return a result, hence IO and Maybe). If the Maybe contains a value, the response should contain this value with a 200 OK response status. If the Maybe is Nothing, a 404 Not Found should be returned.
So far I was following the tutorial, which also describes handling errors using throwError. However, I haven't managed to get it to compile. What I have is the following code:
type MaybeAPI = "maybe" :> Get '[ JSON] String
server :: Server MaybeAPI
server = stringHandler
maybeAPI :: Proxy MaybeAPI
maybeAPI = Proxy
app :: Application
app = serve maybeAPI server
stringHandler :: Handler String
stringHandler = liftIO $ fmap (\s -> (fromMaybe (throwError err404) s)) ioMaybeString
ioMaybeString :: IO (Maybe String)
ioMaybeString = return $ Just "foo"
runServer :: IO ()
runServer = run 8081 app
I know this is probably more verbose than it needs to be, but I guess it can be simplified as soon as it is working. The problem is the stringHandler, for which the compilation fails with:
No instance for (MonadError ServerError []) arising from a use of ‘throwError’
So my question is: Is this the way to implement such an endpoint in Servant? If so, how can I fix the implementation? My Haskell knowledge is rather limited and I never used throwError before, so it's entirely possible that I'm missing something here. Any help is appreciated!
As I mentioned in my comment, the problem is that in the offending line:
stringHandler :: Handler String
stringHandler = liftIO $ fmap (\s -> (fromMaybe (throwError err404) s)) ioMaybeString
s is a Maybe String, so to use it as the second argument to fromMaybe, the first argument must be a String - and throwError is never going to produce a string.
Although you talked about your code perhaps being too verbose and you would look at simplifying it later, I think part of the problem here is that in this particular handler you are trying to be too concise. Let's try to write this in a more basic, pseudo-imperative style. Since Handler is a monad, we can write this in a do block which checks the value of s and takes the appropriate action:
stringHandler :: Handler String
stringHandler = do
s <- liftIO ioMaybeString
case s of
Just str -> return str
Nothing -> throwError err404
Note that throwError can produce a value of type Handler a for any type it needs to be, which in this case is String. And that we have to use liftIO on ioMaybeString to lift it into the Handler monad, else this won't typecheck.
I can understand why you might have thought fromMaybe was a good fit here, but fundamentally it isn't - the reason being that it's a "pure" function, that doesn't involve IO at all, whereas when you're talking about throwing server errors then you are absolutely unavoidably doing IO. These things essentially can't mix within a single function. (Which makes the fmap inappropriate too - that can certainly be used to "lift" a pure computation to work on IO actions, but here, as I've said, the computation you needed fundamentally isn't pure.)
And if you want to make the stringHandler function above more concise, while I don't think it's really an improvement, you could still use >>= explicitly instead of the do block, without making the code too unreadable:
stringHandler = liftIO ioMaybeString >>= f
where f (Just str) = return str
f Nothing = throwError err404

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 use "IO String" as an HTTP response in Happstack?

I'm retrieving data from a database using HDBC, then trying to send this data to a web client using Happstack.
myFunc :: Integer -> IO String
myFunc = ... fetch from db here ...
handlers :: ServerPart Response
handlers =
do decodeBody (defaultBodyPolicy "/tmp/" 0 1000 1000)
msum [
dir "getData" $ ok $ toResponse $ myFunc $ toInteger 1
]
mainFunc = simpleHTTP nullConf handlers
When I build the above code I get this error:
No instance for (ToMessage (IO String)) arising from a use of
`toResponse'
What did I try ?
I tried to convert the IO String to String (using liftIO for example).
I tried to find any similar questions here.
I tried to find a similar example in the Happstack Crash Course.
I googled all related keywords in all different combinations.
Thanks in advance.
You have to design your handlers around the fact that fetching from a database is a magical action that may not give you what you expect. (For example, your database may crash.) This is why its result is served as an IO, which is a particular case of a monad.
A monad is a jar with a very narrow neck, so narrow even that, once you put something in there, you cannot unput it. (Unless it happens to also be a comonad, but that's a whole another story and not the case with IO nor with ServerPart.) So, you would never convert an IO String to a String. Not that you can't, but your program would become incorrect.
Your case is kind of tricky as you have two monads at play there: IO and ServerPart. Fortunately, ServerPart builds upon IO, it is " larger " and can, in a sense, absorb IO: we can put some IO into a ServerPart and it will be a ServerPart still, so we may then give it to simpleHTTP. In happstack, this conversion may be done via require function, but there is a more general solution as well, involving monad transformers and lift.
Let's take a look at the solution with require first. Its type (simplified to our case) is:
IO (Maybe a) -> (a -> ServerPart r) -> ServerPart r
— So, it takes an IO jar with some argument and makes it suitable for a function that lives in the ServerPart jar. We just have to adjust types a bit and create one lambda abstraction:
myFunc :: Integer -> IO (Maybe String)
myFunc _ = return . Just $ "A thing of beauty is a joy forever."
handlers :: ServerPart Response
handlers = require (myFunc 1) $ \x ->
do decodeBody (defaultBodyPolicy "/tmp/" 0 1000 1000)
msum [
dir "getData" $ ok $ toResponse x
]
mainFunc = simpleHTTP nullConf handlers
As you see, we have to make 2 modifications:
Adjust myFunc so that it returns Maybe, as necessitated by require. This is a better design because myFunc may now fail in two ways:
As a Maybe, it may return Nothing, which means 404 or the like. This is rather common a situation.
As an IO, it may error out, which means the database crashed. Now is the time to alert the DevOps team.
Adjust handlers so that myFunc is external to them. One may say more specifically: abstract myFunc from handlers. This is why this syntax is called a lambda abstraction.
require is the way to deal with monads in happstack specifically. Generally though, this is just a case of transforming monads into larger ones, which is done via lift. The type of lift (again, simplified), is:
IO String -> ServerPart String
So, we can just lift the myFunc 1 :: IO String value to the right monad and then compose with >>=, as usual:
myFunc :: Integer -> IO String
myFunc _ = return $ "Its loveliness increases,.."
handlers :: ServerPart Response
handlers = lift (myFunc 1) >>= \x ->
do decodeBody (defaultBodyPolicy "/tmp/" 0 1000 1000)
msum [
dir "getData" $ ok $ toResponse x
]
mainFunc = simpleHTTP nullConf handlers
As simple as that. I used the same lambda abstraction trick again, but you may as well use do-notation:
myFunc :: Integer -> IO String
myFunc _ = return $ "...it will never pass into nothingness."
handlers :: ServerPart Response
handlers = do
x <- lift (myFunc 1)
decodeBody (defaultBodyPolicy "/tmp/" 0 1000 1000)
msum [
dir "getData" $ ok $ toResponse x
]
mainFunc = simpleHTTP nullConf handlers
P.S. Returning to the story of large and small jars: you can put IO into ServerPart precisely because ServerPart is also an IO monad — it is an instance of the MonadIO class. That means that anything you can do in IO you can also do in ServerPart, and, besides general lift, there is a specialized liftIO function that you can use everywhere I used lift. You are likely to meet many other monads out there that are instances of MonadIO as it's a handy way of structuring code in large applications.
In your particular case, I would stick with the require way nevertheless because I think it's how the designers of happstack meant it to be done. I'm not particularly knowledgeable about happstack though, so I may be wrong.
That's it. Happy hacking!

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.

Catching an Exception from runDb

This is a follow-up to my previous post. MaybeT and Transactions in runDb
I thought this will be a simple thing to do but I have been trying to figure this out for over a day and still haven't made much progress. So thought I will give up and ask!
I just added a try function (from Control.Exception.Lifted) to my previous code and I couldn't get the code to type check. Variants like catch and handle had similar issues.
eauth <- LiftIO (
try( runDb $ do
ma <- runMaybeT $ do
valid <- ...
case ma of
Just a -> return a
Nothing -> liftIO $ throwIO MyException
) :: IO (Either MyException Auth)
)
case eauth of
Right auth -> return auth
Left _ -> lift $ left err400 { errBody = "Could not create user"}
My runDb looks like this (I also tried a variant where I removed liftIO):
runDb query = do
pool <- asks getPool
liftIO $ runSqlPool query pool
I get this error:
No instance for (Control.Monad.Reader.Class.MonadReader Config IO)
arising from a use of ‘runDb’
In the expression: runDb
In the first argument of ‘try’, namely
‘(runDb
$ do { ma <- runMaybeT ...
I am running inside servant handler and my return type is AppM Auth where
type AppM = ReaderT Config (EitherT ServantErr IO)
I have tried many combinations of lifting but doesn't seem to be helping. I thought I will take this opportunity to figure out things from scratch and I hit a wall as well. If someone could suggest how you arrived at the answer, it will be super instructive for me.
This has been my thought process:
I see runSqlConn :: MonadBaseControl IO m => SqlPersistT m a -> Connection -> m a
So that seems to imply it will be in the IO monad, which means try should work
I think check the definition of MonadBaseControl which has class MonadBase b m => MonadBaseControl b m | m -> b. At this point I am confused. This functional dependency logic seems to be suggest type m dictates what b will be but in the previous one b was specified as IO.
I check MonadBase and that did not give me any clue either.
I check SqlPersistT and got no clues either.
I reduced the problem to something very simple like result <- liftIO (try (evaluate (5 `div` 0)) :: IO (Either SomeException Int)) and that worked. So I was even more confused at this time. Doesn't runDb work in IO so shouldn't the same thing work for my original code?
I thought I can figure this out by backtracking but it seems like my level of Haskell knowledge is just not sufficient to get at the root of the problem. Appreciate if people can provide step by step pointers as to arrive at the right solution.
Thanks!
General type signature for try:
(MonadBaseControl IO m, Exception e) => m a -> m (Either e a)
Specialized type signature for try (as it appears in your code):
IO Auth -> IO (Either MyException Auth)
So, the monadic value that is the argument to try has type:
IO Auth
Everything listed above, you probably already understood. If we look at the type signature for your runDb, we get this:
runDb :: (MonadReader Config m, MonadIO m) => SqlPersistT m a -> m a
I sort of had to guess because you didn't provide a type signature, but that is probably what it is. So now, the problem should be a little clearer. You are trying to use runDb to create a monadic value for something that's supposed to be in IO. But IO doesn't satisfy the MonadReader Config instance that you need.
To make the mistake more clear, let's make runDb more monomorphic. You could give it this type signature instead:
type AppM = ReaderT Config (EitherT ServantErr IO)
runDb :: SqlPersistT AppM a -> AppM a
And now if you tried to compile your code, you would get an even better error. Instead of telling you
No instance for (Control.Monad.Reader.Class.MonadReader Config IO)
It would tell you that IO doesn't match AppM (although it would probably expand the type synonym). Practically, what this means is that you can't get the shared pool of database connections magically out of IO. You need the ReaderT Config that was passing it around everywhere.
The easiest fix I can think of would be to stop using exceptions where they aren't necessary:
mauth <- runDb $ runMaybeT $ do
... -- Same stuff you were doing earlier
case mauth of
Just auth -> return auth
Nothing -> lift $ left err400 { errBody = "Could not create user"}

Resources