How to use Control.Monad.State with Parsec? - haskell

I'm surprised that I could not find any info on this. I must be the only person having any trouble with it.
So, let's say I have a dash counter. I want it to count the number of dashes in the string, and return the string. Pretend I gave an example that won't work using parsec's state handling. So this should work:
dashCounter = do
str <- many1 dash
count <- get
return (count,str)
dash = do
char '-'
modify (+1)
And indeed, this compiles. Okay, so I try to use it:
:t parse dashCounter "" "----"
parse dashCounter "" "----"
:: (Control.Monad.State.Class.MonadState
t Data.Functor.Identity.Identity,
Num t) =>
Either ParseError (t, [Char])
Okay, that makes sense. It should return the state and the string. Cool.
>parse dashCounter "" "----"
<interactive>:1:7:
No instance for (Control.Monad.State.Class.MonadState
t0 Data.Functor.Identity.Identity)
arising from a use of `dashCounter'
Possible fix:
add an instance declaration for
(Control.Monad.State.Class.MonadState
t0 Data.Functor.Identity.Identity)
In the first argument of `parse', namely `dashCounter'
In the expression: parse dashCounter "" "----"
In an equation for `it': it = parse dashCounter "" "----"
Oops. But then how could it have ever hoped to work in the first place? There's no way to input the initial state.
There is also a function:
>runPT dashCounter (0::Int) "" "----"
But it gives a similar error.
<interactive>:1:7:
No instance for (Control.Monad.State.Class.MonadState Int m0)
arising from a use of `dashCounter'
Possible fix:
add an instance declaration for
(Control.Monad.State.Class.MonadState Int m0)
In the first argument of `runPT', namely `dashCounter'
In the expression: runPT dashCounter (0 :: Int) "" "----"
In an equation for `it':
it = runPT dashCounter (0 :: Int) "" "----"
I feel like I should have to runState on it, or there should be a function that already does it internally, but I can't seem to figure out where to go from here.
Edit: I should have specified more clearly, I did not want to use parsec's state handling. The reason is I have a feeling I don't want its backtracking to affect what it collects with the problem I'm preparing to solve it with.
However, Mr. McCann has figured out how this should fit together and the final code would look like this:
dashCounter = do
str <- many1 dash
count <- get
return (count,str)
dash = do
c <- char '-'
modify (+1)
return c
test = runState (runPT dashCounter () "" "----------") 0
Thanks a lot.

You've actually got multiple problems going on here, all of which are relatively non-obvious the first time around.
Starting with the simplest: dash is returning (), which doesn't seem to be what you want given that you're collecting the results. You probably wanted something like dash = char '-' <* modify (+1). (Note that I'm using an operator from Control.Applicative here, because it looks tidier)
Next, clearing up a point of confusion: When you get the reasonable-looking type signature in GHCi, note the context of (Control.Monad.State.Class.MonadState t Data.Functor.Identity.Identity, Num t). That's not saying what things are, it's telling you want they need to be. Nothing guarantees that the instances it's asking for exist and, in fact, they don't. Identity is not a state monad!
On the other hand, you're absolutely correct in thinking that parse doesn't make sense; you can't use it here. Consider its type: Stream s Identity t => Parsec s () a -> SourceName -> s -> Either ParseError a. As is customary with monad transformers, Parsec is an synonym for ParsecT applied to the identity monad. And while ParsecT does provide user state, you apparently don't want to use it, and ParsecT does not give an instance of MonadState anyhow. Here's the only relevant instance: MonadState s m => MonadState s (ParsecT s' u m). In other words, to treat a parser as a state monad you have to apply ParsecT to some other state monad.
This sort of brings us to the next problem: Ambiguity. You're using a lot of type class methods and no type signatures, so you're likely to run into situations where GHC can't know what type you actually want, so you have to tell it.
Now, as a quick solution, let's first define a type synonym to give a name to the monad transformer stack we want:
type StateParse a = ParsecT String () (StateT Int Identity) a
Give dashCounter the relevant type signature:
dashCounter :: StateParse (Int, String)
dashCounter = do str <- many1 dash
count <- get
return (count,str)
And add a special-purpose "run" function:
runStateParse p sn inp count = runIdentity $ runStateT (runPT p () sn inp) count
Now, in GHCi:
Main> runStateParse dashCounter "" "---" 0
(Right (3,"---"),3)
Also, note that it's pretty common to use a newtype around a transformer stack instead of just a type synonym. This can help with the ambiguity issues in some cases, and obviously avoids ending up with gigantic type signatures.

If you want to use the user state component Parsec offers as a built-in feature, then you can use the getState and modifyState monadic functions.
I tried to stay true to your example program, though using the return of dash doesn't seem useful.
import Text.Parsec
dashCounter :: Parsec String Int (Int, [()])
dashCounter = do
str <- many1 dash
count <- getState
return (count,str)
dash :: Parsec String Int ()
dash = do
char '-'
modifyState (+1)
test = runP dashCounter 0 "" "---"
Note that runP is indeed addressing your concern about runState.

Whilst these answers sort out this specific problem, they ignore the more serious underlying issue with an approach like this. I would like to describe it here for anyone else looking at this answer.
There is a difference between the user state and using the StateT transformer. The internal user state is reset on backtracking but StateT is not. Consider the following code. We want to add one to our counter if there is a dash and two if there is a plus. They produce different results.
As can be seen both using the internal state and attaching a StateT transformer provide the correct result. The latter comes at the expense of having to explicitly lift operations and be much more careful with types.
import Text.Parsec hiding (State)
import Control.Monad.State
import Control.Monad.Identity
f :: ParsecT String Int Identity Int
f = do
try dash <|> plus
getState
dash = do
modifyState (+1)
char '-'
plus = do
modifyState (+2)
char '+'
f' :: ParsecT String () (State Int) ()
f' = void (try dash' <|> plus')
dash' = do
modify (+1)
char '-'
plus' = do
modify (+2)
char '+'
f'' :: StateT Int (Parsec String ()) ()
f'' = void (dash'' <|> plus'')
dash'' :: StateT Int (Parsec String ()) Char
dash'' = do
modify (+1)
lift $ char '-'
plus'' :: StateT Int (Parsec String ()) Char
plus'' = do
modify (+2)
lift $ char '+'
This is the result of running f, f' and f''.
*Main> runParser f 0 "" "+"
Right 2
*Main> flip runState 0 $ runPT f' () "" "+"
(Right (),3)
*Main> runParser (runStateT f'' 0) () "" "+"
Right ((),2)

Related

Couldn't match type `Char' with `[Char]' in Haskell? [closed]

