Avoiding case expressions for chained lookups in Snap - haskell

I am toying around with the Snap framework and I often encounter
the case where I do a database lookup based on a parameter I get
from a form field.
Consider e.g. the following two functions
getParam :: (MonadSnap m) => ByteString -> m (Maybe ByteString)
doLookup :: (MonadIO (m b v), MonadSnaplet m, MonadState s (m b b), HasAcid s UrlDB) => ByteString -> m b v (EventResult QueryByURL)
where UrlDB is a mapping between Integers and URLs. The complicated type signature of the second
function is due to the use of acid-state and eventually results in Maybe Integer.
queryByURL :: Text -> Query UrlDB (Maybe Integer)
So far, my handler looks like
indexHandler :: Handler MyApp MyApp ()
indexHandler = do
mUrl <- getParam "url"
case mUrl of
Nothing -> render "index"
Just url -> do
mId <- doLookup $ url
case mId of
Nothing -> render "index"
Just i -> do
fancyStuffWith i
render "index"
Now, the first thing that annoys me is the staircasing of the case expressions.
The second thing is the threefold appearance of render "index".
Basically, whenever one of the two Maybe values is Nothing, I want to return
a default view.
What would be the cleanest way to do this?

This is what the MaybeT monad transformer is for. Your code could be written like this.
indexHandler :: Handler MyApp MyApp ()
indexHandler = do
runMaybeT $ do
url <- MaybeT $ getParam "url"
i <- MaybeT $ doLookup url
fancyStuffWith i
render "index"
The errors package pulls together these things and adds a lot of convenience functions for working with them. In addition to MaybeT, the EitherT monad transformer does something similar but keeps track of error messages so you can track when your computation failed.

To avoid repeating render "index", you have to see that you basically call it at the end of all code pathes. Then you can try to abstract that pattern matching part with a function. The result is not perfect but slightly better.
indexHandler :: Handler MyApp MyApp ()
indexHandler = do
withJust $ getParam "url" $ \url ->
withJust $ doLookup url $ fancyStuffWith
render "index"
where
withJust :: (IO (Maybe a)) -> (a -> IO()) -> IO ()
withJust iomval cmd = do
mval <- iomval
case mval of
Nothing -> return ()
Just val -> cmd val
the withJust function performs an IO action which might fail to bring a value. If it succeeds, the value is passed to another command.

Related

Chaining functions of type IO (Maybe a )

