Replace nested pattern matching with "do" for Monad - haskell

I want to simplify this code
{-# LANGUAGE OverloadedStrings #-}
import Data.Aeson
import Network.HTTP.Types
import Data.Text
getJSON :: String -> IO (Either String Value)
getJSON url = eitherDecode <$> simpleHttp url
--------------------------------------------------------------------
maybeJson <- getJSON "abc.com"
case maybeJson of
Right jsonValue -> case jsonValue of
(Object jsonObject) ->
case (HashMap.lookup "key123" jsonObject) of
(Just (String val)) -> Data.Text.IO.putStrLn val
_ -> error "Couldn't get the key"
_ -> error "Unexpected JSON"
Left errorMsg -> error $ "Error in parsing: " ++ errorMsg
by using do syntax for Monad
maybeJson <- getJSON "abc.com/123"
let toPrint = do
Right jsonValue <- maybeJson
Object jsonObject <- jsonValue
Just (String val) <- HashMap.lookup "key123" jsonObject
return val
case toPrint of
Just a -> Data.Text.IO.putStrLn a
_ -> error "Unexpected JSON"
And it gave me 3 errors:
src/Main.hs:86:19:
Couldn't match expected type `Value'
with actual type `Either t0 (Either String Value)'
In the pattern: Right jsonValue
In a stmt of a 'do' block: Right jsonValue <- maybeJson
src/Main.hs:88:19:
Couldn't match expected type `Value' with actual type `Maybe Value'
In the pattern: Just (String val)
In a stmt of a 'do' block:
Just (String val) <- HashMap.lookup "key123" jsonObject
src/Main.hs:88:40:
Couldn't match type `Maybe' with `Either String'
Expected type: Either String Value
Actual type: Maybe Value
Even when I replace
Just (String val) <- HashMap.lookup "key123" jsonObject
with
String val <- HashMap.lookup "key123" jsonObject
I'm getting another similar error about Either:
Couldn't match type `Maybe' with `Either String'
Expected type: Either String Value
Actual type: Maybe Value
In the return type of a call of `HashMap.lookup'
In a stmt of a 'do' block:
String val <- HashMap.lookup "key123" jsonObject
How do I fix those errors?

You can't easily simplify that into a single block of do-notation, because each case is matching over a different type. The first is unpacking an either, the second a Value and the third a Maybe. Do notation works by threading everything together through a single type, so it's not directly applicable here.
You could convert all the cases to use the same monad and then write it all out in a do-block. For example, you could have helper functions that do the second and third pattern match and produce an appropriate Either. However, this wouldn't be very different to what you have now!
In fact, if I was going for this approach, I'd just be content to extract the two inner matches into their own where variables and leave it at that. Trying to put the whole thing together into one monad just confuses the issue; it's just not the right abstraction here.
Instead, you can reach for a different sort of abstraction. In particular, consider using the lens library which has prisms for working with nested pattern matches like this. It even supports aeson nateively! Your desired function would look something like this:
decode :: String -> Maybe Value
decode json = json ^? key "key123"
You could also combine this with more specific prisms, like if you're expecting a string value:
decode :: String -> Maybe String
decode json = json ^? key "key123" . _String
This takes care of parsing the json, making sure that it's an object and getting whatever's at the specified key. The only problem is that it doesn't give you a useful error message about why it failed; unfortunately, I'm not good enough with lens to understand how to fix that (if it's possible at all).

So every line in a do expression for a Monad must return a value in that Monadic type. Monad is a typeclass here, not a type by itself. So putting everything in a do Monad is not really a sensible statement.
You can try your code with everything wrapped in a Maybe monad.
Assuming you've fetched your JSON value:
{-# LANGUAGE OverloadedStrings #-}
import Data.Aeson
import Network.HTTP
import qualified Data.Map as M
import Control.Applicative
import qualified Data.HashMap.Strict as HM
--------------------------------------------------------------------
main = do
maybeJson <- return $ toJSON (M.fromList [("key123","value")] :: M.Map String String)
ioVal <- return $ do -- The Maybe monad do expression starts here
maybeJson <- Just maybeJson
jsonObject <- case maybeJson of
Object x -> Just x
_ -> Nothing
val <- HM.lookup "key123" jsonObject
return val
putStrLn $ show ioVal
Once we start working in the Maybe monad, every expression must return a Maybe Something value. The way the Maybe monad works is that anything that is a Just something comes out as a pure something that you can work with, but if you get a Nothing, the rest of the code will be skipped and you'll get a Nothing.
This property of falling through is unique to the Maybe monad. Different monads behave differently.
You should read up more about Monads and the IO monad here: http://www.haskell.org/haskellwiki/Introduction_to_IO
You should read more about monads and what they really help you do:
http://learnyouahaskell.com/a-fistful-of-monads
(You should work through the previous chapters and then get to this chapter. Once you do, you'll have a pretty solid understanding of what is happening).
I also think your HTTP request is screwed up. Here's an example of a POST request that you can use.
import qualified Network.HTTP as H
main = do
postData <- return $ H.urlEncodeVars [("someVariable","someValue")]
request <- return $ H.postRequestWithBody "http://www.google.com/recaptcha/api/verify" "application/x-www-form-urlencoded" postData
putStrLn $ show request
-- Make the request
(Right response) <- H.simpleHTTP request
-- Print status code
putStrLn $ show $ H.rspCode response
-- Print response
putSrLn $ show $ H.rspBody response
UPDATED:
Use the following to help you get a JSON value:
import qualified Data.ByteString.Lazy as LC
import qualified Data.ByteString.Char8 as C
import qualified Data.Aeson as DA
responseBody <- return $ H.rspBody response
responseJSON <- return (DA.decode (LC.fromChunks [C.pack responseBody]) :: Maybe DA.Value)
You'll have to make a request object to make a request. There are quite a few helpers. I meant the post request as the most generic case:
http://hackage.haskell.org/package/HTTP-4000.0.5/docs/Network-HTTP.html

Since you are in the IO monad, all the <- are going to assume that you are dealing with IO operations. When you write
do
Right jsonValue <- maybeJson
Object jsonObject <- jsonValue
you are saying that jsonValue must be an IO action just like maybeJson. But this is not the case! jsonValue is but a regular Either value. The silution here would ge to use a do-block let instead of a <-:
do
Right jsonValue <- maybeJson
let Object jsonObject = jsonValue
However, its important to note that in both versions of your code you are using an irrecoverable error to abort your program if the JSON parsing fails. If you want to be able to collect errors, the basic idea would be to convert your values to Either (and then use the monad instance for Either to avoid having lots of nested case expressions)

Related

Problem decoding json from input args with Aeson

I'm trying to write a Haskell program that expects Json string provided as input. Expected Json is a list of Person objects. I want to handle a case when user did not provide input by defaulting to Json of empty list.
It seems like I'm running into type conversion issue between ByteString and String. I do have OverloadedStrings turned on but it doesn't seem to help here. Here's the simplified code.
{-# LANGUAGE OverloadedStrings #-}
import GHC.Generics
import System.Environment
import Data.Aeson
import Data.Maybe (fromMaybe, listToMaybe)
import Data.Text (Text)
data Person = Person { pName :: Text, pAge :: Int } deriving (Show,
Generic)
instance ToJSON Person
instance FromJSON Person
main :: IO (Maybe [Person])
main = do
args <- getArgs
arg1 <- pure $ (fromMaybe "[]" (listToMaybe args))
-- let arg1 = "[{\"pName\": \"James\", \"pAge\": 30}]"
return $ decode arg1 :: IO (Maybe [Person])
Error I'm getting is:
• Couldn't match type ‘[Char]’
with ‘Data.ByteString.Lazy.Internal.ByteString’
Expected type: Data.ByteString.Lazy.Internal.ByteString
Actual type: String
• In the first argument of ‘decode’, namely ‘arg1’
In the second argument of ‘($)’, namely ‘decode arg1’
In a stmt of a 'do' block:
return $ decode arg1 :: IO (Maybe [Person])
If I uncomment let arg1 to simulate what arg1 should be, then code compiles.
The problem is that getArgs returns a [String], not a [ByteString]. decode really wants a ByteString as input.
OverloadedStrings doesn't help with that; it only affects string literals in your code, not external inputs. That's why the version with the hardcoded argument (let arg1 = "[{\"pName\": \"James\", \"pAge\": 30}]") works: arg1 automatically becomes a ByteString to make decode arg1 work, but getArgs has an incompatible type.
One possible fix would be to encode the command line strings to bytes somehow, but there seems to be an easier alternative:
import System.Posix.Env.ByteString (getArgs)
which gives you a
getArgs :: IO [ByteString]
(I haven't actually tested this code; you may also have to use decodeStrict instead of decode.)

Haskell: how to extract a value from a Right

I am building up a simple script to parse a two-items-per-row CSV file:
//Main.hs
module Main where
import qualified Data.ByteString.Lazy as BL
import qualified Data.Vector as V
import Data.Csv
type Row = (BL.ByteString, BL.ByteString)
main :: IO ()
main = do
csvData <- BL.readFile "csvs/twostringsperrow.csv"
let v = decode NoHeader csvData :: Either String (V.Vector Row)
putStrLn "All done"
The script works. Obviously it doesn't do much at the moment, but it works, which is reassuring.
I want to now interact with this in the GHCi and so I run those couple of lines:
$ stack ghci
...
*Main> csvData <- BL.readFile "csvs/twostringsperrow.csv"
*Main> let v = decode NoHeader csvData :: Either String (V.Vector Row)
*Main> v
Right [("1","2"),("3","4")]
At this point I can see that the parsing has been successful and would like to get the [("1","2"),("3","4")] out of the Right into a variable called df so that I can have a play with it. i.e.:
*Main> let df = <something here> v
*Main> df
[("1","2"),("3","4")]
How do I do that?
You can use pattern matching logic here. For example:
let Right df = v
We thus here unwrap the data out of Right data constructor.
You can for example write a function that handles both the Left and Right case, since it is typically better to implement total functions (functions that can process the entire space of values specified by the type).
A basic approach it to use a case.
do ...
x <- parse ...
case x of
Left e -> putStrLn ("Parse error" ++ show e)
Right y -> putStrLn ("Parse OK!" ++ show y)
Don't forget that we can not, in general, "remove a Right" in a safe way, since a value of type Either ParseError T is not necessarily a Right, but could also be a Left.
Indeed, the parsing library returns such a sum type in order to force us to handle the error, and consider both cases.
There are some dangerous partial functions that indeed "remove Right" but it is better to avoid them.

How can I convert IO ByteString to IO String

I know how to convert a ByteString to a String with unpack but I'm struggling to figure out how to convert an IO ByteString (which is what I get back from the fetchHeader function in HaskellNet) to an IO String. I'm basically trying to do something like this
getAllHeadersForMessageUID :: IMapConnection -> UID -> IO String
getAllHeadersForMessageUID connection uid = do
headers <- fetchHeader connection uid
return (headers >>= BS.unpack)
The error message doesn't make sense to me
Couldn't match expected type ‘[BS.ByteString]’
with actual type ‘BS.ByteString’
In the first argument of ‘(>>=)’, namely ‘headers’
In the first argument of ‘return’, namely ‘(headers >>= BS.unpack)
I don't know why a list of ByteString is expected.
Try using return $ BS.unpack headers instead of return (headers >>= BS.unpack).
Or try return $ map BS.unpack headers if headers is a list of ByteStrings.
Besides the fact that it happens to type check (and I'm assuming BS.unpack headers works), here's a way to think about things:
headers is a pure value
BS.unpack is a pure function
headers >>= ... doesn't make sense because the LHS of >>= needs to be a monadic computation
... >>= BS.unpack doesn't make sense because the RHS of >>= needs to be a function which produces a monadic computation
BS.unpack headers is the string we want to return, but it's a pure value
we therefore use return to promote the pure value to a monadic computation
Update:
The following code shows that if fetchHeader has type IO [BS.ByteString], then your code will type check:
import Data.ByteString.Char8 as BS
fetchHeader :: IO [BS.ByteString] -- this works
-- fetchHeader :: IO BS.ByteString -- this doesn't
fetchHeader = undefined
foo :: IO String
foo = do
headers <- fetchHeader
return $ headers >>= BS.unpack
On the other hand, if you change its type to IO BS.ByteString you get the error you encountered.
Update 2:
Interestingly enough, when headers is a list of ByteStrings, the expression headers >>= BS.unpack does make sense and is equivalent to:
concat $ map BS.unpack headers
User5402's answer assumes the ByteString is pure ASCII (which is OK if you are the only person using your code, but there are several reasons why it's a bad idea if you intend to share it)
If the ByteString is encoded with UTF-8: you can convert it to String like this:
import qualified Codec.Binary.UTF8.String as UTF8
foo b = do
bs <- b
return $ UTF8.decode $ unpack bs
I'm not sure how to deal with other encodings such as windows codepages (other than by setting the encoding of a handle, which isn't applicable here).

catching errors during string parsing

I want to parse String to get Int and I use this:
string2int :: String -> Int
string2int str = read str::Int
Now I want to catch paring exception/error as SIMPLY as possible.
I tried:
import qualified Control.Exception as E
eVal <- try (print (string2int "a")) :: IO (Either E.SomeException ())
case eVal of
Left e -> do { putStrLn "exception"; }
Right n -> do { putStrLn "good"; }
But compiler says couldn't match expected type 'E.SomeException()'
with actual type E.IOException.
What am I doing wrong?
Ok I don't know how to use it for my problem: I want somthing like this:
loadfunction = do
{
x <- string2int getLine
if( failed parsing int ) call somefunction
y <- string2int getLine
if( failed parsing int ) call somefunction
otherfunction x y
}
I dont know how to do it using your answers...
You're using try imported from the old exceptions mechanism, but are trying to use its result type as if it was using the new extensible Control.Exception mechanism. Use E.try instead.
You should ideally import Control.Exception like this:
import Prelude hiding (catch)
import Control.Exception
and remove all imports of Control.OldException. Then you can use its functions directly without worrying about any clashes.
By the way, you don't have to use IO exceptions to handle read errors; you can use reads instead:
reads :: (Read a) => String -> [(a, String)]
Here's how I'd write your code with reads:
case reads "a" of
[(a, "")] -> do
print a
putStrLn "good"
_ -> putStrLn "exception"
The fact that reads returns a list is a little confusing; practically, you can think of it as returning Maybe (a, String) instead. If you want a version using Maybe, you can define it like this:
readMaybe :: (Read a) => String -> Maybe a
readMaybe s =
case reads s of
[(a, "")] -> Just a
_ -> Nothing
which makes your code become:
case readMaybe "a" of
Just a -> do
print a
putStrLn "good"
Nothing -> putStrLn "exception"
(You can also define readMaybe as listToMaybe . map fst . filter (null . snd) . reads like dave4420 did; they'll be equivalent in practice, since none of the standard Read instances ever return lists of more than one element.)
In general, you should try and use pure error-handling methods like this whenever possible, and only use IO exceptions when there's really no other option, or you're dealing with IO-specific code (like file/network handling, etc.). However, if you want to stick with exceptions, using E.try instead should fix your error.
Based on your updated question, however, exceptions might be the right way to go after all; something like ErrorT would also work, but if you're already doing everything in IO to start with, then there's no harm in using exceptions. So I would write your example like this:
loadfunction = do
line1 <- getLine
x <- string2int line1
line2 <- getLine
y <- string2int line2
otherfunction x y
and use E.catch to handle the exceptions it throws; take a look at the documentation for catch to see how to do that.

Grandfather Paradox in Haskell

I'm trying to write a renamer for a compiler that I'm writing in Haskell.
The renamer scans an AST looking for symbol DEFs, which it enters into a symbol table, and symbol USEs, which it resolves by looking in the symbol table.
In this language, uses can come before or after defs, so it would seem that a 2 pass strategy is required; one pass to find all the defs and build the symbol table, and a second to resolve all the uses.
However, since Haskell is lazy (like me), I figure I can tie-the-knot and pass the renamer the final symbol table before it is actually built. This is fine as long as I promise to actually build it. In an imperative programming language, this would be like sending a message back in time. This does work in Haskell, but care must be taken to not introduce a temporal paradox.
Here's a terse example:
module Main where
import Control.Monad.Error
import Control.Monad.RWS
import Data.Maybe ( catMaybes )
import qualified Data.Map as Map
import Data.Map ( Map )
type Symtab = Map String Int
type RenameM = ErrorT String (RWS Symtab String Symtab)
data Cmd = Def String Int
| Use String
renameM :: [Cmd] -> RenameM [(String, Int)]
renameM = liftM catMaybes . mapM rename1M
rename1M :: Cmd -> RenameM (Maybe (String, Int))
rename1M (Def name value) = do
modify $ \symtab -> Map.insert name value symtab
return Nothing
rename1M (Use name) = return . liftM ((,) name) . Map.lookup name =<< ask
--rename1M (Use name) =
-- maybe (return Nothing) (return . Just . (,) name) . Map.lookup name =<< ask
--rename1M (Use name) =
-- maybe (throwError $ "Cannot locate " ++ name) (return . Just . (,) name) . Map.lookup name =<< ask
rename :: [Cmd] -> IO ()
rename cmds = do
let (result, symtab, log) = runRWS (runErrorT $ renameM cmds) symtab Map.empty
print result
main :: IO ()
main = do
rename [ Use "foo"
, Def "bar" 2
, Use "bar"
, Def "foo" 1
]
This is the line where the knot is tied:
let (result, symtab, log) = runRWS (runErrorT $ renameM cmds) symtab Map.empty
The running symbol table is stored in the MonadState of the RWS, and the final symbol table is stored in the MonadReader.
In the above example, I have 3 versions of rename1M for Uses (2 are commented out). In this first form, it works fine.
If you comment out the first rename1M Use, and uncomment the second, the program does not terminate. However, it is, in spirit, no different than the first form. The difference is that it has two returns instead of one, so the Maybe returned from Map.lookup must be evaluated to see which path to take.
The third form is the one that I really want. I want to throw an error if I can't find a symbol. But this version also does not terminate. Here, the temporal paradox is obvious; the decision about whether the the symbol will be in the table can affect whether it will be in the table...
So, my question is, is there an elegant way to do what the third version does (throw an error) without running into the paradox? Send the errors on the MonadWriter without allowing the lookup to change the path? Two passes?
Do you really have to interrupt execution when an error occurs? An alternative approach would be to log errors. After tying the knot, you can check whether the list of errors is empty. I've taken this approach in the past.
-- I've wrapped a writer in a writer transformer. You'll probably want to implement it differently to avoid ambiguity
-- related to writer methods.
type RenameM = WriterT [RenameError] (RWS Symtab String Symtab)
rename1M (Use name) = do
symtab_entry <- asks (Map.lookup name)
-- Write a list of zero or more errors. Evaluation of the list is not forced until all processing is done.
tell $ if isJust symtab_entry then [] else missingSymbol name
return $ Just (name, fromMaybe (error "lookup failed") symtab_entry)
rename cmds = do
let ((result, errors), symtab, log) = runRWS (runWriterT $ renameM cmds) symtab Map.empty
-- After tying the knot, check for errors
if null errors then print result else print errors
This does not produce laziness-related nontermination problems because the contents of the symbol table are not affected by whether or not a lookup succeeded.
I don't have a well thought out answer, but one quick thought. Your single pass over the AST takes all the Def and produces a (Map Symbol _), and I wonder if the same AST pass can take all the Use and produce a (Set Symbol) as well as the lazy lookup.
Afterwards you can quite safely compare the Symbols in the keys of the Map with the Symbols in the Set. If the Set has anything not in the Map then you can report all of those Symbols are errors. If any Def'd Symbols are not in in the Set then you can warn about unused Symbols.

Resources