Closed. This question needs debugging details. It is not currently accepting answers.
Edit the question to include desired behavior, a specific problem or error, and the shortest code necessary to reproduce the problem. This will help others answer the question.
Closed 5 years ago.
Improve this question
Can I ask why I get this?
Couldn't match type Char' with[Char]'
Expected type: [String]
Actual type: [Char]
In the second argument of (:)', namelystart'
In the expression: (show gm : start)
main :: IO ()
main = do
c <- parseArguments <$> getArgs
input <- hGetContents stdin
either print (handleGM input) c
handleGM input Config{..} = do
handleGM <$> readFile tgrammer >>= either putStrLn (mapM_ putStrLn)
where
handleGM gm = do
gm' <- parseGM gm
case action of
Simulate -> printGrammer gm' input
printGrammer gm#TGrammer{..} input =
(show gm:start)
Data:
type TState = String
type TSymbol = Char
data TGrammer = TGrammer
{ neterminaly :: [TState]
, terminaly :: [TState]
, start :: [Char]
, rules :: [Rules]
}
deriving (Show)
data Rules = Rules
{ from :: TSymbol
, to :: String
}
deriving (Show)
There are quite a few things that are very weird about your code, so hopefully correcting them will help you solve your problem.
Type Signatures
You should always include type signatures on your top-level bindings, as well as any non-trivial where or let bindings. These are my best guesses as to what you intended the types to be:
handleGM :: String -> Config -> IO ()
printGrammer :: TGrammer -> String -> IO ()
Shadowed Binding
handleGM appears to be defined twice, once inside of itself in a where binding. This is really bad practice because it looks like you are trying to do a recursive call. You should consider renaming the internal function, or in this case, just writing it out in the do-notation, since its not recursive (and therefore doesn't need the where binding). In fact, you have misused <$>, which should only be used to map a pure function over an impure value. In this case, you are trying to use it to map an impure function of an impure value, which results in the confusing and not-what-you-want selection of Either String () as the type for the inside handleGM.
Operator overuse
It's best not to use <$> and >>= if your code isn't working, as it can hide what is actually happening, so write them out explicitly (do-notation) when you have problems like this.
Here is how I would revise handleGM so based on the above:
handleGM :: String -> Config -> IO ()
handleGM input Config{..} = do
a <- readFile tgrammer
b <- either putStrLn (mapM_ putStrLn) a
gm' <- parseGM b
case action of
Simulate -> printGrammer gm' input
[Char] doesn't match Char
This is because you used the cons operator (:) :: Char -> [Char] -> [Char], but the first argument you gave it was already a [Char] (namely, show gm). What you probably want is (++) :: [Char] -> [Char] -> [Char] which will put your two [Char] together into one longer [Char]. You probably also want to print to the terminal rather than just compute a [Char], which means you need to use a function like putStrLn :: String -> IO (). If these are accurate, here is what I would revise printGrammer to:
printGrammer :: TGrammer -> String -> IO ()
printGrammer gm#TGrammer{..} input = putStrLn (show gm ++ start)
Miscellaneous
You don't seem to actually do anything with input, so why bother passing it in at all?
You might benefit from turning on -Wall by passing it as an argument when you compile. It turns on all the compiler warning so it will tell you if you probably made a mistake.
You only have one case in your case. Why have the case there at all if it doesn't ever do anything different.
action seems to be pulled out of thin air; where does it come from?

Language.Haskell.Interpreter: is this the right tool for the job at hand?

I have a little toy semantics for natural language, with words like:
ran :: String -> Bool
ran = (`elem` ["Bart", "Homer", "Marge"])
and:
bart :: String
bart = "Bart"
So for example, I can have (ran bart) :: Bool, and so on.
I want to write a parser which, for example takes the string "Bart ran" and returns True. I'd probably use Parsec for this.
However, the problem is being able to call functions via strings. E.g. getting from "ran" to the function ran. For this, I thought Language.Haskell.Interpreter's interpret function might be appropriate.
So my questions are:
Is this a sensible way to do what I want to do?
If so, why doesn't the following work, entered into GHCi, given a module called Grammar.hs in the same directory with ran defined as above:
let a = runInterpreter $ do
loadModules ["Grammar"]
setImports ["Prelude"]
interpret "ran" (as :: String -> Bool)
let b = do
x <- a
return $ x <*> pure "John"
b
I get the error:
"Left (WontCompile [GhcError {errMsg = "<interactive>:2:1:\n Not in scope: \8216ran\8217\n Perhaps you meant \8216tan\8217 (imported from Prelude)"}])"
which suggests that the import isn't working, and indeed, if I try something similar with a Prelude function, everything works.
Why do I get the following type error (among many others) if I try to compile the same code as in Q2, (minus the let):
No instance for MonadIO m0 arising from a use of runInterpreter
As for #2, you need to add "Grammar" to the setImports list as well:
runInterpreter $ do
loadModules ["HintDefs"]
setImports ["Prelude", "HintDefs"]
interpret "ran" (as :: String -> Bool)
As for #3, it is because runInterpreter is monomorphic in the choice of monad to run it in:
runInterpreter :: (MonadIO m, MonadMask m)
=> InterpreterT m a
-> m (Either InterpreterError a)
So you'll need to choose a particular m by running it in e.g. IO:
main :: IO ()
main = do
ran <- runInterpreter $ do
loadModules ["HintDefs"]
setImports ["Prelude", "HintDefs"]
interpret "ran" (as :: String -> Bool)
print $ ran <*> pure "John"
Now, as for #1, I am not convinced you need something as stupidly powerful as HInt here. You could just maintain a dictionary of String -> Bool functions keyed by a String key, something simple like a Map String (String -> Bool), and then use that to look up ran etc.

Write list of random numbers to file. No Instance for (Show (IO a0))

I am trying to write to file a list of random Integers in a file. There seems to be a problem with writeFile here. When I use my function randomFile it says no instance for (Show (IO a0)). I see writeFile doesn't print anything to screen but IO(), so when I call the function randomFile 1 2 3 it says no Instance for Show (IO a0) but actually I just want to execute the function and not have to print anything but how can I avoid this problem. I might be making a lot of errors here. Any help.
import Control.Monad
import Control.Applicative
import System.Random
randNo mind maxd = randomRIO (mind,maxd)
randomFile mind maxd noe = do
let l=(replicate (fromInteger(noe ^ noe)) ( mind `randNo` maxd))
writeFile "RFile.txt" (show l)
I think you have a misunderstanding of what IO is. If you haven't done it, I strongly recommend going through the Input and Output section of Learn You a Haskell.
IO doesn't necessarily have anything to do with print. In Haskell every entry in memory that was made by your own code is considered "pure" while any entry that touches the rest of the computer lives in IO (with some exceptions you will learn about over time).
We model IO using something called a Monad. Which you will learn more about the longer you do Haskell. To understand this, let's look at an example of some code that does and doesn't use IO:
noIOused :: Int -> Int
noIOused x = x + 5
usesIO :: Int -> IO Int
usesIO x = print x >> return (x + 5)
usesIO2 :: Int -> IO Int
usesIO2 x = do
print x
return (x + 5)
The first function is "pure". The second and third functions have an IO "effect" that comes in the form of printing to the screen. usesIO and usesIO2 are just 2 different ways of doing the same thing (it's the same code but with different syntax). I'll use the second format, called do notation from here.
Here are some other ways you could have had IO effects:
add5WithFile :: Int -> IO Int
add5WithFile x = do
writeFile "someFile.txt" (show x)
return (x + 5)
Notice that in that function we didn't print anything, we wrote a file. But writing a file has a side effect and interacts with the rest of the system. So any value we return has to get wrapped in IO.
addRandom :: Int -> IO Int
addRandom x = do
y <- randomRIO (1,10)
return (x + y)
In addRandom we called randomRIO (1,10). But the problem is that randomRIO doesn't return an Int. It returns an IO Int. Why? Because in order to get true randomness we need to interact with the system in some way. To get around that, we have to temporarily strip away the IO. That's where this line comes in:
y <- randomRIO (1,10)
That <- arrow tells us that we want a y value outside of IO. For as long as we remain inside the do syntax that y value is going to be "pure". Now we can use it just like any other value.
So for example we couldn't do this:
let w = x + (randomRIO (1,10))
Because that would be trying to add Int to IO Int. And unfortunately our + function doesn't know how to do that. So first we have to "bind" the result of randomRIO to y before we can add it to x.
Now let's look at your code:
let l=(replicate (fromInteger(noe ^ noe)) ( mind `randNo` maxd))
writeFile "RFile.txt" (show l)
The type of l is actually IO a0. It's a0 because you haven't told the compiler what kind of number you want. So it doesn't know if you want a fraction, a double, a big integer or whatever.
So the first problem is to let the compiler know a little bit more about what kind of random number you want. We do this by adding a type annotation:
randNo :: Int -> Int -> IO Int
randNo mind maxd = randomRIO (mind,maxd)
Now both you and the compiler knows what kind of value randNo is.
Now we need to "bind" that value inside of the do notation to temporarily escape IO. You might think that would be simple, like this:
randomFile mind maxd noe = do
l <- replicate (fromInteger(noe ^ noe)) ( mind `randNo` maxd)
writeFile "RFile.txt" (show l)
Surely that will "bind" the IO Int to l right? Unfortunately not. The problem here is that replicate is a function of the form Int -> a -> [a]. That is, given a number and a type, it will give you a list of that type.
If you give replicate an IO Int it's going to make [IO Int]. That actually looks more like this: List (IO Int) except we use [] as syntactic sugar for lists. Unfortunately if we want to "bind" an IO value to something with <- it has to be the out-most type.
So what you need is a way to turn an [IO Int] into an IO [Int]. There are two ways to do that. If we put \[IO a\] -> IO \[a\] into Hoogle we get this:
sequence :: Monad m => [m a] -> m [a]
As I mentioned before, we generalise IO to something called a Monad. Which isn't really that big a deal, we could pretend that sequence has this signature: sequence :: [IO a] -> IO [a] and it would be the same thing just specialised to IO.
Now your function would be done like this:
randomFile mind maxd noe = do
l <- sequence (replicate (fromInteger(noe ^ noe)) ( mind `randNo` maxd))
writeFile "RFile.txt" (show l)
But a sequence followed by replicate is something people have to do all the time. So someone went and made a function called replicateM:
replicateM :: Monad m => Int -> m a -> m [a]
Now we can write your function like this:
randomFile mind maxd noe = do
l <- replicateM (fromInteger(noe ^ noe)) ( mind `randNo` maxd)
writeFile "RFile.txt" (show l)
And for some real Haskell magic, you can write all 3 lines of code in a single line, like this:
randomFile mind maxd noe = randomRIO >>= writeFile "RFile.txt" . replicateM (fromInteger(noe ^ noe))
If that looks like gibberish to you, then there's a lot you need to learn. Here is the suggested path:
If you haven't already, start from the beginning with Learn You a Haskell
Then learn about how You could have invented Monads
Then learn more about how to use randomness in Haskell
Finally see if you can complete the 20 intermediate Haskell exercises

Maybe monad inside stack of transformers

I have the following code:
import Control.Monad
import Control.Monad.Trans
import Control.Monad.Trans.State
type T = StateT Int IO Int
someMaybe = Just 3
f :: T
f = do
x <- get
val <- lift $ do
val <- someMaybe
-- more code in Maybe monad
-- return 4
return 3
When I use do notation inside to work in Maybe monad it fails. From the error it gives it looks like type signature for this do doesn't match. However I have no idea how to fix it. I tried some lift combinations, but none of them worked and I don't want to guess anymore.
The problem is that Maybe is not part of your transformer stack. If your transformer only knows about StateT Int and IO, it does not know anything about how to lift Maybe.
You can fix this by changing your type T to something like:
type T = StateT Int (MaybeT IO) Int
(You'll need to import Control.Monad.Trans.Maybe.)
You will also need to change your inner do to work with MaybeT rather than Maybe. This means wrapping raw Maybe a values with MaybeT . return:
f :: T
f = do
x <- get
val <- lift $ do
val <- MaybeT $ return someMaybe
-- more code in Maybe monad
return 4
return 3
This is a little awkward, so you probably want to write a function like liftMaybe:
liftMaybe = MaybeT . return
If you used lift to lift IO a values in other parts of your code, this will now break because you have three levels in your transformer stack now. You will get an error that looks like this:
Couldn't match expected type `MaybeT IO t0'
with actual type `IO String'
To fix this, you should use liftIO for all your raw IO a values. This uses a typeclass to life IO actions through any number of transformer layers.
In response to your comment: if you only have a bit of code depending on Maybe, it would be easier just to put the result of the do notation into a variable and match against that:
let maybeVal = do val <- someMaybe
-- more Maybe code
return 4
case maybeVal of
Just res -> ...
Nothing -> ...
This means that the Maybe code will not be able to do an IO. You can also naturally use a function like fromMaybe instead of case.
If you want to run the code in the inner do purely in the Maybe monad, you will not have access to the StateT Int or IO monads (which might be a good thing). Doing so will return a Maybe value, which you will have to scrutinize:
import Control.Monad
import Control.Monad.Trans
import Control.Monad.Trans.State
type T = StateT Int IO Int
someMaybe = Just 3
f :: T
f = do
x <- get
-- no need to use bind
let mval = do
-- this code is purely in the Maybe monad
val <- someMaybe
-- more code in Maybe monad
return 4
-- scrutinize the resulting Maybe value now we are back in the StateT monad
case mval of
Just val -> liftIO . putStrLn $ "I got " ++ show val
Nothing -> liftIO . putStrLn $ "I got a rock"
return 3

Parsec and Applicative style

can someone help me to understand how to use Applicative style for writing Parsec parsers? This is the code i have:
module Main where
import Control.Applicative hiding (many)
import Text.Parsec
import Data.Functor.Identity
data Cmd = A | B deriving (Show)
main = do
line <- getContents
putStrLn . show $ parseCmd line
parseCmd :: String -> Either ParseError String
parseCmd input = parse cmdParse "(parser)" input
cmdParse :: Parsec String () String
cmdParse = do
slash <- char '/'
whatever <- many alphaNum
return (slash:whatever)
cmdParse2 :: String -> Parsec String () String
cmdParse2 = (:) <$> (char '/') <*> many alphaNum
but when i try to compile it, i get following:
/home/tomasherman/Desktop/funinthesun.hs:21:13:
Couldn't match expected type `Parsec String () String'
with actual type `[a0]'
Expected type: a0 -> [a0] -> Parsec String () String
Actual type: a0 -> [a0] -> [a0]
In the first argument of `(<$>)', namely `(:)'
In the first argument of `(<*>)', namely `(:) <$> (char '/')'
Failed, modules loaded: none.
The idea is that i want cmdParse2 to do same thing that cmdParse does, but using applicative stuff...my approach is probably completely wrong, i'm new to haskell
Your applicative usage is spot on, you just have an incorrect signature. Try:
cmdParse2 :: Parsec String () String
Your approach looks correct to me, the problem is that cmdParse2 has the wrong type. It should have the same type as cmdParse. By the way, you can omit the parens around char '/' in the applicative style parser.

Resources