attoparsec-isotropic: right-to-left parser backward compatible with attoparsec
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
Modules
[Index] [Quick Jump]
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
- ByteString
- Attoparsec
Flags
Manual Flags
| Name | Description | Default |
|---|---|---|
| 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
- attoparsec-isotropic-0.14.6.tar.gz [browse] (Cabal source package)
- Package description (as included in the package)
Maintainer's Corner
For package maintainers and hackage trustees
Candidates
- No Candidates
| Versions [RSS] | 0.14.4, 0.14.5, 0.14.6 |
|---|---|
| Change log | changelog.md |
| Dependencies | array (<1), attoparsec-isotropic, base (<5), bytestring (<1), containers (<1), deepseq (<2), fail (<5), ghc-prim (<0.14), haddock-use-refs (<2), scientific (<1), semigroups (<0.21), tagged (<1), text (<3), trace-embrace (>=1.2 && <3), transformers (<1) [details] |
| Tested with | ghc ==9.10.1, ghc ==9.12.2 |
| 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-09-18T18:30:47Z |
| Distributions | |
| Reverse Dependencies | 1 direct, 0 indirect [details] |
| Downloads | 28 total (6 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] |