[Haskell-cafe] parsec problem: infinite loop (possibly connected to try(lookahead ...)) but how?)

keydana at gmx.de keydana at gmx.de
Sat Mar 1 18:33:47 UTC 2014


Hi,

I want to parse a rather unstructured log file, skipping blocks I'm not interested in but keeping others. For that purpose, I define "markers" that flag the beginning of interesting chunks. The "skip parser" reads anything until such a marker (using 

manyTill parseAny (try (lookAhead parseMarker))

and then the relative content parser starts by really consuming this marker string.

I have a test case demonstrating this principle which works fine, but when I execute the (seemingly!) equivalent "real" code on a piece of a (seemingly!) equivalent "real log file", ghci enters an infinite loop - and I have no idea why...

I'd be very grateful for any help, as I'm completely stuck here ;-)

Following are:

- the test input file
- the piece of "real logfile"
- the complete code in one piece (Main.hs), with the test case code in the bottom

These are the results when I run

1) the test case:

*Main>  readFile "testfile.txt" >>= parseTest parseAll
["aaa\naaa\n","aaa\naaa\n","aaa\naaa\n"]

2) the main code (endless loop interrupted, with output from debug.trace):

parseUntilChunkWFG: ""
parseMaybeChunk: Nothing
parseWFGMarker: Global Wait-For-Graph(WFG) at ddTS[0.3] :

parseUntilChunkWFG: ""
parseMaybeChunk: Nothing
^CparseWFGMarker: Global Wait-For-Graph(WFG) at ddTS[0.3] :

parseUntilChunkWFG: ""
parseMaybeChunk: Nothing
Interrupted.


This is the test input file, with vi newline symbols:

##########################################################################
this is just some stuff$
I wanna skip$
$
this is, too$
12[] $
$
BEGIN_MARKER$
aaa$
aaa$
$
this here again I can skip$
$
BEGIN_MARKER$
aaa$
aaa$
$
and then it goes on till the end of the file$
##########################################################################


... and this is the real piece (part of, what is important I have 2 chunks of "interesting content"):


##########################################################################
  client details:$
    O/S info: user: oracle, term: pts/2, ospid: 5820$
    machine: node1.skyrac.com program: sqlplus at node1.skyrac.com (TNS V1-V3)$
    application name: sqlplus at node1.skyrac.com (TNS V1-V3), hash value=10026263$
  current SQL:$
  insert into test values(2)$
DUMP LOCAL BLOCKER: initiate state dump for DEADLOCK$
  possible owner[39.5827] on resource TX-00080011-00000545$
$
*** 2014-02-22 08:43:55.554$
Submitting asynchronized dump request [28]. summary=[ges process stack dump (kjdglblkrdm1)].$
Global blockers dump end:-----------------------------------$
Global Wait-For-Graph(WFG) at ddTS[0.3] :$
BLOCKED 0x83437238 3 wq 2 cvtops x1 TX 0xc0006.0x1c5(ext 0x4,0x0)[27000-0001-00000001] inst 1 $
BLOCKER 0x83b196a8 3 wq 1 cvtops x28 TX 0xc0006.0x1c5(ext 0x4,0x0)[36000-0002-00000005] inst 2 $
BLOCKED 0x83437238 3 wq 2 cvtops x1 TX 0x80011.0x545(ext 0x2,0x0)[36000-0002-00000005] inst 2 $
BLOCKER 0x83b35b10 3 wq 1 cvtops x28 TX 0x80011.0x545(ext 0x2,0x0)[27000-0001-00000001] inst 1 $
$
*** 2014-02-22 08:43:56.292$
* Cancel deadlock victim lockp 0x83437238 $
DUMP LOCAL BLOCKER: initiate state dump for DEADLOCK$
  possible owner[39.5827] on resource TX-00080011-00000545$
$
*** 2014-02-22 08:43:55.554$
Submitting asynchronized dump request [28]. summary=[ges process stack dump (kjdglblkrdm1)].$
Global blockers dump end:-----------------------------------$
Global Wait-For-Graph(WFG) at ddTS[0.3] :$
BLOCKED 0x83437238 3 wq 2 cvtops x1 TX 0xc0006.0x1c5(ext 0x4,0x0)[27000-0001-00000001] inst 1$
BLOCKER 0x83b196a8 3 wq 1 cvtops x28 TX 0xc0006.0x1c5(ext 0x4,0x0)[36000-0002-00000005] inst 2$
BLOCKED 0x83437238 3 wq 2 cvtops x1 TX 0x80011.0x545(ext 0x2,0x0)[36000-0002-00000005] inst 2$
BLOCKER 0x83b35b10 3 wq 1 cvtops x28 TX 0x80011.0x545(ext 0x2,0x0)[27000-0001-00000001] inst 1$
$
*** 2014-02-22 08:43:56.292$

##########################################################################


... and this is the code:


##########################################################################
module Main (
    main
) where

import System.Environment
import System.Directory
import Text.ParserCombinators.Parsec
import Debug.Trace
import Numeric
import Data.Maybe
import Data.Char

main = do
  --files <- getArgs
  currDir <- getCurrentDirectory
  --let filepaths = map ((currDir ++ "/") ++)  ["munip1_lmd0_5702.trc", "munip2_lmd0_5966.trc"]
  let filepaths = map ((currDir ++ "/") ++)  ["munip1_lmd0_5702.trc"]
  wfgs <- mapM (\p -> parseFromFile parseChunks p) filepaths
  print wfgs

