[Haskell-beginners] Problems with parsing in attoparsec
Michel Kuhlmann
michel at kuhlmanns.info
Tue Apr 9 08:00:55 CEST 2013
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
More information about the Beginners
mailing list