I am writing a small library for interacting with a few external APIs. One set of functions will construct a valid request to the yahoo api and parse the result to a data type. Another set of functions will look up the users current location based on IP and return a data type representing the current location. While the code works, it seems having to explicitly pattern match to sequence multiple functions of type IO (Maybe a).
-- Yahoo API
constructQuery :: T.Text -> T.Text -> T.Text
constructQuery city state = "select astronomy, item.condition from weather.forecast" <>
" where woeid in (select woeid from geo.places(1)" <>
" where text=\"" <> city <> "," <> state <> "\")"
buildRequest :: T.Text -> IO ByteString
buildRequest yql = do
let root = "https://query.yahooapis.com/v1/public/yql"
datatable = "store://datatables.org/alltableswithkeys"
opts = defaults & param "q" .~ [yql]
& param "env" .~ [datatable]
& param "format" .~ ["json"]
r <- getWith opts root
return $ r ^. responseBody
run :: T.Text -> IO (Maybe Weather)
run yql = buildRequest yql >>= (\r -> return $ decode r :: IO (Maybe Weather))
-- IP Lookup
getLocation:: IO (Maybe IpResponse)
getLocation = do
r <- get "http://ipinfo.io/json"
let body = r ^. responseBody
return (decode body :: Maybe IpResponse)
-- Combinator
runMyLocation:: IO (Maybe Weather)
runMyLocation = do
r <- getLocation
case r of
Just ip -> getWeather ip
_ -> return Nothing
where getWeather = (run . (uncurry constructQuery) . (city &&& region))
Is it possible to thread getLocation and run together without resorting to explicit pattern matching to "get out" of the Maybe Monad?
You can happily nest do blocks that correspond to different monads, so it's just fine to have a block of type Maybe Weather in the middle of your IO (Maybe Weather) block.
For example,
runMyLocation :: IO (Maybe Weather)
runMyLocation = do
r <- getLocation
return $ do ip <- r; return (getWeather ip)
where
getWeather = run . (uncurry constructQuery) . (city &&& region)
This simple pattern do a <- r; return f a indicates that you don't need the monad instance for Maybe at all though - a simple fmap is enough
runMyLocation :: IO (Maybe Weather)
runMyLocation = do
r <- getLocation
return (fmap getWeather r)
where
getWeather = run . (uncurry constructQuery) . (city &&& region)
and now you see that the same pattern appears again, so you can write
runMyLocation :: IO (Maybe Weather)
runMyLocation = fmap (fmap getWeather) getLocation
where
getWeather = run . (uncurry constructQuery) . (city &&& region)
where the outer fmap is mapping over your IO action, and the inner fmap is mapping over your Maybe value.
I misinterpreted the type of getWeather (see comment below) such that you will end up with IO (Maybe (IO (Maybe Weather))) rather than IO (Maybe Weather).
What you need is a "join" through a two layer monad stack. This is essentially what a monad transformer provides for you (see #dfeuer's answer) but it is possible to write this combinator manually in the case of Maybe -
import Data.Maybe (maybe)
flatten :: (Monad m) => m (Maybe (m (Maybe a))) -> m (Maybe a)
flatten m = m >>= fromMaybe (return Nothing)
in which case you can write
runMyLocation :: IO (Maybe Weather)
runMyLocation = flatten $ fmap (fmap getWeather) getLocation
where
getWeather = run . (uncurry constructQuery) . (city &&& region)
which should have the correct type. If you are going to chain multiple functions like this, you will need multiple calls to flatten, in which case it maybe be easier to build a monad transformer stack instead (with the caveat's in #dfeuer's answer).
There is probably a canonical name for the function I've called "flatten" in the transformers or mtl libraries, but I can't find it at the moment.
Note that the function fromMaybe from Data.Maybe essentially does the case analysis for you, but abstracts it into a function.
Some consider this an anti-pattern, but you could use MaybeT IO a instead of IO (Maybe a). The problem is that you only deal with one of the ways getLocation can fail—it could also throw an IO exception. From that perspective, you might as well drop the Maybe and just throw your own exception if decoding fails, catching it wherever you like.
change getWeather to have Maybe IpResponse->IO.. and use >>= to implement it and then you can do getLocation >>= getWeather. The >>= in getWeather is the one from Maybe, that will deal with Just and Nothing and the other getLocation>>= getWeather the one from IO.
you can even abstract from Maybe and use any Monad: getWeather :: Monad m -> m IpResponse -> IO .. and will 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"}

Type signature of runErrorT

I have a function, target say, which demands a parameter of type
target :: Action m UserId -> something
where m is any monad.
I acquire the parameter from an existing function, call it "func"
func :: something -> Action m UserId
to which I wish to retrofit an ErrorT transformer
func :: something -> ErrorT String (Action m) UserId
When I use runErrorT on func in order to extract the successful/failed result, I of course get a result of type
Action m (Either String UserId)
I.e. the either representing success or failure is embedded in the surrounding monad. This is great for some purposes e.g. testing for left and right in the context of the Action monad.
What I really need is a version of runErrorT which returns
Either String (Action m UserId)
because then I could just take the Right value and use it. What do I do in these circumstances? Alternatively is there a clever way of rejigging
Action m (Either String UserId) -> Either String (Action m UserId)
but where I don't have access to the necessary constructor
UserId -> Action m UserId
since it so happens that Action is itself a transformer
type Action = ReaderT MongoDBContext
Let's say you have
func :: a -> ErrorT String (Action m) UserId
target :: Action m UserId -> b
Then
run :: a -> Action m (Either String b)
run a = do
result <- runErrorT $ func a
return $ case result of
Left str -> Left str
Right uid -> Right $ target (return uid)
Or more succinctly
run = runErrorT . fmap (target . return) . func
In general, this can't be done without knowledge of the specific m. For example, this is no function of type IO (Either String Int) -> Either String (IO Int) that doesn't use unsafePerformIO or something like that.
You can write something like:
dupNoEx :: IO (Either String Int) -> IO (Either String (IO Int))
dupNoEx act = do
ev <- act
case v of
Left s -> return $ Left s
Right i -> return . Right $ return i
but, I don't know how valuable it might be.

Is there a way to unwrap a type from an IO monad?

I have this very simple function
import qualified Data.ByteString.Lazy as B
getJson :: IO B.ByteString
getJson = B.readFile jsonFile
readJFile :: IO (Maybe Response)
readJFile = parsing >>= (\d ->
case d of
Left err -> return Nothing
Right ps -> return (Just ps))
where parsing = fmap eitherDecode getJson :: IO (Either String Response)
where jsonFile is a path to a file on my harddrive (pardon the lack of do-notation, but I found this more clear to work with)
my question is; is there a way for me to ditch the IO part so I can work with the bytestring alone?
I know that you can pattern match on certain monads like Either and Maybe to get their values out, but can you do something similar with IO?
Or voiced differently: is there a way for me to make readJFile return Maybe Response without the IO?
To expand on my comments, here's how you can do it:
getJson :: IO B.ByteString
getJson = B.readFile jsonFile -- as before
readJFile :: B.ByteString -> Maybe Response -- look, no IO
readJFile b = case eitherDecode b of
Left err -> Nothing
Right ps -> Just ps
In the end, you combine everything in one IO action again:
getAndProcess :: IO (Maybe Response)
getAndProcess = do
b <- getJson
return (readJFile b)
You never need to "drag a monad" through any functions, unless they all need to actually do IO. Just lift the entire chain into the monad with fmap (or liftM / liftM2 / ...).
For instance,
f1 :: B.ByteString -> K
f2 :: K -> I
f3 :: K -> J
f4 :: I -> J -> M
and your entire thing is supposed to be like
m :: M
m = let k = "f1 getJson"
in f4 (f2 k) (f3 k)
The you can simply do
m = fmap (\b -> let k = f1 b
in f4 (f2 k) (f3 k) )
getJson
Incidentally, this might look nicer with do notation:
m = do
b <- getJson
return $ let k = f1 b
in f4 (f2 k) (f3 k)
Concerning you edit and the question
is there a way for me to make readJFile return Maybe Response without the IO?
No, that can't possibly work, because readJFile does need to do IO. There's no way escaping from the IO monad then, that's the whole point of it! (Well, there is unsafePerformIO as Ricardo says, but this is definitely not a valid application for it.)
If it's the clunkiness of unpacking Maybe values in the IO monad, and the signatures with parens in them, you may want to looks at the MaybeT transformer.
readJFile' :: MaybeT IO Response
readJFile' = do
b <- liftIO getJson
case eitherDecode b of
Left err -> mzero
Right ps -> return ps
No, there is no safe way to get a value out of the IO monad. Instead you should do the work inside the IO monad by applying functions with fmap or bind (>>=). Also you should use decode instead of eitherDecode when you want your result to be in Maybe.
getJson :: IO B.ByteString
getJson = B.readFile jsonFile
parseResponse :: B.ByteString -> Maybe Response
parseResponse = decode
readJFile :: IO (Maybe Response)
readJFile = fmap parseResponse getJSON
You could also use do notation if that is clearer to you:
readJFile :: IO (Maybe Response)
readJFile = do
bytestring <- getJson
return $ decode bytestring
Note that you dont even need the parseResponse function since readJFile specifies the type.
In general, yes, there is a way. Accompanied by a lot of "but", but there is. You're asking for what it's called an unsafe IO operation: System.IO.Unsafe. It's used to write wrappers when calling to external libraries usually, it's not something to resort to in regular Haskell code.
Basically, you can call unsafePerformIO :: IO a -> a which does exactly what you want, it strips out the IO part and gives you back wrapped value of type a. But, if you look at the documentation, there are a number of requirements which you should guarantee yourself to the system, which all end up in the same idea: even though you performed the operation via IO, the answer should be the result of a function, as expected from any other haskell function which does not operate in IO: it should always have the same result without side effects, only based on the input values.
Here, given your code, this is obviously NOT the case, since you're reading from a file. You should just continue working within the IO monad, by calling your readJFile from within another function with result type IO something. Then, you'll be able to read the value within the IO wrapper (being in IO yourself), work on it, and then re-wrap the result in another IO when returning.

How do I combine IOError exceptions with locally relevant exceptions?

I am building a Haskell application and trying to figure out how I am going to build the error handling mechanism. In the real application, I'm doing a bunch of work with Mongo. But, for this, I'm going to simplify by working with basic IO operations on a file.
So, for this test application, I want to read in a file and verify that it contains a proper fibonnacci sequence, with each value separated by a space:
1 1 2 3 5 8 13 21
Now, when reading the file, any number of things could actually be wrong, and I am going to call all of those exceptions in the Haskell usage of the word.
data FibException = FileUnreadable IOError
| FormatError String String
| InvalidValue Integer
| Unknown String
instance Error FibException where
noMsg = Unknown "No error message"
strMsg = Unknown
Writing a pure function that verifies the sequence and throws an error in the case that the sequence is invalid is easy (though I could probably do better):
verifySequence :: String -> (Integer, Integer) -> Either FibException ()
verifySequence "" (prev1, prev2) = return ()
verifySequence s (prev1, prev2) =
let readInt = reads :: ReadS Integer
res = readInt s in
case res of
[] -> throwError $ FormatError s
(val, rest):[] -> case (prev1, prev2, val) of
(0, 0, 1) -> verifySequence rest (0, 1)
(p1, p2, val') -> (if p1 + p2 /= val'
then throwError $ InvalidValue val'
else verifySequence rest (p2, val))
_ -> throwError $ InvalidValue val
After that, I want the function that reads the file and verifies the sequence:
type FibIOMonad = ErrorT FibException IO
verifyFibFile :: FilePath -> FibIOMonad ()
verifyFibFile path = do
sequenceStr <- liftIO $ readFile path
case (verifySequence sequenceStr (0, 0)) of
Right res -> return res
Left err -> throwError err
This function does exactly what I want if the file is in the invalid format (it returns Left (FormatError "something")) or if the file has a number out of sequence (Left (InvalidValue 15)). But it throws an error if the file specified does not exist.
How do I catch the IO errors that readFile may produce so that I can transform them into the FileUnreadable error?
As a side question, is this even the best way to do it? I see the advantage that the caller of verifyFibFile does not have to set up two different exception handling mechanisms and can instead catch just one exception type.
You might consider EitherT and the errors package in general. http://hackage.haskell.org/packages/archive/errors/1.3.1/doc/html/Control-Error-Util.html has a utility tryIO for catching IOError in EitherT and you could use fmapLT to map error values to your custom type.
Specifically:
type FibIOMonad = EitherT FibException IO
verifyFibFile :: FilePath -> FibIOMonad ()
verifyFibFile path = do
sequenceStr <- fmapLT FileUnreadable (tryIO $ readFile path)
hoistEither $ verifySequence sequenceStr (0, 0)
#Savanni D'Gerinel: you are on the right track. Let's extract your error-catching code from verifyFibFile to make it more generic, and modify it slightly so that it works directly in ErrorT:
catchError' :: ErrorT e IO a -> (IOError -> ErrorT e IO a) -> ErrorT e IO a
catchError' m f =
ErrorT $ catchError (runErrorT m) (fmap runErrorT f)
verifyFibFile can now be written as:
verifyFibFile' :: FilePath -> FibIOMonad ()
verifyFibFile' path = do
sequenceStr <- catchError' (liftIO $ readFile path) (throwError . FileUnReadable)
ErrorT . return $ verifySequence sequenceStr' (0, 0)
Notice what we have done in catchError'. We have stripped the ErrorT constructor from the ErrorT e IO a action, and also from the return value of the error-handling function, knowing than we can reconstruct them afterwards by wrapping the result of the control operation in ErrorT again.
Turns out that this is a common pattern, and it can be done with monad transformers other than ErrorT. It can get tricky though (how to do this with ReaderT for example?). Luckily, the monad-control packgage already provides this functionality for many common transformers.
The type signatures in monad-control can seem scary at first. Start by looking at just one function: control. It has the type:
control :: MonadBaseControl b m => (RunInBase m b -> b (StM m a)) -> m a
Let's make it more specific by making b be IO:
control :: MonadBaseControl IO m => (RunInBase m IO -> IO (StM m a)) -> m a
m is a monad stack built on top of IO. In your case, it would be ErrorT IO.
RunInBase m IO is a type alias for a magical function, that takes a value of type m a and returns a value of type IO *something*, something being some complex magic that encodes the state of the whole monad stack inside IO and lets you reconstruct the m a value afterwards, once you have "fooled" the control operation that only accepts IO values. control provides you with that function, and also handles the reconstruction for you.
Applying this to your problem, we rewrite verifyFibFile once more as:
import Control.Monad.Trans.Control (control)
import Control.Exception (catch)
verifyFibFile'' :: FilePath -> FibIOMonad ()
verifyFibFile'' path = do
sequenceStr <- control $ \run -> catch (run . liftIO $ readFile path)
(run . throwError . FileUnreadable)
ErrorT . return $ verifySequence sequenceStr' (0, 0)
Keep in mind that this only works when the proper instance of MonadBaseControl b m exists.
Here is a nice introduction to monad-control.
So, here's an answer that I have developed. It centers around getting readFile wrapped into the proper catchError statement, and then lifted.
verifyFibFile :: FilePath -> FibIOMonad ()
verifyFibFile path = do
contents <- liftIO $ catchError (readFile path >>= return . Right) (return . Left . FileUnreadable)
case contents of
Right sequenceStr' -> case (verifySequence sequenceStr' (0, 0)) of
Right res -> return res
Left err -> throwError err
Left err -> throwError err
So, verifyFibFile gets a little more nested in this solution.
readFile path has type IO String, obviously. In this context, the type for catchError will be:
catchError :: IO String -> (IOError -> IO String) -> IO String
So, my strategy was to catch the error and turn it into the left side of an Either, and turn the successful value into the right side, changing my data type to this:
catchError :: IO (Either FibException String) -> (IOError -> IO (Either FibException String)) -> IO (Either FibException String)
I do this by, in the first parameter, simply wrapping the result into Right. I figure that I won't actually execute the return . Right branch of the code unless readFile path was successful. In the other parameter to catch, I start with an IOError, wrap it in Left, and then return it back into the IO context. After that, no matter what the result is, I lift the IO value up into the FibIOMonad context.
I'm bothered by the fact that the code gets even more nested. I have Left values, and all of those Left values get thrown. I'm basically in an Either context, and I had thought that one of the benefits Either's implementation of the Monad class was that Left values would simply be passed along through the binding operations and that no further code in that context would be executed. I would love some elucidation on this, or to see how the nesting can be removed from this function.
Maybe it can't. It does seem that the caller, however, can call verifyFibFile repeatedly and execution basically stops the first time verifyFibFile returns an error. This works:
runTest = do
res <- verifyFibFile "goodfib.txt"
liftIO $ putStrLn "goodfib.txt"
--liftIO $ printResult "goodfib.txt" res
res <- verifyFibFile "invalidValue.txt"
liftIO $ putStrLn "invalidValue.txt"
res <- verifyFibFile "formatError.txt"
liftIO $ putStrLn "formatError.txt"
Main> runErrorT $ runTest
goodfib.txt
Left (InvalidValue 17)
Given the files that I have created, both invalidValue.txt and formatError.txt cause errors, but this function returns Left (InvalidValue ...) for me.
That's okay, but I still feel like I've missed something with my solution. And I have no idea whether I'll be able to translate this into something that makes MongoDB access more robust.

Resources