Parsing string with parsec that needs to end with particular words?











up vote
1
down vote

favorite












I am working on some programming exercises. The one I am working on has following input format:



Give xxxxxxxxx as yyyy.


xxxxxxxx can be in several formats that repeatedly show up during these exercises. In particular its either binary (groups of 8 separated by spaces), hexadecimal (without spaces) or octal (groups of up to 3 numbers). I have already written parsers for these formats - however they all stumble over the "as". They looked like this



binaryParser = BinaryQuestion  <$> (count 8 ( oneOf "01") ) `sepBy1` space


I solved using this monstrosity (trimmed unnecessary code)



{-# LANGUAGE OverloadedStrings #-}
import Text.Parsec.ByteString
import Text.Parsec
import Text.Parsec.Char
import Data.ByteString.Char8 (pack, unpack, dropWhile, drop, snoc)
import qualified Data.ByteString as B

data Input = BinaryQuestion [String]
| HexQuestion [String]
| OctalQuestion [String]
deriving Show
data Question = Question {input :: Input, target :: Target} deriving Show
data Target = Word deriving Show

test1 :: B.ByteString
test1 = "Give 01110100 01110101 01110010 01110100 01101100 01100101 as a word."
test2 :: B.ByteString
test2 = "Give 646f63746f72 as a word."
test3 :: B.ByteString
test3 = "Give 164 151 155 145 as a word."

targetParser :: Parser Target
targetParser = string "word" >> return Word

wrapAs :: Parser a -> Parser [a]
wrapAs kind = manyTill kind (try (string " as"))
inputParser :: Parser Input
inputParser = choice [try binaryParser, try (space >> hexParser), try octParser]
binaryParser :: Parser Input
binaryParser = BinaryQuestion <$> wrapAs (space >> count 8 ( oneOf "01") )
hexParser :: Parser Input
hexParser = HexQuestion <$> wrapAs (count 2 hexDigit)
octParser :: Parser Input
octParser = OctalQuestion <$> wrapAs (many1 space >> many1 (oneOf ['0'..'7']))

questionParser :: Parser Question
questionParser = do
string "Give"
inp <- inputParser
string " a "
tar <- targetParser
char '.'
eof
return $ Question inp tar


I don't like that I need to use the following string "as" inside the parsing of Input, and they generally are less readable. I mean using regex it would be trivial to have a trailing string. So I am not satisfied with my solution.



Is there a way I can reuse the 'nice' parsers - or at least use more readable parsers?



additional notes



The code I along the lines I wish I could get working would look like this:



{-# LANGUAGE OverloadedStrings #-}

import Text.Parsec.ByteString
import Text.Parsec
import Text.Parsec.Char
import Data.ByteString.Char8 (pack, unpack, dropWhile, drop, snoc)
import qualified Data.ByteString as B

data Input = BinaryQuestion [String]
| HexQuestion [String]
| OctalQuestion [String]
deriving Show
data Question = Question {input :: Input, target :: Target} deriving Show
data Target = Word deriving Show

test1 :: B.ByteString
test1 = "Give 01110100 01110101 01110010 01110100 01101100 01100101 as a word."
test2 :: B.ByteString
test2 = "Give 646f63746f72 as a word."
test3 :: B.ByteString
test3 = "Give 164 151 155 145 as a word."

targetParser :: Parser Target
targetParser = string "word" >> return Word

inputParser :: Parser Input
inputParser = choice [try binaryParser, try hexParser, try octParser]
binaryParser :: Parser Input
binaryParser = BinaryQuestion <$> count 8 ( oneOf "01") `sepBy1` space
hexParser :: Parser Input
hexParser = HexQuestion <$> many1 (count 2 hexDigit)
octParser :: Parser Input
octParser = OctalQuestion <$> (many1 (oneOf ['0'..'7'])) `sepBy1` space

questionParser :: Parser Question
questionParser = do
string "Give"
many1 space
inp <- inputParser
many1 space
string "as a"
many1 space
tar <- targetParser
char '.'
eof
return $ Question inp tar


but parseTest questionParser test3 will return me parse error at (line 1, column 22):
unexpected "a"



I suppose the problem is that space is used as separator inside the input but also comes in the as a string. I don't see any function inside parsec that would fit. In frustration I tried adding try in various places - however no success.










share|improve this question
























  • try this code, test1 has error too: expecting space or "as a", right?
    – assembly.jc
    Nov 10 at 19:43










  • exactly, but test2 works (doesn't contain any spaces).
    – bdecaf
    Nov 11 at 17:41










  • Finally, I find a simple solution using Parsec, please see the EDIT of my answer.
    – assembly.jc
    Nov 14 at 11:18















up vote
1
down vote

favorite












I am working on some programming exercises. The one I am working on has following input format:



Give xxxxxxxxx as yyyy.


xxxxxxxx can be in several formats that repeatedly show up during these exercises. In particular its either binary (groups of 8 separated by spaces), hexadecimal (without spaces) or octal (groups of up to 3 numbers). I have already written parsers for these formats - however they all stumble over the "as". They looked like this



binaryParser = BinaryQuestion  <$> (count 8 ( oneOf "01") ) `sepBy1` space


I solved using this monstrosity (trimmed unnecessary code)



{-# LANGUAGE OverloadedStrings #-}
import Text.Parsec.ByteString
import Text.Parsec
import Text.Parsec.Char
import Data.ByteString.Char8 (pack, unpack, dropWhile, drop, snoc)
import qualified Data.ByteString as B

data Input = BinaryQuestion [String]
| HexQuestion [String]
| OctalQuestion [String]
deriving Show
data Question = Question {input :: Input, target :: Target} deriving Show
data Target = Word deriving Show

test1 :: B.ByteString
test1 = "Give 01110100 01110101 01110010 01110100 01101100 01100101 as a word."
test2 :: B.ByteString
test2 = "Give 646f63746f72 as a word."
test3 :: B.ByteString
test3 = "Give 164 151 155 145 as a word."

targetParser :: Parser Target
targetParser = string "word" >> return Word

wrapAs :: Parser a -> Parser [a]
wrapAs kind = manyTill kind (try (string " as"))
inputParser :: Parser Input
inputParser = choice [try binaryParser, try (space >> hexParser), try octParser]
binaryParser :: Parser Input
binaryParser = BinaryQuestion <$> wrapAs (space >> count 8 ( oneOf "01") )
hexParser :: Parser Input
hexParser = HexQuestion <$> wrapAs (count 2 hexDigit)
octParser :: Parser Input
octParser = OctalQuestion <$> wrapAs (many1 space >> many1 (oneOf ['0'..'7']))

questionParser :: Parser Question
questionParser = do
string "Give"
inp <- inputParser
string " a "
tar <- targetParser
char '.'
eof
return $ Question inp tar


I don't like that I need to use the following string "as" inside the parsing of Input, and they generally are less readable. I mean using regex it would be trivial to have a trailing string. So I am not satisfied with my solution.



Is there a way I can reuse the 'nice' parsers - or at least use more readable parsers?



additional notes



The code I along the lines I wish I could get working would look like this:



{-# LANGUAGE OverloadedStrings #-}

import Text.Parsec.ByteString
import Text.Parsec
import Text.Parsec.Char
import Data.ByteString.Char8 (pack, unpack, dropWhile, drop, snoc)
import qualified Data.ByteString as B

data Input = BinaryQuestion [String]
| HexQuestion [String]
| OctalQuestion [String]
deriving Show
data Question = Question {input :: Input, target :: Target} deriving Show
data Target = Word deriving Show

test1 :: B.ByteString
test1 = "Give 01110100 01110101 01110010 01110100 01101100 01100101 as a word."
test2 :: B.ByteString
test2 = "Give 646f63746f72 as a word."
test3 :: B.ByteString
test3 = "Give 164 151 155 145 as a word."

targetParser :: Parser Target
targetParser = string "word" >> return Word

inputParser :: Parser Input
inputParser = choice [try binaryParser, try hexParser, try octParser]
binaryParser :: Parser Input
binaryParser = BinaryQuestion <$> count 8 ( oneOf "01") `sepBy1` space
hexParser :: Parser Input
hexParser = HexQuestion <$> many1 (count 2 hexDigit)
octParser :: Parser Input
octParser = OctalQuestion <$> (many1 (oneOf ['0'..'7'])) `sepBy1` space

questionParser :: Parser Question
questionParser = do
string "Give"
many1 space
inp <- inputParser
many1 space
string "as a"
many1 space
tar <- targetParser
char '.'
eof
return $ Question inp tar


but parseTest questionParser test3 will return me parse error at (line 1, column 22):
unexpected "a"



I suppose the problem is that space is used as separator inside the input but also comes in the as a string. I don't see any function inside parsec that would fit. In frustration I tried adding try in various places - however no success.










share|improve this question
























  • try this code, test1 has error too: expecting space or "as a", right?
    – assembly.jc
    Nov 10 at 19:43










  • exactly, but test2 works (doesn't contain any spaces).
    – bdecaf
    Nov 11 at 17:41










  • Finally, I find a simple solution using Parsec, please see the EDIT of my answer.
    – assembly.jc
    Nov 14 at 11:18













up vote
1
down vote

favorite









up vote
1
down vote

favorite











I am working on some programming exercises. The one I am working on has following input format:



Give xxxxxxxxx as yyyy.


xxxxxxxx can be in several formats that repeatedly show up during these exercises. In particular its either binary (groups of 8 separated by spaces), hexadecimal (without spaces) or octal (groups of up to 3 numbers). I have already written parsers for these formats - however they all stumble over the "as". They looked like this



binaryParser = BinaryQuestion  <$> (count 8 ( oneOf "01") ) `sepBy1` space


I solved using this monstrosity (trimmed unnecessary code)



{-# LANGUAGE OverloadedStrings #-}
import Text.Parsec.ByteString
import Text.Parsec
import Text.Parsec.Char
import Data.ByteString.Char8 (pack, unpack, dropWhile, drop, snoc)
import qualified Data.ByteString as B

data Input = BinaryQuestion [String]
| HexQuestion [String]
| OctalQuestion [String]
deriving Show
data Question = Question {input :: Input, target :: Target} deriving Show
data Target = Word deriving Show

test1 :: B.ByteString
test1 = "Give 01110100 01110101 01110010 01110100 01101100 01100101 as a word."
test2 :: B.ByteString
test2 = "Give 646f63746f72 as a word."
test3 :: B.ByteString
test3 = "Give 164 151 155 145 as a word."

targetParser :: Parser Target
targetParser = string "word" >> return Word

wrapAs :: Parser a -> Parser [a]
wrapAs kind = manyTill kind (try (string " as"))
inputParser :: Parser Input
inputParser = choice [try binaryParser, try (space >> hexParser), try octParser]
binaryParser :: Parser Input
binaryParser = BinaryQuestion <$> wrapAs (space >> count 8 ( oneOf "01") )
hexParser :: Parser Input
hexParser = HexQuestion <$> wrapAs (count 2 hexDigit)
octParser :: Parser Input
octParser = OctalQuestion <$> wrapAs (many1 space >> many1 (oneOf ['0'..'7']))

questionParser :: Parser Question
questionParser = do
string "Give"
inp <- inputParser
string " a "
tar <- targetParser
char '.'
eof
return $ Question inp tar


I don't like that I need to use the following string "as" inside the parsing of Input, and they generally are less readable. I mean using regex it would be trivial to have a trailing string. So I am not satisfied with my solution.



Is there a way I can reuse the 'nice' parsers - or at least use more readable parsers?



additional notes



The code I along the lines I wish I could get working would look like this:



{-# LANGUAGE OverloadedStrings #-}

import Text.Parsec.ByteString
import Text.Parsec
import Text.Parsec.Char
import Data.ByteString.Char8 (pack, unpack, dropWhile, drop, snoc)
import qualified Data.ByteString as B

data Input = BinaryQuestion [String]
| HexQuestion [String]
| OctalQuestion [String]
deriving Show
data Question = Question {input :: Input, target :: Target} deriving Show
data Target = Word deriving Show

test1 :: B.ByteString
test1 = "Give 01110100 01110101 01110010 01110100 01101100 01100101 as a word."
test2 :: B.ByteString
test2 = "Give 646f63746f72 as a word."
test3 :: B.ByteString
test3 = "Give 164 151 155 145 as a word."

targetParser :: Parser Target
targetParser = string "word" >> return Word

inputParser :: Parser Input
inputParser = choice [try binaryParser, try hexParser, try octParser]
binaryParser :: Parser Input
binaryParser = BinaryQuestion <$> count 8 ( oneOf "01") `sepBy1` space
hexParser :: Parser Input
hexParser = HexQuestion <$> many1 (count 2 hexDigit)
octParser :: Parser Input
octParser = OctalQuestion <$> (many1 (oneOf ['0'..'7'])) `sepBy1` space

questionParser :: Parser Question
questionParser = do
string "Give"
many1 space
inp <- inputParser
many1 space
string "as a"
many1 space
tar <- targetParser
char '.'
eof
return $ Question inp tar


but parseTest questionParser test3 will return me parse error at (line 1, column 22):
unexpected "a"



I suppose the problem is that space is used as separator inside the input but also comes in the as a string. I don't see any function inside parsec that would fit. In frustration I tried adding try in various places - however no success.










share|improve this question















I am working on some programming exercises. The one I am working on has following input format:



Give xxxxxxxxx as yyyy.


xxxxxxxx can be in several formats that repeatedly show up during these exercises. In particular its either binary (groups of 8 separated by spaces), hexadecimal (without spaces) or octal (groups of up to 3 numbers). I have already written parsers for these formats - however they all stumble over the "as". They looked like this



binaryParser = BinaryQuestion  <$> (count 8 ( oneOf "01") ) `sepBy1` space


I solved using this monstrosity (trimmed unnecessary code)



{-# LANGUAGE OverloadedStrings #-}
import Text.Parsec.ByteString
import Text.Parsec
import Text.Parsec.Char
import Data.ByteString.Char8 (pack, unpack, dropWhile, drop, snoc)
import qualified Data.ByteString as B

data Input = BinaryQuestion [String]
| HexQuestion [String]
| OctalQuestion [String]
deriving Show
data Question = Question {input :: Input, target :: Target} deriving Show
data Target = Word deriving Show

test1 :: B.ByteString
test1 = "Give 01110100 01110101 01110010 01110100 01101100 01100101 as a word."
test2 :: B.ByteString
test2 = "Give 646f63746f72 as a word."
test3 :: B.ByteString
test3 = "Give 164 151 155 145 as a word."

targetParser :: Parser Target
targetParser = string "word" >> return Word

wrapAs :: Parser a -> Parser [a]
wrapAs kind = manyTill kind (try (string " as"))
inputParser :: Parser Input
inputParser = choice [try binaryParser, try (space >> hexParser), try octParser]
binaryParser :: Parser Input
binaryParser = BinaryQuestion <$> wrapAs (space >> count 8 ( oneOf "01") )
hexParser :: Parser Input
hexParser = HexQuestion <$> wrapAs (count 2 hexDigit)
octParser :: Parser Input
octParser = OctalQuestion <$> wrapAs (many1 space >> many1 (oneOf ['0'..'7']))

questionParser :: Parser Question
questionParser = do
string "Give"
inp <- inputParser
string " a "
tar <- targetParser
char '.'
eof
return $ Question inp tar


I don't like that I need to use the following string "as" inside the parsing of Input, and they generally are less readable. I mean using regex it would be trivial to have a trailing string. So I am not satisfied with my solution.



Is there a way I can reuse the 'nice' parsers - or at least use more readable parsers?



additional notes



The code I along the lines I wish I could get working would look like this:



{-# LANGUAGE OverloadedStrings #-}

import Text.Parsec.ByteString
import Text.Parsec
import Text.Parsec.Char
import Data.ByteString.Char8 (pack, unpack, dropWhile, drop, snoc)
import qualified Data.ByteString as B

data Input = BinaryQuestion [String]
| HexQuestion [String]
| OctalQuestion [String]
deriving Show
data Question = Question {input :: Input, target :: Target} deriving Show
data Target = Word deriving Show

test1 :: B.ByteString
test1 = "Give 01110100 01110101 01110010 01110100 01101100 01100101 as a word."
test2 :: B.ByteString
test2 = "Give 646f63746f72 as a word."
test3 :: B.ByteString
test3 = "Give 164 151 155 145 as a word."

targetParser :: Parser Target
targetParser = string "word" >> return Word

inputParser :: Parser Input
inputParser = choice [try binaryParser, try hexParser, try octParser]
binaryParser :: Parser Input
binaryParser = BinaryQuestion <$> count 8 ( oneOf "01") `sepBy1` space
hexParser :: Parser Input
hexParser = HexQuestion <$> many1 (count 2 hexDigit)
octParser :: Parser Input
octParser = OctalQuestion <$> (many1 (oneOf ['0'..'7'])) `sepBy1` space

questionParser :: Parser Question
questionParser = do
string "Give"
many1 space
inp <- inputParser
many1 space
string "as a"
many1 space
tar <- targetParser
char '.'
eof
return $ Question inp tar


but parseTest questionParser test3 will return me parse error at (line 1, column 22):
unexpected "a"



I suppose the problem is that space is used as separator inside the input but also comes in the as a string. I don't see any function inside parsec that would fit. In frustration I tried adding try in various places - however no success.







haskell parsec






share|improve this question















share|improve this question













share|improve this question




share|improve this question








edited Nov 10 at 10:40

























asked Nov 10 at 7:36









bdecaf

3,8941636




3,8941636












  • try this code, test1 has error too: expecting space or "as a", right?
    – assembly.jc
    Nov 10 at 19:43










  • exactly, but test2 works (doesn't contain any spaces).
    – bdecaf
    Nov 11 at 17:41










  • Finally, I find a simple solution using Parsec, please see the EDIT of my answer.
    – assembly.jc
    Nov 14 at 11:18


















  • try this code, test1 has error too: expecting space or "as a", right?
    – assembly.jc
    Nov 10 at 19:43










  • exactly, but test2 works (doesn't contain any spaces).
    – bdecaf
    Nov 11 at 17:41










  • Finally, I find a simple solution using Parsec, please see the EDIT of my answer.
    – assembly.jc
    Nov 14 at 11:18
















try this code, test1 has error too: expecting space or "as a", right?
– assembly.jc
Nov 10 at 19:43




try this code, test1 has error too: expecting space or "as a", right?
– assembly.jc
Nov 10 at 19:43












exactly, but test2 works (doesn't contain any spaces).
– bdecaf
Nov 11 at 17:41




exactly, but test2 works (doesn't contain any spaces).
– bdecaf
Nov 11 at 17:41












Finally, I find a simple solution using Parsec, please see the EDIT of my answer.
– assembly.jc
Nov 14 at 11:18




Finally, I find a simple solution using Parsec, please see the EDIT of my answer.
– assembly.jc
Nov 14 at 11:18












2 Answers
2






active

oldest

votes

















up vote
1
down vote













You are working with the pattern: Give {source} as a {target}.
So you can pipe:




  • Parser for Give a

  • Parser for {source}

  • Parser for as a

  • Parser for {target}


No need to wrap the parser for {source} with the parser for as a.






share|improve this answer





















  • maybe I misunderstand you - but in this case I get parse error at (line 1, column 60): unexpected "a" - I append the code I used to the question.
    – bdecaf
    Nov 10 at 10:04










  • You do not parse the spaces around the "as a". It expect the "as a" but you provide " as a "
    – Yotam Ohad
    Nov 11 at 16:10










  • doesn't the many1 space take care of the spaces?
    – bdecaf
    Nov 11 at 17:29










  • I think it might be the use of sep1 that forces it to accept two or more spaces.
    – Yotam Ohad
    Nov 11 at 18:38










  • interesting. So just using many spaces should capture one? But I get the same parsing error.
    – bdecaf
    Nov 12 at 6:50


















up vote
1
down vote













EDIT:



As said in comment, the clean parser cannot be reused by Previouse solution stated at the end of this post.



It led to develop a small parser using Parsec to handle all the possible situations for end parsing of numeric string separated by space i.e.




  1. end with a space followed by non-required-digit character, e.g. "..11 as"

  2. end with a space, e.g. "..11 "

  3. end with eof, e.g. "..11"


and such a parser as below:



numParser:: (Parser Char->Parser String)->[Char]->Parser [String]
numParser repeatParser digits =
let digitParser = repeatParser $ oneOf digits
endParser = (try $ lookAhead $ (space >> noneOf digits)) <|>
(try $ lookAhead $ (space <* eof)) <|>
(eof >> return ' ')
in do init <- digitParser
rest <- manyTill (space >> digitParser) endParser
return (init : rest)


And binaryParser and octParser need to be modified as below:



binaryParser = BinaryQuestion <$> numParser (count 8) "01"
octParser = OctalQuestion <$> numParser many1 ['0'..'7']


And Nothing need to change of questionParser stated in question, for reference, I state it again here:



questionParser = do
string "Give"
many1 space
inp <- inputParser
many1 space --no need change to many
string "as a"
many1 space
tar <- targetParser
char '.'
eof
return $ Question inp tar


Previous Solution:



The functions endBy1 and many in Text.Parsec are helpful in this situation.



To replace sepBy1 by endBy1 as



binaryParser = BinaryQuestion  <$> count 8 ( oneOf "01") `endBy1` space


and



octParser = OctalQuestion  <$>  (many1 (oneOf ['0'..'7'])) `endBy1` space


Unlike sepBy1, endBy1 will read next some chars to determine whether end the parsing, and therefor, one space after the last digit will be consumed, i.e.



Give 164 151 155 145 as a word.
^ this space will be consumed


So, instead of checking one or many space before "as a...", it need check zero or many space, so why use many function instead of many1, now the code become:



...
inp <- inputParser
many space -- change to many
string "as a"
....





share|improve this answer























  • It's cleaner than my monstrosity ;) However the space then seeps into the parser. What I would like to learn how to reuse a "clean" parser in such situations. Say I have a second program that would send me the input as "123 123 123" (no ending space).
    – bdecaf
    Nov 11 at 9:54






  • 1




    @bdecaf But why don't use Parsec to extract the input string firstly, say "164 151 155 145" in test3, and then use inputParser to parse it ? which can reuse most Parser except questionParser.
    – assembly.jc
    Nov 11 at 11:35










  • sounds like an idea. Need some time to wrap my head around how to do this ;)
    – bdecaf
    Nov 11 at 17:34










  • @bdecaf But the extract first approach need to parse same string twice. If need to parse a long string read from file, it is inefficient. I still look for a better way using Parsec to solve this type of problem. Maybe, in general, break string into tokens firstly is elegant approach, but too complex to your case.
    – assembly.jc
    Nov 13 at 5:54











Your Answer






StackExchange.ifUsing("editor", function () {
StackExchange.using("externalEditor", function () {
StackExchange.using("snippets", function () {
StackExchange.snippets.init();
});
});
}, "code-snippets");

StackExchange.ready(function() {
var channelOptions = {
tags: "".split(" "),
id: "1"
};
initTagRenderer("".split(" "), "".split(" "), channelOptions);

StackExchange.using("externalEditor", function() {
// Have to fire editor after snippets, if snippets enabled
if (StackExchange.settings.snippets.snippetsEnabled) {
StackExchange.using("snippets", function() {
createEditor();
});
}
else {
createEditor();
}
});

function createEditor() {
StackExchange.prepareEditor({
heartbeatType: 'answer',
convertImagesToLinks: true,
noModals: true,
showLowRepImageUploadWarning: true,
reputationToPostImages: 10,
bindNavPrevention: true,
postfix: "",
imageUploader: {
brandingHtml: "Powered by u003ca class="icon-imgur-white" href="https://imgur.com/"u003eu003c/au003e",
contentPolicyHtml: "User contributions licensed under u003ca href="https://creativecommons.org/licenses/by-sa/3.0/"u003ecc by-sa 3.0 with attribution requiredu003c/au003e u003ca href="https://stackoverflow.com/legal/content-policy"u003e(content policy)u003c/au003e",
allowUrls: true
},
onDemand: true,
discardSelector: ".discard-answer"
,immediatelyShowMarkdownHelp:true
});


}
});














draft saved

draft discarded


















StackExchange.ready(
function () {
StackExchange.openid.initPostLogin('.new-post-login', 'https%3a%2f%2fstackoverflow.com%2fquestions%2f53236949%2fparsing-string-with-parsec-that-needs-to-end-with-particular-words%23new-answer', 'question_page');
}
);

Post as a guest















Required, but never shown

























2 Answers
2






active

oldest

votes








2 Answers
2






active

oldest

votes









active

oldest

votes






active

oldest

votes








up vote
1
down vote













You are working with the pattern: Give {source} as a {target}.
So you can pipe:




  • Parser for Give a

  • Parser for {source}

  • Parser for as a

  • Parser for {target}


No need to wrap the parser for {source} with the parser for as a.






share|improve this answer





















  • maybe I misunderstand you - but in this case I get parse error at (line 1, column 60): unexpected "a" - I append the code I used to the question.
    – bdecaf
    Nov 10 at 10:04










  • You do not parse the spaces around the "as a". It expect the "as a" but you provide " as a "
    – Yotam Ohad
    Nov 11 at 16:10










  • doesn't the many1 space take care of the spaces?
    – bdecaf
    Nov 11 at 17:29










  • I think it might be the use of sep1 that forces it to accept two or more spaces.
    – Yotam Ohad
    Nov 11 at 18:38










  • interesting. So just using many spaces should capture one? But I get the same parsing error.
    – bdecaf
    Nov 12 at 6:50















up vote
1
down vote













You are working with the pattern: Give {source} as a {target}.
So you can pipe:




  • Parser for Give a

  • Parser for {source}

  • Parser for as a

  • Parser for {target}


No need to wrap the parser for {source} with the parser for as a.






share|improve this answer





















  • maybe I misunderstand you - but in this case I get parse error at (line 1, column 60): unexpected "a" - I append the code I used to the question.
    – bdecaf
    Nov 10 at 10:04










  • You do not parse the spaces around the "as a". It expect the "as a" but you provide " as a "
    – Yotam Ohad
    Nov 11 at 16:10










  • doesn't the many1 space take care of the spaces?
    – bdecaf
    Nov 11 at 17:29










  • I think it might be the use of sep1 that forces it to accept two or more spaces.
    – Yotam Ohad
    Nov 11 at 18:38










  • interesting. So just using many spaces should capture one? But I get the same parsing error.
    – bdecaf
    Nov 12 at 6:50













up vote
1
down vote










up vote
1
down vote









You are working with the pattern: Give {source} as a {target}.
So you can pipe:




  • Parser for Give a

  • Parser for {source}

  • Parser for as a

  • Parser for {target}


No need to wrap the parser for {source} with the parser for as a.






share|improve this answer












You are working with the pattern: Give {source} as a {target}.
So you can pipe:




  • Parser for Give a

  • Parser for {source}

  • Parser for as a

  • Parser for {target}


No need to wrap the parser for {source} with the parser for as a.







share|improve this answer












share|improve this answer



share|improve this answer










answered Nov 10 at 8:50









Yotam Ohad

11519




11519












  • maybe I misunderstand you - but in this case I get parse error at (line 1, column 60): unexpected "a" - I append the code I used to the question.
    – bdecaf
    Nov 10 at 10:04










  • You do not parse the spaces around the "as a". It expect the "as a" but you provide " as a "
    – Yotam Ohad
    Nov 11 at 16:10










  • doesn't the many1 space take care of the spaces?
    – bdecaf
    Nov 11 at 17:29










  • I think it might be the use of sep1 that forces it to accept two or more spaces.
    – Yotam Ohad
    Nov 11 at 18:38










  • interesting. So just using many spaces should capture one? But I get the same parsing error.
    – bdecaf
    Nov 12 at 6:50


















  • maybe I misunderstand you - but in this case I get parse error at (line 1, column 60): unexpected "a" - I append the code I used to the question.
    – bdecaf
    Nov 10 at 10:04










  • You do not parse the spaces around the "as a". It expect the "as a" but you provide " as a "
    – Yotam Ohad
    Nov 11 at 16:10










  • doesn't the many1 space take care of the spaces?
    – bdecaf
    Nov 11 at 17:29










  • I think it might be the use of sep1 that forces it to accept two or more spaces.
    – Yotam Ohad
    Nov 11 at 18:38










  • interesting. So just using many spaces should capture one? But I get the same parsing error.
    – bdecaf
    Nov 12 at 6:50
















maybe I misunderstand you - but in this case I get parse error at (line 1, column 60): unexpected "a" - I append the code I used to the question.
– bdecaf
Nov 10 at 10:04




maybe I misunderstand you - but in this case I get parse error at (line 1, column 60): unexpected "a" - I append the code I used to the question.
– bdecaf
Nov 10 at 10:04












You do not parse the spaces around the "as a". It expect the "as a" but you provide " as a "
– Yotam Ohad
Nov 11 at 16:10




You do not parse the spaces around the "as a". It expect the "as a" but you provide " as a "
– Yotam Ohad
Nov 11 at 16:10












doesn't the many1 space take care of the spaces?
– bdecaf
Nov 11 at 17:29




doesn't the many1 space take care of the spaces?
– bdecaf
Nov 11 at 17:29












I think it might be the use of sep1 that forces it to accept two or more spaces.
– Yotam Ohad
Nov 11 at 18:38




I think it might be the use of sep1 that forces it to accept two or more spaces.
– Yotam Ohad
Nov 11 at 18:38












interesting. So just using many spaces should capture one? But I get the same parsing error.
– bdecaf
Nov 12 at 6:50




interesting. So just using many spaces should capture one? But I get the same parsing error.
– bdecaf
Nov 12 at 6:50












up vote
1
down vote













EDIT:



As said in comment, the clean parser cannot be reused by Previouse solution stated at the end of this post.



It led to develop a small parser using Parsec to handle all the possible situations for end parsing of numeric string separated by space i.e.




  1. end with a space followed by non-required-digit character, e.g. "..11 as"

  2. end with a space, e.g. "..11 "

  3. end with eof, e.g. "..11"


and such a parser as below:



numParser:: (Parser Char->Parser String)->[Char]->Parser [String]
numParser repeatParser digits =
let digitParser = repeatParser $ oneOf digits
endParser = (try $ lookAhead $ (space >> noneOf digits)) <|>
(try $ lookAhead $ (space <* eof)) <|>
(eof >> return ' ')
in do init <- digitParser
rest <- manyTill (space >> digitParser) endParser
return (init : rest)


And binaryParser and octParser need to be modified as below:



binaryParser = BinaryQuestion <$> numParser (count 8) "01"
octParser = OctalQuestion <$> numParser many1 ['0'..'7']


And Nothing need to change of questionParser stated in question, for reference, I state it again here:



questionParser = do
string "Give"
many1 space
inp <- inputParser
many1 space --no need change to many
string "as a"
many1 space
tar <- targetParser
char '.'
eof
return $ Question inp tar


Previous Solution:



The functions endBy1 and many in Text.Parsec are helpful in this situation.



To replace sepBy1 by endBy1 as



binaryParser = BinaryQuestion  <$> count 8 ( oneOf "01") `endBy1` space


and



octParser = OctalQuestion  <$>  (many1 (oneOf ['0'..'7'])) `endBy1` space


Unlike sepBy1, endBy1 will read next some chars to determine whether end the parsing, and therefor, one space after the last digit will be consumed, i.e.



Give 164 151 155 145 as a word.
^ this space will be consumed


So, instead of checking one or many space before "as a...", it need check zero or many space, so why use many function instead of many1, now the code become:



...
inp <- inputParser
many space -- change to many
string "as a"
....





share|improve this answer























  • It's cleaner than my monstrosity ;) However the space then seeps into the parser. What I would like to learn how to reuse a "clean" parser in such situations. Say I have a second program that would send me the input as "123 123 123" (no ending space).
    – bdecaf
    Nov 11 at 9:54






  • 1




    @bdecaf But why don't use Parsec to extract the input string firstly, say "164 151 155 145" in test3, and then use inputParser to parse it ? which can reuse most Parser except questionParser.
    – assembly.jc
    Nov 11 at 11:35










  • sounds like an idea. Need some time to wrap my head around how to do this ;)
    – bdecaf
    Nov 11 at 17:34










  • @bdecaf But the extract first approach need to parse same string twice. If need to parse a long string read from file, it is inefficient. I still look for a better way using Parsec to solve this type of problem. Maybe, in general, break string into tokens firstly is elegant approach, but too complex to your case.
    – assembly.jc
    Nov 13 at 5:54















up vote
1
down vote













EDIT:



As said in comment, the clean parser cannot be reused by Previouse solution stated at the end of this post.



It led to develop a small parser using Parsec to handle all the possible situations for end parsing of numeric string separated by space i.e.




  1. end with a space followed by non-required-digit character, e.g. "..11 as"

  2. end with a space, e.g. "..11 "

  3. end with eof, e.g. "..11"


and such a parser as below:



numParser:: (Parser Char->Parser String)->[Char]->Parser [String]
numParser repeatParser digits =
let digitParser = repeatParser $ oneOf digits
endParser = (try $ lookAhead $ (space >> noneOf digits)) <|>
(try $ lookAhead $ (space <* eof)) <|>
(eof >> return ' ')
in do init <- digitParser
rest <- manyTill (space >> digitParser) endParser
return (init : rest)


And binaryParser and octParser need to be modified as below:



binaryParser = BinaryQuestion <$> numParser (count 8) "01"
octParser = OctalQuestion <$> numParser many1 ['0'..'7']


And Nothing need to change of questionParser stated in question, for reference, I state it again here:



questionParser = do
string "Give"
many1 space
inp <- inputParser
many1 space --no need change to many
string "as a"
many1 space
tar <- targetParser
char '.'
eof
return $ Question inp tar


Previous Solution:



The functions endBy1 and many in Text.Parsec are helpful in this situation.



To replace sepBy1 by endBy1 as



binaryParser = BinaryQuestion  <$> count 8 ( oneOf "01") `endBy1` space


and



octParser = OctalQuestion  <$>  (many1 (oneOf ['0'..'7'])) `endBy1` space


Unlike sepBy1, endBy1 will read next some chars to determine whether end the parsing, and therefor, one space after the last digit will be consumed, i.e.



Give 164 151 155 145 as a word.
^ this space will be consumed


So, instead of checking one or many space before "as a...", it need check zero or many space, so why use many function instead of many1, now the code become:



...
inp <- inputParser
many space -- change to many
string "as a"
....





share|improve this answer























  • It's cleaner than my monstrosity ;) However the space then seeps into the parser. What I would like to learn how to reuse a "clean" parser in such situations. Say I have a second program that would send me the input as "123 123 123" (no ending space).
    – bdecaf
    Nov 11 at 9:54






  • 1




    @bdecaf But why don't use Parsec to extract the input string firstly, say "164 151 155 145" in test3, and then use inputParser to parse it ? which can reuse most Parser except questionParser.
    – assembly.jc
    Nov 11 at 11:35










  • sounds like an idea. Need some time to wrap my head around how to do this ;)
    – bdecaf
    Nov 11 at 17:34










  • @bdecaf But the extract first approach need to parse same string twice. If need to parse a long string read from file, it is inefficient. I still look for a better way using Parsec to solve this type of problem. Maybe, in general, break string into tokens firstly is elegant approach, but too complex to your case.
    – assembly.jc
    Nov 13 at 5:54













up vote
1
down vote










up vote
1
down vote









EDIT:



As said in comment, the clean parser cannot be reused by Previouse solution stated at the end of this post.



It led to develop a small parser using Parsec to handle all the possible situations for end parsing of numeric string separated by space i.e.




  1. end with a space followed by non-required-digit character, e.g. "..11 as"

  2. end with a space, e.g. "..11 "

  3. end with eof, e.g. "..11"


and such a parser as below:



numParser:: (Parser Char->Parser String)->[Char]->Parser [String]
numParser repeatParser digits =
let digitParser = repeatParser $ oneOf digits
endParser = (try $ lookAhead $ (space >> noneOf digits)) <|>
(try $ lookAhead $ (space <* eof)) <|>
(eof >> return ' ')
in do init <- digitParser
rest <- manyTill (space >> digitParser) endParser
return (init : rest)


And binaryParser and octParser need to be modified as below:



binaryParser = BinaryQuestion <$> numParser (count 8) "01"
octParser = OctalQuestion <$> numParser many1 ['0'..'7']


And Nothing need to change of questionParser stated in question, for reference, I state it again here:



questionParser = do
string "Give"
many1 space
inp <- inputParser
many1 space --no need change to many
string "as a"
many1 space
tar <- targetParser
char '.'
eof
return $ Question inp tar


Previous Solution:



The functions endBy1 and many in Text.Parsec are helpful in this situation.



To replace sepBy1 by endBy1 as



binaryParser = BinaryQuestion  <$> count 8 ( oneOf "01") `endBy1` space


and



octParser = OctalQuestion  <$>  (many1 (oneOf ['0'..'7'])) `endBy1` space


Unlike sepBy1, endBy1 will read next some chars to determine whether end the parsing, and therefor, one space after the last digit will be consumed, i.e.



Give 164 151 155 145 as a word.
^ this space will be consumed


So, instead of checking one or many space before "as a...", it need check zero or many space, so why use many function instead of many1, now the code become:



...
inp <- inputParser
many space -- change to many
string "as a"
....





share|improve this answer














EDIT:



As said in comment, the clean parser cannot be reused by Previouse solution stated at the end of this post.



It led to develop a small parser using Parsec to handle all the possible situations for end parsing of numeric string separated by space i.e.




  1. end with a space followed by non-required-digit character, e.g. "..11 as"

  2. end with a space, e.g. "..11 "

  3. end with eof, e.g. "..11"


and such a parser as below:



numParser:: (Parser Char->Parser String)->[Char]->Parser [String]
numParser repeatParser digits =
let digitParser = repeatParser $ oneOf digits
endParser = (try $ lookAhead $ (space >> noneOf digits)) <|>
(try $ lookAhead $ (space <* eof)) <|>
(eof >> return ' ')
in do init <- digitParser
rest <- manyTill (space >> digitParser) endParser
return (init : rest)


And binaryParser and octParser need to be modified as below:



binaryParser = BinaryQuestion <$> numParser (count 8) "01"
octParser = OctalQuestion <$> numParser many1 ['0'..'7']


And Nothing need to change of questionParser stated in question, for reference, I state it again here:



questionParser = do
string "Give"
many1 space
inp <- inputParser
many1 space --no need change to many
string "as a"
many1 space
tar <- targetParser
char '.'
eof
return $ Question inp tar


Previous Solution:



The functions endBy1 and many in Text.Parsec are helpful in this situation.



To replace sepBy1 by endBy1 as



binaryParser = BinaryQuestion  <$> count 8 ( oneOf "01") `endBy1` space


and



octParser = OctalQuestion  <$>  (many1 (oneOf ['0'..'7'])) `endBy1` space


Unlike sepBy1, endBy1 will read next some chars to determine whether end the parsing, and therefor, one space after the last digit will be consumed, i.e.



Give 164 151 155 145 as a word.
^ this space will be consumed


So, instead of checking one or many space before "as a...", it need check zero or many space, so why use many function instead of many1, now the code become:



...
inp <- inputParser
many space -- change to many
string "as a"
....






share|improve this answer














share|improve this answer



share|improve this answer








edited Nov 14 at 11:14

























answered Nov 10 at 21:08









assembly.jc

1,130212




1,130212












  • It's cleaner than my monstrosity ;) However the space then seeps into the parser. What I would like to learn how to reuse a "clean" parser in such situations. Say I have a second program that would send me the input as "123 123 123" (no ending space).
    – bdecaf
    Nov 11 at 9:54






  • 1




    @bdecaf But why don't use Parsec to extract the input string firstly, say "164 151 155 145" in test3, and then use inputParser to parse it ? which can reuse most Parser except questionParser.
    – assembly.jc
    Nov 11 at 11:35










  • sounds like an idea. Need some time to wrap my head around how to do this ;)
    – bdecaf
    Nov 11 at 17:34










  • @bdecaf But the extract first approach need to parse same string twice. If need to parse a long string read from file, it is inefficient. I still look for a better way using Parsec to solve this type of problem. Maybe, in general, break string into tokens firstly is elegant approach, but too complex to your case.
    – assembly.jc
    Nov 13 at 5:54


















  • It's cleaner than my monstrosity ;) However the space then seeps into the parser. What I would like to learn how to reuse a "clean" parser in such situations. Say I have a second program that would send me the input as "123 123 123" (no ending space).
    – bdecaf
    Nov 11 at 9:54






  • 1




    @bdecaf But why don't use Parsec to extract the input string firstly, say "164 151 155 145" in test3, and then use inputParser to parse it ? which can reuse most Parser except questionParser.
    – assembly.jc
    Nov 11 at 11:35










  • sounds like an idea. Need some time to wrap my head around how to do this ;)
    – bdecaf
    Nov 11 at 17:34










  • @bdecaf But the extract first approach need to parse same string twice. If need to parse a long string read from file, it is inefficient. I still look for a better way using Parsec to solve this type of problem. Maybe, in general, break string into tokens firstly is elegant approach, but too complex to your case.
    – assembly.jc
    Nov 13 at 5:54
















It's cleaner than my monstrosity ;) However the space then seeps into the parser. What I would like to learn how to reuse a "clean" parser in such situations. Say I have a second program that would send me the input as "123 123 123" (no ending space).
– bdecaf
Nov 11 at 9:54




It's cleaner than my monstrosity ;) However the space then seeps into the parser. What I would like to learn how to reuse a "clean" parser in such situations. Say I have a second program that would send me the input as "123 123 123" (no ending space).
– bdecaf
Nov 11 at 9:54




1




1




@bdecaf But why don't use Parsec to extract the input string firstly, say "164 151 155 145" in test3, and then use inputParser to parse it ? which can reuse most Parser except questionParser.
– assembly.jc
Nov 11 at 11:35




@bdecaf But why don't use Parsec to extract the input string firstly, say "164 151 155 145" in test3, and then use inputParser to parse it ? which can reuse most Parser except questionParser.
– assembly.jc
Nov 11 at 11:35












sounds like an idea. Need some time to wrap my head around how to do this ;)
– bdecaf
Nov 11 at 17:34




sounds like an idea. Need some time to wrap my head around how to do this ;)
– bdecaf
Nov 11 at 17:34












@bdecaf But the extract first approach need to parse same string twice. If need to parse a long string read from file, it is inefficient. I still look for a better way using Parsec to solve this type of problem. Maybe, in general, break string into tokens firstly is elegant approach, but too complex to your case.
– assembly.jc
Nov 13 at 5:54




@bdecaf But the extract first approach need to parse same string twice. If need to parse a long string read from file, it is inefficient. I still look for a better way using Parsec to solve this type of problem. Maybe, in general, break string into tokens firstly is elegant approach, but too complex to your case.
– assembly.jc
Nov 13 at 5:54


















draft saved

draft discarded




















































Thanks for contributing an answer to Stack Overflow!


  • Please be sure to answer the question. Provide details and share your research!

But avoid



  • Asking for help, clarification, or responding to other answers.

  • Making statements based on opinion; back them up with references or personal experience.


To learn more, see our tips on writing great answers.





Some of your past answers have not been well-received, and you're in danger of being blocked from answering.


Please pay close attention to the following guidance:


  • Please be sure to answer the question. Provide details and share your research!

But avoid



  • Asking for help, clarification, or responding to other answers.

  • Making statements based on opinion; back them up with references or personal experience.


To learn more, see our tips on writing great answers.




draft saved


draft discarded














StackExchange.ready(
function () {
StackExchange.openid.initPostLogin('.new-post-login', 'https%3a%2f%2fstackoverflow.com%2fquestions%2f53236949%2fparsing-string-with-parsec-that-needs-to-end-with-particular-words%23new-answer', 'question_page');
}
);

Post as a guest















Required, but never shown





















































Required, but never shown














Required, but never shown












Required, but never shown







Required, but never shown

































Required, but never shown














Required, but never shown












Required, but never shown







Required, but never shown







Popular posts from this blog

Schultheiß

Liste der Kulturdenkmale in Wilsdruff

Android Play Services Check