[Haskell-beginners] Problems with parsing in attoparsec
mukesh tiwari
mukeshtiwari.iiitm at gmail.com
Tue Apr 9 16:02:11 CEST 2013
Hi Michel
I think you are reading empty string inside index function. I figured out
little bit and some where you are reading empty string but could not
concentrate enough ( or expert enough :) ) to see more because you are
parsing you code based on counting the number of characters ( take 6 inside
index function ).
*Main> read ""::Int
*** Exception: Prelude.read: no parse
Except the first test case, I changed the space between 0 and 2 ( for last
test case, I reduced the space between 0 and 4 ) to seven and now it's not
parsing completely but there is no error.
I have posted the code on ideone[1]. Here is the output on my system. I
have also attached the code.
*Main> :load "/Users/mukeshtiwari/Programming/Haskell/ParsingAtto.hs"
[1 of 1] Compiling Main (
/Users/mukeshtiwari/Programming/Haskell/ParsingAtto.hs, interpreted )
Ok, modules loaded: Main.
*Main> test1
Done "\n" [(1,IndexedFaceTriangle 10 1 9),(2,IndexedFaceTriangle 1 2 9)]
*Main> test2
Done " 12 8 1 0\n" [[(1,IndexedFaceTriangle 10 1
9),(2,IndexedFaceTriangle 1 2 9),(11,IndexedFaceQuad 9 2 0 4)]]
*Main> test3
Done " 12 8 1 0\n" [[(1,IndexedFaceTriangle 10 1
9),(2,IndexedFaceTriangle 1 2 9),(11,IndexedFaceQuad 9 2 0 4)]]
*Main> test4
Done " 12 8 1 0\n" [[(1,IndexedFaceTriangle 10 1
9),(2,IndexedFaceTriangle 1 2 9),(11,IndexedFaceQuad 9 2 0 4)]]
*Main> test5
Done " 12 8 1 0\n" [[(1,IndexedFaceTriangle 10 1
9),(2,IndexedFaceTriangle 1 2 9),(11,IndexedFaceQuad 9 2 0 4)]]
[1] http://ideone.com/x75C3j
Mukesh Tiwari
On Tue, Apr 9, 2013 at 11:30 AM, Michel Kuhlmann <michel at kuhlmanns.info>wrote:
> Hi,
> I couldn't figure out, why I'm failing with attoparsec.
> I have the follwing code (https://github.com/michelk/devsurf/tree/readNet)
>
> import Data.Attoparsec.Text
> import qualified Data.Text as T
> import Language.DevSurf.Readers.SpringNet
> import Prelude hiding (takeWhile, take)
>
> data IndexedFace
> = IndexedFaceTriangle Int Int Int
> | IndexedFaceQuad Int Int Int Int
> deriving (Show)
>
> -- | block of faces-lines
> faces :: Parser [[(Int, IndexedFace)]]
> faces = faceLine `sepBy` endOfLine
>
> -- | Line containing up to two indexed faces
> faceLine :: Parser [(Int, IndexedFace)]
> faceLine = face `sepBy` (take 6)
>
> -- | single indexed-face
> face :: Parser (Int, IndexedFace)
> face = do
> i <- index
> v1 <- index
> v2 <- index
> v3 <- index
> v4 <- index
> case v4 of
> 0 -> return (i, IndexedFaceTriangle v1 v2 v3)
> _ -> return (i, IndexedFaceQuad v1 v2 v3 v4)
>
> -- | node or face index 6 wide
> index :: Parser Int
> index = do
> i <- take 6
> return . read . T.unpack $ i
>
> When testing, the follwing is working:
>
> testEleL2 = do
> let ele = T.pack " 1 10 1 9 0 2
> 1 2 9 0\n"
> r = parse faceLine ele
> case r of
> Partial _ -> print $ feed r (T.pack "")
> _ -> print r
>
> testEles = do
> let eles = T.pack $ concat [" 1 10 1 9 0
> 2 1 2 9 0\n"
> --," 3 11 9 2 0\n"
> ," 4 12 8 1 0\n"
> ]
> r = parse faces eles
> case r of
> Partial _ -> print $ feed r (T.pack "")
> _ -> print r
>
> testEles = do
> let eles = T.pack $ concat [" 1 10 1 9 0
> 2 1 2 9 0\n"
> ," 3 11 9 2 0\n"
> --," 4 12 8 1 0\n"
> ]
> r = parse faces eles
> case r of
> Partial _ -> print $ feed r (T.pack "")
> _ -> print r
>
> But this is not working
>
> testEles = do
> let eles = T.pack $ concat [" 1 10 1 9 0
> 2 1 2 9 0\n"
> ," 3 11 9 2 0\n"
> ," 4 12 8 1 0\n"
> ]
> r = parse faces eles
> case r of
> Partial _ -> print $ feed r (T.pack "")
> _ -> print r
>
>
> testEles = do
> let eles = T.pack $ concat [" 1 10 1 9 0
> 2 1 2 9 0\n"
> ," 3 11 9 2 0
> 4 12 8 1 0\n"
> ]
> r = parse faces eles
> case r of
> Partial _ -> print $ feed r (T.pack "")
> _ -> print r
>
> Please help.
> Thanks, Michel
>
> _______________________________________________
> Beginners mailing list
> Beginners at haskell.org
> http://www.haskell.org/mailman/listinfo/beginners
>
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://www.haskell.org/pipermail/beginners/attachments/20130409/90cdef56/attachment.htm>
-------------- next part --------------
A non-text attachment was scrubbed...
Name: ParsingAtto.hs
Type: application/octet-stream
Size: 2773 bytes
Desc: not available
URL: <http://www.haskell.org/pipermail/beginners/attachments/20130409/90cdef56/attachment.obj>
More information about the Beginners
mailing list