<html>
  <head>
    <meta content="text/html; charset=ISO-8859-1"
      http-equiv="Content-Type">
  </head>
  <body bgcolor="#FFFFFF" text="#000000">
    <div class="moz-cite-prefix">David,<br>
      <br>
      Many thanks! Yes I had the infinite loop to0.<br>
      <br>
      Regards<br>
         Roland<br>
      <br>
      Am 21.06.2014 15:33, schrieb David McBride:<br>
    </div>
    <blockquote
cite="mid:CAN+Tr43YNs3NwMTr_gDL9w5-gOM3JvvJM6RO7KQby0AsmTn9hw@mail.gmail.com"
      type="cite">
      <div dir="ltr">
        <div>
          <div>
            <div>You have a couple problems here.<br>
              <br>
              P.many1 $ pNumber <* (string "END") ... which is the
              same as ... P.many1 (pNumber <* string "END")<br>
              <br>
            </div>
            In other words it matches 111 END 222 END 333 END.  Try
            this:<br>
            <br>
            ns <- (P.many1 pNumber) <* string "END"<br>
            <br>
          </div>
          This almost works, but when you actually run it you'll get an
          infinite loop.  The reason is because pNumber if it doesn't
          find a match it will never actually fail, therefore many1 will
          continue using it forever attempting to find a match that will
          never occur.  The reason why it never fails is that it is
          composed of combinators that never fail, pSkipSpaces and
          itself are both composed entirely of takeWhiles, which if they
          don't find a match they just continue on without doing
          anything.  If you make a small change though: <br>
          <br>
          term <- P.takeWhile1 (\c -> c >= 0x31 && c
          <= 0x39)<br>
          <br>
        </div>
        then it works fine.<br>
        <div><br>
          <div>
            <div><br>
            </div>
          </div>
        </div>
      </div>
      <div class="gmail_extra"><br>
        <br>
        <div class="gmail_quote">On Sat, Jun 21, 2014 at 8:47 AM, Roland
          Senn <span dir="ltr"><<a moz-do-not-send="true"
              href="mailto:rsx@bluewin.ch" target="_blank">rsx@bluewin.ch</a>></span>
          wrote:<br>
          <blockquote class="gmail_quote" style="margin:0 0 0
            .8ex;border-left:1px #ccc solid;padding-left:1ex">I'm trying
            to do a first very simple example with attoparsec.<br>
            <br>
            The file "test.txt" contains the line:<br>
            <br>
            START 111 2222 333 END<br>
            <br>
            The following code works and gives the result: Done "\n"
            ["111","2222","333"]<br>
            <br>
            {-# LANGUAGE OverloadedStrings #-}<br>
            import qualified Data.ByteString as BS<br>
            import Control.Applicative<br>
            import Data.Attoparsec.ByteString as P<br>
            main :: IO()<br>
            main = do<br>
                bs <- BS.readFile "test.txt"<br>
                parseTest pTest bs<br>
            pTest :: Parser [BS.ByteString]<br>
            pTest = do<br>
                string "START"<br>
                n1 <- pNumber<br>
                n2 <- pNumber<br>
                n3 <- pNumber<br>
                string "END"<br>
                return [n1, n2, n3]<br>
            pNumber :: Parser BS.ByteString<br>
            pNumber = do<br>
                pSkipSpaces<br>
                term <- P.takeWhile (\c -> c >= 0x31 &&
            c <= 0x39)<br>
                pSkipSpaces<br>
                return term<br>
            pSkipSpaces :: Parser ()<br>
            pSkipSpaces = do<br>
                P.takeWhile (\c -> c == 0x20)<br>
                return ()<br>
            <br>
            Unfortunately I must have exactly three numbers between
            START and END. To make this more flexible, I changed pTest:<br>
            <br>
            pTest :: Parser [BS.ByteString]<br>
            pTest = do<br>
                string "START"<br>
                ns <- P.many1 $ pNumber <* (string "END")<br>
                return ns<br>
            <br>
            Now the program fails with: Fail "2222 333 END\n" [] "Failed
            reading: takeWith"<br>
            Why ??<br>
            <br>
            Many thanks for your help!<br>
            <br>
            _______________________________________________<br>
            Beginners mailing list<br>
            <a moz-do-not-send="true"
              href="mailto:Beginners@haskell.org">Beginners@haskell.org</a><br>
            <a moz-do-not-send="true"
              href="http://www.haskell.org/mailman/listinfo/beginners"
              target="_blank">http://www.haskell.org/mailman/listinfo/beginners</a><br>
            <br>
          </blockquote>
        </div>
        <br>
      </div>
      <br>
      <fieldset class="mimeAttachmentHeader"></fieldset>
      <br>
      <pre wrap="">_______________________________________________
Beginners mailing list
<a class="moz-txt-link-abbreviated" href="mailto:Beginners@haskell.org">Beginners@haskell.org</a>
<a class="moz-txt-link-freetext" href="http://www.haskell.org/mailman/listinfo/beginners">http://www.haskell.org/mailman/listinfo/beginners</a>
</pre>
    </blockquote>
    <br>
  </body>
</html>