attoparsec-isotropic: right-to-left parser backward compatible with attoparsec

[ bsd3, library, parsing, text ] [ Propose Tags ] [ Report a vulnerability ]

A fork of attoparsec library allows to define omnidirected parsers or parsers consuming input from right-to-left. The library is highly backward compabitle with original interface. Idea to do the fork is inspired by the need to parse a CSV file in robin-hood-profit in one go with “constant” memory footprint and rows in reverse chronological order.

Example

{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE TupleSections #-}
import Data.Attoparsec.ByteString

test = parseOnly ab "ab" == parseBackOnly ba "ab"
  where
    ab = (,) <$> string "a" <*> string "b"
    ba = (,) <$> string "b" <*> string "a"

test2 = parseOnly ab "ab" == parseBackOnly ab "ba"
  where
    ab = string "a" >*< string "b"

Running parser in reverse incrementally

Snippet from the CSV parser app:

consumeFile :: Handle -> (RobinRow -> ProfitM ()) -> ProfitM ()
consumeFile h handleRow = do
  input <- readBlock h
  go Nothing input
  where
    go !loopDetector input = do
      iBlock <- gets (^. #currentBlock)
      if iBlock < 0 && input == mempty
        then pure ()
        else do
          parseBackWith (readBlock h) parseRow input >>= \case
            Fail _unconsumed ctx er -> do
              erpos <- liftIO $ hTell h
              fail $ "Failed to parse CSV file around " <> show erpos <> " byte; due: "
                <> show er <> "; context: " <> show ctx
            Partial _ -> fail "CSV file is partial"
            Done (unconsumed :: ByteString) (rawRow :: [ByteString]) -> do
              iBlock' <- gets (^. #currentBlock)
              if loopDetector == Just (unconsumed, iBlock')
                then
                  fail $ "Loop detected. Unconsumed input: " <> show unconsumed
                else do
                  trashCodes <- asks (^. #codesToSkip)
                  case parseRobinRow trashCodes rawRow of
                    Left e -> fail e
                    Right row -> do
                      forM_ row handleRow
                      go (Just (unconsumed, iBlock')) unconsumed

[Skip to Readme]

library attoparsec-isotropic

library attoparsec-isotropic:attoparsec-isotropic-internal

Modules

[Index] [Quick Jump]

  • Data
    • Attoparsec
      • ByteString
        • Data.Attoparsec.ByteString.Buffer
        • Data.Attoparsec.ByteString.FastSet
      • Internal
        • Data.Attoparsec.Internal.Compat
        • Data.Attoparsec.Internal.Fhthagn
      • Text
        • Data.Attoparsec.Text.Buffer
        • Data.Attoparsec.Text.FastSet

Flags

Manual Flags

NameDescriptionDefault
developer

Whether to build the library in development mode

Disabled

Use -f <flag> to enable a flag, or -f -<flag> to disable that flag. More info

Downloads

Maintainer's Corner

Package maintainers

For package maintainers and hackage trustees

Candidates

  • No Candidates
Versions [RSS] 0.14.4
Change log changelog.md
Dependencies array (<0.6), attoparsec-isotropic, base (>=4.5 && <5), bytestring (<0.13), containers (<0.9), deepseq (<1.8), fail (>=4.9 && <4.10), ghc-prim (<0.14), haddock-use-refs (<2.0), scientific (>=0.3.1 && <0.4), semigroups (>=0.16.1 && <0.21), tagged (<0.9), text (<3.0), trace-embrace (<2.0.2), transformers (>=0.2 && <0.4 || >=0.4.1.0 && <0.7) [details]
Tested with ghc ==9.10.1
License BSD-3-Clause
Author Daniil Iaitskov <dyaitskov@gmail.com>
Maintainer Daniil Iaitskov <dyaitskov@gmail.com>
Category Text, Parsing
Home page https://github.com/yaitskov/attoparsec-isotropic
Bug tracker https://github.com/yaitskov/attoparsec-isotropic/issues
Source repo head: git clone https://github.com/yaitskov/attoparsec-isotropic.git
Uploaded by DaniilIaitskov at 2025-05-30T02:06:38Z
Distributions
Downloads 3 total (3 in the last 30 days)
Rating (no votes yet) [estimated by Bayesian average]
Your Rating
  • λ
  • λ
  • λ
Status Docs uploaded by user
Build status unknown [no reports yet]

Readme for attoparsec-isotropic-0.14.4

[back to package description]

Welcome to attoparsec-isotropic

A fork of attoparsec library allows to define omnidirected parsers or parsers consuming input from right-to-left. The library is highly backward compabitle with original interface. Idea to do the fork is inspired by the need to parse a CSV file in robin-hood-profit in one go with "constant" memory footprint and rows in reverse chronological order.

Example

{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE TupleSections #-}
import Data.Attoparsec.ByteString

test = parseOnly ab "ab" == parseBackOnly ba "ab"
  where
    ab = (,) <$> string "a" <*> string "b"
    ba = (,) <$> string "b" <*> string "a"

test2 = parseOnly ab "ab" == parseBackOnly ab "ba"
  where
    ab = string "a" >*< string "b"

Running parser in reverse incrementally

Snippet from the CSV parser app:

consumeFile :: Handle -> (RobinRow -> ProfitM ()) -> ProfitM ()
consumeFile h handleRow = do
  input <- readBlock h
  go Nothing input
  where
    go !loopDetector input = do
      iBlock <- gets (^. #currentBlock)
      if iBlock < 0 && input == mempty
        then pure ()
        else do
          parseBackWith (readBlock h) parseRow input >>= \case
            Fail _unconsumed ctx er -> do
              erpos <- liftIO $ hTell h
              fail $ "Failed to parse CSV file around " <> show erpos <> " byte; due: "
                <> show er <> "; context: " <> show ctx
            Partial _ -> fail "CSV file is partial"
            Done (unconsumed :: ByteString) (rawRow :: [ByteString]) -> do
              iBlock' <- gets (^. #currentBlock)
              if loopDetector == Just (unconsumed, iBlock')
                then
                  fail $ "Loop detected. Unconsumed input: " <> show unconsumed
                else do
                  trashCodes <- asks (^. #codesToSkip)
                  case parseRobinRow trashCodes rawRow of
                    Left e -> fail e
                    Right row -> do
                      forM_ row handleRow
                      go (Just (unconsumed, iBlock')) unconsumed