parseChunks :: Parser [Chunk]
parseChunks = do
  chunks <- many1 parseMaybeChunk
  -- trace ("parseChunks: " ++ (show chunks)) return (catMaybes chunks)
  return (catMaybes chunks)
  
parseMaybeChunk :: Parser (Maybe Chunk)
parseMaybeChunk = do
  chunk <- try (parseChunkWFG >>= return . Just)
           <|> try (parseUntilChunkWFG >> return Nothing)
           <|> (parseTillEOF >> return Nothing)
  trace ("parseMaybeChunk: " ++ show chunk) return chunk
  --return chunk

parseUntilChunkWFG :: Parser [Char]
parseUntilChunkWFG = do
  skip <- manyTill parseAny (try (lookAhead parseWFGMarker) )
  trace ("parseUntilChunkWFG: " ++ show skip) return skip
  --return skip

parseAny :: Parser Char
parseAny = do
  anyC <- oneOf (['a'..'z'] ++ ['A'..'Z'] ++ ['0'..'9'] ++ "()[]* -:.,/_?@='\n\\")
  --trace ("parseAny: " ++ (show anyC)) return anyC
  return anyC

parseWFGMarker :: Parser [Char]
parseWFGMarker = do
  marker <- string "Global Wait-For-Graph(WFG) at ddTS[0.3] :\n"
  trace ("parseWFGMarker: " ++ marker) return marker
  --return marker

parseTillEOF :: Parser [Char]
parseTillEOF = do 
  anyCs <- many1 anyChar
  eof 
  --trace ("parseTillEOF: " ++ anyCs) return anyCs
  return anyCs

parseChunkWFG :: Parser Chunk
parseChunkWFG = do
  marker <- string "Global Wait-For-Graph(WFG) at ddTS[0.3] :\n"
  wfg <- manyTill parseWFGEntry newline
  --trace ("parseChunkWFG: " ++ (show wfg)) return $ ChunkWFG wfg
  return $ ChunkWFG wfg

parseWFGEntry :: Parser WFGEntry
parseWFGEntry = do
  role      <- try (string "BLOCKER") <|> string "BLOCKED"
  skipMany1 (space >> string "0x")
  lockaddr  <- many1 hexDigit
  skipMany1 (space >> (many1 digit) >> space >> string "wq" >> space >>
            (many1 digit) >> space >> string "cvtops" >> space >>
            char 'x' >> (many1 digit) >> space)
  restype   <- manyTill upper space
  skipMany1 (string "0x")
  id1       <- manyTill hexDigit (string ".0x")
  id2       <- manyTill hexDigit (string "(ext ")
  manyTill (digit <|> oneOf ")[]x,-") (string " inst ")
  instid    <- manyTill digit (space >> newline)
  let wfgEntry = WFGEntry (read role :: Role)
                          lockaddr
                          (ResourceId id1 id2 restype)
                          (read instid)
  --trace ("parseWFGEntry: " ++ show wfgEntry) return $ wfgEntry
  {- trace ("parseWFGEntry: " ++ role ++ " " ++ lockaddr ++ " " ++ restype
          ++ " " ++ id1 ++ " " ++ id2 ++ " " ++ instid)
          return $ wfgEntry
  -}
  return $ wfgEntry
  
data Chunk = ChunkWFG WFG
              deriving (Show, Read)

data ResourceId = ResourceId {
  id1       :: String,
  id2       :: String,
  restype   :: String
} deriving (Show, Read)

data WFGEntry = WFGEntry {
  role      :: Role,
  lockaddr  :: String,
  resource  :: ResourceId,
  instid    :: Int
} deriving (Show, Read)

type WFG = [WFGEntry]

data Role = BLOCKED | BLOCKER deriving (Show, Read)


------------------- testcase code ---------------------------
parseAll :: Parser [String]
parseAll = do
  chunks <- many1 parseChunk
  return (catMaybes chunks)

parseChunk :: Parser (Maybe [Char])
parseChunk = do
  chunk <- try (parseContent >>= return . Just)
           <|> try (parseUntilMarker >> return Nothing)
           <|> (parseTillEOF >> return Nothing)
  --trace ("parseChunk: " ++ show chunk) return chunk
  return chunk

parseUntilMarker :: Parser [Char]
parseUntilMarker = do
  skip <- manyTill parseAny (try (lookAhead parseMarker) )
  --trace ("parseUntilMarker: " ++ show skip) return skip
  return skip

parseMarker :: Parser [Char]
parseMarker = do
  marker <- string "BEGIN_MARKER\n"
  --trace ("parseWFGMarker: " ++ marker) return marker
  return marker

parseContent :: Parser [Char]
parseContent = do
  marker <- string "BEGIN_MARKER\n"
  items <- manyTill parseItem newline
  --trace ("parseContent: " ++ (show items)) return $ concat items
  return $ concat items
  
parseItem  :: Parser [Char]
parseItem =  string "aaa\n"
##########################################################################


Many thanks in advance for any hints what might be going on :-)!
Sigrid



-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://www.haskell.org/pipermail/haskell-cafe/attachments/20140301/347af868/attachment.html>


More information about the Haskell-Cafe mailing list