looksee-0.6.0: A simple text parser with decent errors
Safe HaskellSafe-Inferred
LanguageGHC2021

Looksee

Description

A simple text parser with decent errors

Synopsis

Documentation

data Span a Source #

A generic span, used for tracking ranges of offsets or (line, col)

Constructors

Span 

Fields

Instances

Instances details
Foldable Span Source # 
Instance details

Defined in Looksee

Methods

fold :: Monoid m => Span m -> m #

foldMap :: Monoid m => (a -> m) -> Span a -> m #

foldMap' :: Monoid m => (a -> m) -> Span a -> m #

foldr :: (a -> b -> b) -> b -> Span a -> b #

foldr' :: (a -> b -> b) -> b -> Span a -> b #

foldl :: (b -> a -> b) -> b -> Span a -> b #

foldl' :: (b -> a -> b) -> b -> Span a -> b #

foldr1 :: (a -> a -> a) -> Span a -> a #

foldl1 :: (a -> a -> a) -> Span a -> a #

toList :: Span a -> [a] #

null :: Span a -> Bool #

length :: Span a -> Int #

elem :: Eq a => a -> Span a -> Bool #

maximum :: Ord a => Span a -> a #

minimum :: Ord a => Span a -> a #

sum :: Num a => Span a -> a #

product :: Num a => Span a -> a #

Traversable Span Source # 
Instance details

Defined in Looksee

Methods

traverse :: Applicative f => (a -> f b) -> Span a -> f (Span b) #

sequenceA :: Applicative f => Span (f a) -> f (Span a) #

mapM :: Monad m => (a -> m b) -> Span a -> m (Span b) #

sequence :: Monad m => Span (m a) -> m (Span a) #

Functor Span Source # 
Instance details

Defined in Looksee

Methods

fmap :: (a -> b) -> Span a -> Span b #

(<$) :: a -> Span b -> Span a #

Show a => Show (Span a) Source # 
Instance details

Defined in Looksee

Methods

showsPrec :: Int -> Span a -> ShowS #

show :: Span a -> String #

showList :: [Span a] -> ShowS #

Eq a => Eq (Span a) Source # 
Instance details

Defined in Looksee

Methods

(==) :: Span a -> Span a -> Bool #

(/=) :: Span a -> Span a -> Bool #

Ord a => Ord (Span a) Source # 
Instance details

Defined in Looksee

Methods

compare :: Span a -> Span a -> Ordering #

(<) :: Span a -> Span a -> Bool #

(<=) :: Span a -> Span a -> Bool #

(>) :: Span a -> Span a -> Bool #

(>=) :: Span a -> Span a -> Bool #

max :: Span a -> Span a -> Span a #

min :: Span a -> Span a -> Span a #

type LineColLookup = Vector (Int, Int) Source #

Auxiliary data structure to translate offsets to (line, col)

calculateLineCol :: Text -> LineColLookup Source #

Construct an offset lookup from a document

lookupLineCol :: Int -> LineColLookup -> (Int, Int) Source #

Returns 0-based (line, col) for the given offset. Clamps to the valid range of offsets, returning (0, 0) for empty text. Note that the valid range is from before the first character to before the last, so a 3 character string has three valid offsets (0, 1, and 2).

newtype Label Source #

A parser label (for error reporting)

Constructors

Label 

Fields

Instances

Instances details
IsString Label Source # 
Instance details

Defined in Looksee

Methods

fromString :: String -> Label #

Show Label Source # 
Instance details

Defined in Looksee

Methods

showsPrec :: Int -> Label -> ShowS #

show :: Label -> String #

showList :: [Label] -> ShowS #

Eq Label Source # 
Instance details

Defined in Looksee

Methods

(==) :: Label -> Label -> Bool #

(/=) :: Label -> Label -> Bool #

Ord Label Source # 
Instance details

Defined in Looksee

Methods

compare :: Label -> Label -> Ordering #

(<) :: Label -> Label -> Bool #

(<=) :: Label -> Label -> Bool #

(>) :: Label -> Label -> Bool #

(>=) :: Label -> Label -> Bool #

max :: Label -> Label -> Label #

min :: Label -> Label -> Label #

textSpan :: Text -> Span Int Source #

Create a span from the given text

data Reason e r Source #

Reason for parse failure

Instances

Instances details
Bifoldable Reason Source # 
Instance details

Defined in Looksee

Methods

bifold :: Monoid m => Reason m m -> m #

bifoldMap :: Monoid m => (a -> m) -> (b -> m) -> Reason a b -> m #

bifoldr :: (a -> c -> c) -> (b -> c -> c) -> c -> Reason a b -> c #

bifoldl :: (c -> a -> c) -> (c -> b -> c) -> c -> Reason a b -> c #

Bifunctor Reason Source # 
Instance details

Defined in Looksee

Methods

bimap :: (a -> b) -> (c -> d) -> Reason a c -> Reason b d #

first :: (a -> b) -> Reason a c -> Reason b c #

second :: (b -> c) -> Reason a b -> Reason a c #

Bitraversable Reason Source # 
Instance details

Defined in Looksee

Methods

bitraverse :: Applicative f => (a -> f c) -> (b -> f d) -> Reason a b -> f (Reason c d) #

Foldable (Reason e) Source # 
Instance details

Defined in Looksee

Methods

fold :: Monoid m => Reason e m -> m #

foldMap :: Monoid m => (a -> m) -> Reason e a -> m #

foldMap' :: Monoid m => (a -> m) -> Reason e a -> m #

foldr :: (a -> b -> b) -> b -> Reason e a -> b #

foldr' :: (a -> b -> b) -> b -> Reason e a -> b #

foldl :: (b -> a -> b) -> b -> Reason e a -> b #

foldl' :: (b -> a -> b) -> b -> Reason e a -> b #

foldr1 :: (a -> a -> a) -> Reason e a -> a #

foldl1 :: (a -> a -> a) -> Reason e a -> a #

toList :: Reason e a -> [a] #

null :: Reason e a -> Bool #

length :: Reason e a -> Int #

elem :: Eq a => a -> Reason e a -> Bool #

maximum :: Ord a => Reason e a -> a #

minimum :: Ord a => Reason e a -> a #

sum :: Num a => Reason e a -> a #

product :: Num a => Reason e a -> a #

Traversable (Reason e) Source # 
Instance details

Defined in Looksee

Methods

traverse :: Applicative f => (a -> f b) -> Reason e a -> f (Reason e b) #

sequenceA :: Applicative f => Reason e (f a) -> f (Reason e a) #

mapM :: Monad m => (a -> m b) -> Reason e a -> m (Reason e b) #

sequence :: Monad m => Reason e (m a) -> m (Reason e a) #

Functor (Reason e) Source # 
Instance details

Defined in Looksee

Methods

fmap :: (a -> b) -> Reason e a -> Reason e b #

(<$) :: a -> Reason e b -> Reason e a #

(Show e, Show r) => Show (Reason e r) Source # 
Instance details

Defined in Looksee

Methods

showsPrec :: Int -> Reason e r -> ShowS #

show :: Reason e r -> String #

showList :: [Reason e r] -> ShowS #

(Eq e, Eq r) => Eq (Reason e r) Source # 
Instance details

Defined in Looksee

Methods

(==) :: Reason e r -> Reason e r -> Bool #

(/=) :: Reason e r -> Reason e r -> Bool #

(Ord e, Ord r) => Ord (Reason e r) Source # 
Instance details

Defined in Looksee

Methods

compare :: Reason e r -> Reason e r -> Ordering #

(<) :: Reason e r -> Reason e r -> Bool #

(<=) :: Reason e r -> Reason e r -> Bool #

(>) :: Reason e r -> Reason e r -> Bool #

(>=) :: Reason e r -> Reason e r -> Bool #

max :: Reason e r -> Reason e r -> Reason e r #

min :: Reason e r -> Reason e r -> Reason e r #

data ErrF e r Source #

Base functor for Err containing the range and reason for the error

Constructors

ErrF 

Fields

Instances

Instances details
Bifoldable ErrF Source # 
Instance details

Defined in Looksee

Methods

bifold :: Monoid m => ErrF m m -> m #

bifoldMap :: Monoid m => (a -> m) -> (b -> m) -> ErrF a b -> m #

bifoldr :: (a -> c -> c) -> (b -> c -> c) -> c -> ErrF a b -> c #

bifoldl :: (c -> a -> c) -> (c -> b -> c) -> c -> ErrF a b -> c #

Bifunctor ErrF Source # 
Instance details

Defined in Looksee

Methods

bimap :: (a -> b) -> (c -> d) -> ErrF a c -> ErrF b d #

first :: (a -> b) -> ErrF a c -> ErrF b c #

second :: (b -> c) -> ErrF a b -> ErrF a c #

Bitraversable ErrF Source # 
Instance details

Defined in Looksee

Methods

bitraverse :: Applicative f => (a -> f c) -> (b -> f d) -> ErrF a b -> f (ErrF c d) #

Foldable (ErrF e) Source # 
Instance details

Defined in Looksee

Methods

fold :: Monoid m => ErrF e m -> m #

foldMap :: Monoid m => (a -> m) -> ErrF e a -> m #

foldMap' :: Monoid m => (a -> m) -> ErrF e a -> m #

foldr :: (a -> b -> b) -> b -> ErrF e a -> b #

foldr' :: (a -> b -> b) -> b -> ErrF e a -> b #

foldl :: (b -> a -> b) -> b -> ErrF e a -> b #

foldl' :: (b -> a -> b) -> b -> ErrF e a -> b #

foldr1 :: (a -> a -> a) -> ErrF e a -> a #

foldl1 :: (a -> a -> a) -> ErrF e a -> a #

toList :: ErrF e a -> [a] #

null :: ErrF e a -> Bool #

length :: ErrF e a -> Int #

elem :: Eq a => a -> ErrF e a -> Bool #

maximum :: Ord a => ErrF e a -> a #

minimum :: Ord a => ErrF e a -> a #

sum :: Num a => ErrF e a -> a #

product :: Num a => ErrF e a -> a #

Traversable (ErrF e) Source # 
Instance details

Defined in Looksee

Methods

traverse :: Applicative f => (a -> f b) -> ErrF e a -> f (ErrF e b) #

sequenceA :: Applicative f => ErrF e (f a) -> f (ErrF e a) #

mapM :: Monad m => (a -> m b) -> ErrF e a -> m (ErrF e b) #

sequence :: Monad m => ErrF e (m a) -> m (ErrF e a) #

Functor (ErrF e) Source # 
Instance details

Defined in Looksee

Methods

fmap :: (a -> b) -> ErrF e a -> ErrF e b #

(<$) :: a -> ErrF e b -> ErrF e a #

(Show e, Show r) => Show (ErrF e r) Source # 
Instance details

Defined in Looksee

Methods

showsPrec :: Int -> ErrF e r -> ShowS #

show :: ErrF e r -> String #

showList :: [ErrF e r] -> ShowS #

(Eq e, Eq r) => Eq (ErrF e r) Source # 
Instance details

Defined in Looksee

Methods

(==) :: ErrF e r -> ErrF e r -> Bool #

(/=) :: ErrF e r -> ErrF e r -> Bool #

(Ord e, Ord r) => Ord (ErrF e r) Source # 
Instance details

Defined in Looksee

Methods

compare :: ErrF e r -> ErrF e r -> Ordering #

(<) :: ErrF e r -> ErrF e r -> Bool #

(<=) :: ErrF e r -> ErrF e r -> Bool #

(>) :: ErrF e r -> ErrF e r -> Bool #

(>=) :: ErrF e r -> ErrF e r -> Bool #

max :: ErrF e r -> ErrF e r -> ErrF e r #

min :: ErrF e r -> ErrF e r -> ErrF e r #

newtype Err e Source #

A parse error, which may contain multiple sub-errors

Constructors

Err 

Fields

Instances

Instances details
Foldable Err Source # 
Instance details

Defined in Looksee

Methods

fold :: Monoid m => Err m -> m #

foldMap :: Monoid m => (a -> m) -> Err a -> m #

foldMap' :: Monoid m => (a -> m) -> Err a -> m #

foldr :: (a -> b -> b) -> b -> Err a -> b #

foldr' :: (a -> b -> b) -> b -> Err a -> b #

foldl :: (b -> a -> b) -> b -> Err a -> b #

foldl' :: (b -> a -> b) -> b -> Err a -> b #

foldr1 :: (a -> a -> a) -> Err a -> a #

foldl1 :: (a -> a -> a) -> Err a -> a #

toList :: Err a -> [a] #

null :: Err a -> Bool #

length :: Err a -> Int #

elem :: Eq a => a -> Err a -> Bool #

maximum :: Ord a => Err a -> a #

minimum :: Ord a => Err a -> a #

sum :: Num a => Err a -> a #

product :: Num a => Err a -> a #

Traversable Err Source # 
Instance details

Defined in Looksee

Methods

traverse :: Applicative f => (a -> f b) -> Err a -> f (Err b) #

sequenceA :: Applicative f => Err (f a) -> f (Err a) #

mapM :: Monad m => (a -> m b) -> Err a -> m (Err b) #

sequence :: Monad m => Err (m a) -> m (Err a) #

Functor Err Source # 
Instance details

Defined in Looksee

Methods

fmap :: (a -> b) -> Err a -> Err b #

(<$) :: a -> Err b -> Err a #

(Typeable e, Show e) => Exception (Err e) Source # 
Instance details

Defined in Looksee

Show e => Show (Err e) Source # 
Instance details

Defined in Looksee

Methods

showsPrec :: Int -> Err e -> ShowS #

show :: Err e -> String #

showList :: [Err e] -> ShowS #

Eq e => Eq (Err e) Source # 
Instance details

Defined in Looksee

Methods

(==) :: Err e -> Err e -> Bool #

(/=) :: Err e -> Err e -> Bool #

Ord e => Ord (Err e) Source # 
Instance details

Defined in Looksee

Methods

compare :: Err e -> Err e -> Ordering #

(<) :: Err e -> Err e -> Bool #

(<=) :: Err e -> Err e -> Bool #

(>) :: Err e -> Err e -> Bool #

(>=) :: Err e -> Err e -> Bool #

max :: Err e -> Err e -> Err e #

min :: Err e -> Err e -> Err e #

HasErrMessage e => HasErrMessage (Err e) Source # 
Instance details

Defined in Looksee

Methods

getErrMessage :: (Int -> Text) -> Err e -> [Text] Source #

Corecursive (Err e) Source # 
Instance details

Defined in Looksee

Methods

embed :: Base (Err e) (Err e) -> Err e #

ana :: (a -> Base (Err e) a) -> a -> Err e #

apo :: (a -> Base (Err e) (Either (Err e) a)) -> a -> Err e #

postpro :: Recursive (Err e) => (forall b. Base (Err e) b -> Base (Err e) b) -> (a -> Base (Err e) a) -> a -> Err e #

gpostpro :: (Recursive (Err e), Monad m) => (forall b. m (Base (Err e) b) -> Base (Err e) (m b)) -> (forall c. Base (Err e) c -> Base (Err e) c) -> (a -> Base (Err e) (m a)) -> a -> Err e #

Recursive (Err e) Source # 
Instance details

Defined in Looksee

Methods

project :: Err e -> Base (Err e) (Err e) #

cata :: (Base (Err e) a -> a) -> Err e -> a #

para :: (Base (Err e) (Err e, a) -> a) -> Err e -> a #

gpara :: (Corecursive (Err e), Comonad w) => (forall b. Base (Err e) (w b) -> w (Base (Err e) b)) -> (Base (Err e) (EnvT (Err e) w a) -> a) -> Err e -> a #

prepro :: Corecursive (Err e) => (forall b. Base (Err e) b -> Base (Err e) b) -> (Base (Err e) a -> a) -> Err e -> a #

gprepro :: (Corecursive (Err e), Comonad w) => (forall b. Base (Err e) (w b) -> w (Base (Err e) b)) -> (forall c. Base (Err e) c -> Base (Err e) c) -> (Base (Err e) (w a) -> a) -> Err e -> a #

type Base (Err e) Source # 
Instance details

Defined in Looksee

type Base (Err e) = ErrF e

errSpan :: Err e -> Span Int Source #

Span of a parse error

errReason :: Err e -> Reason e (Err e) Source #

Reason for a parse error

data AltPhase Source #

Phase of alternative parsing (for error reporting)

Instances

Instances details
Bounded AltPhase Source # 
Instance details

Defined in Looksee

Enum AltPhase Source # 
Instance details

Defined in Looksee

Show AltPhase Source # 
Instance details

Defined in Looksee

Eq AltPhase Source # 
Instance details

Defined in Looksee

Ord AltPhase Source # 
Instance details

Defined in Looksee

data ParserT e m a Source #

The parser monad transformer

Instances

Instances details
MonadReader r m => MonadReader r (ParserT e m) Source # 
Instance details

Defined in Looksee

Methods

ask :: ParserT e m r #

local :: (r -> r) -> ParserT e m a -> ParserT e m a #

reader :: (r -> a) -> ParserT e m a #

MonadState s m => MonadState s (ParserT e m) Source # 
Instance details

Defined in Looksee

Methods

get :: ParserT e m s #

put :: s -> ParserT e m () #

state :: (s -> (a, s)) -> ParserT e m a #

MonadTrans (ParserT e) Source # 
Instance details

Defined in Looksee

Methods

lift :: Monad m => m a -> ParserT e m a #

Monad m => MonadFail (ParserT e m) Source # 
Instance details

Defined in Looksee

Methods

fail :: String -> ParserT e m a #

MonadIO m => MonadIO (ParserT e m) Source # 
Instance details

Defined in Looksee

Methods

liftIO :: IO a -> ParserT e m a #

Monad m => Alternative (ParserT e m) Source # 
Instance details

Defined in Looksee

Methods

empty :: ParserT e m a #

(<|>) :: ParserT e m a -> ParserT e m a -> ParserT e m a #

some :: ParserT e m a -> ParserT e m [a] #

many :: ParserT e m a -> ParserT e m [a] #

Applicative (ParserT e m) Source # 
Instance details

Defined in Looksee

Methods

pure :: a -> ParserT e m a #

(<*>) :: ParserT e m (a -> b) -> ParserT e m a -> ParserT e m b #

liftA2 :: (a -> b -> c) -> ParserT e m a -> ParserT e m b -> ParserT e m c #

(*>) :: ParserT e m a -> ParserT e m b -> ParserT e m b #

(<*) :: ParserT e m a -> ParserT e m b -> ParserT e m a #

Functor (ParserT e m) Source # 
Instance details

Defined in Looksee

Methods

fmap :: (a -> b) -> ParserT e m a -> ParserT e m b #

(<$) :: a -> ParserT e m b -> ParserT e m a #

Monad (ParserT e m) Source # 
Instance details

Defined in Looksee

Methods

(>>=) :: ParserT e m a -> (a -> ParserT e m b) -> ParserT e m b #

(>>) :: ParserT e m a -> ParserT e m b -> ParserT e m b #

return :: a -> ParserT e m a #

Monoid a => Monoid (ParserT e m a) Source # 
Instance details

Defined in Looksee

Methods

mempty :: ParserT e m a #

mappend :: ParserT e m a -> ParserT e m a -> ParserT e m a #

mconcat :: [ParserT e m a] -> ParserT e m a #

Semigroup a => Semigroup (ParserT e m a) Source # 
Instance details

Defined in Looksee

Methods

(<>) :: ParserT e m a -> ParserT e m a -> ParserT e m a #

sconcat :: NonEmpty (ParserT e m a) -> ParserT e m a #

stimes :: Integral b => b -> ParserT e m a -> ParserT e m a #

type Parser e = ParserT e Identity Source #

The parser monad

parseT :: Monad m => ParserT e m a -> Text -> m (Either (Err e) a) Source #

Run a parser transformer. You must consume all input or this will error! If you really don't care about the rest of the input, you can always discard it with dropAllP.

parse :: Parser e a -> Text -> Either (Err e) a Source #

Run a parser (see parseT)

parseI :: HasErrMessage e => Parser e a -> Text -> IO (Either (Err e) a) Source #

Run a parser and print any errors that occur

spanP :: Monad m => ParserT e m (Span Int) Source #

Get the span (in character offset) at the current point representing the entire parseable range. At the start of parsing this will be `Span 0 n` for an n-character document. The start offset will increase as input is consumed, and the end offset will decrease as lookahead delimits the range. To evaluate the "real" range of characters consumed by a parser, construct a span with the starting offsets before and after executing a subparser (or use spanAroundP).

spanAroundP :: Monad m => (Span Int -> a -> b) -> ParserT e m a -> ParserT e m b Source #

Incorporate span information into a parsed object.

throwP :: Monad m => e -> ParserT e m a Source #

Throw a custom parse error

altP :: (Monad m, Foldable f) => f (ParserT e m a) -> ParserT e m a Source #

Parse with many possible branches

emptyP :: Monad m => ParserT e m a Source #

Fail with no results

explainP :: Monad m => (Reason e (Err e) -> Maybe (Text, Bool)) -> ParserT e m a -> ParserT e m a Source #

If things fail and you can give a good message explaining why, this combinator will annotate the error with your explanation. Returning True with message will hide the original error message in textual rendering.

endP :: Monad m => ParserT e m () Source #

Succeed if this is the end of input

optP :: Monad m => ParserT e m a -> ParserT e m (Maybe a) Source #

Makes parse success optional

lookP :: Monad m => ParserT e m a -> ParserT e m a Source #

Lookahead - rewinds state if the parser succeeds, otherwise throws error

branchP :: (Monad m, Foldable f) => f (ParserT e m (), ParserT e m a) -> ParserT e m a Source #

Branches guarded by lookahead. Use this for more concise errors. altP will happily tell you about each of the errors it encountered in every branch, but this will quietly prune non-matching branches. Tries until first success (in order), so you can tack on a fallthrough case even if you tried a branch earlier.

commitP :: (Monad m, Foldable f) => f (ParserT e m (), ParserT e m a) -> ParserT e m a Source #

An alternative to branchP that does not backtrack after committing to a branch.

labelP :: Monad m => Label -> ParserT e m a -> ParserT e m a Source #

Labels parse errors

textP :: Monad m => Text -> ParserT e m Text Source #

Expect the given text at the start of the range

textP_ :: Monad m => Text -> ParserT e m () Source #

Saves you from importing void

charP :: Monad m => Char -> ParserT e m Char Source #

Expect the given character at the start of the range

charP_ :: Monad m => Char -> ParserT e m () Source #

Saves you from importing void

breakP :: Monad m => Text -> ParserT e m a -> ParserT e m a Source #

Split once on the delimiter (first argument), parsing everything before it with a narrowed range. Chooses first split from START to END of range (see infixRP).

someBreakP :: Monad m => Text -> ParserT e m a -> ParserT e m a Source #

Split once on the delimiter (first argument), parsing everything before it with a narrowed range. Chooses splits from START to END of range (see someInfixRP).

splitP :: Monad m => Text -> ParserT e m a -> ParserT e m (Seq a) Source #

Split on the delimiter, parsing segments with a narrowed range, until parsing fails. Returns the sequence of successes with state at the delimiter preceding the failure (or end of input), Note that this will always succeed, sometimes consuming no input and yielding empty results.

split1P :: Monad m => Text -> ParserT e m a -> ParserT e m (Seq a) Source #

Like splitP but ensures the sequence is at least length 1.

split2P :: Monad m => Text -> ParserT e m a -> ParserT e m (Seq a) Source #

Like splitP but ensures the sequence is at least length 2. (This ensures there is at least one delimiter included.)

leadP :: Monad m => Text -> ParserT e m a -> ParserT e m (Seq a) Source #

Like splitP but ensures a leading delimiter

lead1P :: Monad m => Text -> ParserT e m a -> ParserT e m (Seq a) Source #

Like split1P but ensures a leading delimiter

trailP :: Monad m => Text -> ParserT e m a -> ParserT e m (Seq a) Source #

Like splitP but ensures a trailing delimiter

trail1P :: Monad m => Text -> ParserT e m a -> ParserT e m (Seq a) Source #

Like split1P but ensures a trailing delimiter

infixRP :: Monad m => Text -> ParserT e m a -> ParserT e m b -> ParserT e m (a, b) Source #

Right-associative infix parsing. Searches for the operator from START to END of range, trying only the first break point.

someInfixRP :: Monad m => Text -> ParserT e m a -> ParserT e m b -> ParserT e m (a, b) Source #

Right-associative infix parsing. Searches for the operator from START to END of range, trying subsequent break points until success.

takeP :: Monad m => Int -> ParserT e m Text Source #

Take the given number of characters from the start of the range, or fewer if empty

dropP :: Monad m => Int -> ParserT e m Int Source #

Drop the given number of characters from the start of the range, or fewer if empty

takeExactP :: Monad m => Int -> ParserT e m Text Source #

Take exactly the given number of characters from the start of the range, or error

dropExactP :: Monad m => Int -> ParserT e m () Source #

Drop exactly the given number of characters from the start of the range, or error

takeWhileP :: Monad m => (Char -> Bool) -> ParserT e m Text Source #

Take characters from the start of the range satisfying the predicate

dropWhileP :: Monad m => (Char -> Bool) -> ParserT e m Int Source #

Drop characters from the start of the range satisfying the predicate

takeWhile1P :: Monad m => (Char -> Bool) -> ParserT e m Text Source #

Like takeWhileP but ensures at least 1 character has been taken

dropWhile1P :: Monad m => (Char -> Bool) -> ParserT e m Int Source #

Like dropWhileP but ensures at least 1 character has been dropped

takeAllP :: Monad m => ParserT e m Text Source #

Take the remaining range, leaving it empty

dropAllP :: Monad m => ParserT e m Int Source #

Drop the remaining range, leaving it empty

takeAll1P :: Monad m => ParserT e m Text Source #

Like takeAllP but ensures at least 1 character has been taken

dropAll1P :: Monad m => ParserT e m Int Source #

Like dropAllP but ensures at least 1 character has been dropped

betweenP :: ParserT e m x -> ParserT e m y -> ParserT e m a -> ParserT e m a Source #

Parse between an opening delimiter (first parser) and a closing delimited (second parser)

repeatP :: Monad m => ParserT e m a -> ParserT e m (Seq a) Source #

Repeat a parser until it fails, collecting the results.

repeat1P :: Monad m => ParserT e m a -> ParserT e m (Seq a) Source #

Like repeatP but ensures at least one result.

sepByP :: Monad m => ParserT e m () -> ParserT e m a -> ParserT e m (Seq a) Source #

Parse a sequence of items delimited by the first parser

sepBy1P :: Monad m => ParserT e m () -> ParserT e m a -> ParserT e m (Seq a) Source #

Like sepByP but ensures at least one result.

sepBy2P :: Monad m => ParserT e m () -> ParserT e m a -> ParserT e m (Seq a) Source #

Like sepByP but ensures at least two results (and at least one delimiter).

spaceP :: Monad m => ParserT e m () Source #

Consumes many spaces at the start of the range

stripP :: Monad m => ParserT e m a -> ParserT e m a Source #

Strips spaces before and after parsing

stripStartP :: Monad m => ParserT e m a -> ParserT e m a Source #

Strips spaces before parsing

stripEndP :: Monad m => ParserT e m a -> ParserT e m a Source #

Strips spaces after parsing

measureP :: Monad m => ParserT e m a -> ParserT e m (a, Int) Source #

Parses and returns the length of the consumed input along with the result

unconsP :: Monad m => ParserT e m (Maybe Char) Source #

Takes exactly 1 character from the start of the range, returning Nothing if at end of input

headP :: Monad m => ParserT e m Char Source #

Takes exactly 1 character from the start of the range, throwing error if at end of input

signedWithP :: Monad m => (a -> a) -> ParserT e m a -> ParserT e m a Source #

Add signed-ness to any parser with a negate function

signedP :: (Monad m, Num a) => ParserT e m a -> ParserT e m a Source #

Add signed-ness to any numeric parser

intP :: Monad m => ParserT e m Integer Source #

Parse an signed integer

uintP :: Monad m => ParserT e m Integer Source #

Parse an unsigned integer

decP :: Monad m => ParserT e m Rational Source #

Parse a signed decimal

udecP :: Monad m => ParserT e m Rational Source #

Parse an unsigned decimal

sciP :: Monad m => ParserT e m Scientific Source #

Parse a signed scientific number

usciP :: Monad m => ParserT e m Scientific Source #

Parse an unsigned scientific number

numP :: Monad m => ParserT e m (Either Integer Scientific) Source #

Parse a signed integer/scientific number, defaulting to integer if possible.

unumP :: Monad m => ParserT e m (Either Integer Scientific) Source #

Parse an unsigned integer/scientific number, defaulting to integer if possible.

space1P :: Monad m => ParserT e m () Source #

Like spaceP but ensures at least 1 space removed

strip1P :: Monad m => ParserT e m a -> ParserT e m a Source #

Like stripP but ensures at least 1 space removed

stripStart1P :: Monad m => ParserT e m a -> ParserT e m a Source #

Like stripStartP but ensures at least 1 space removed

stripEnd1P :: Monad m => ParserT e m a -> ParserT e m a Source #

Like stripEndP but ensures at least 1 space removed

transP :: (MonadTrans t, Monad m) => (forall a. t m a -> m a) -> ParserT e (t m) b -> ParserT e m b Source #

Unwrap a monad transformer layer (see scopeP for use)

scopeP :: Monad m => s -> ParserT e (StateT s m) a -> ParserT e m a Source #

Parse with some local state

iterP :: ParserT e m (Maybe a) -> ParserT e m a Source #

Repeats the parser until it returns a Just value

strP :: Monad m => Char -> ParserT e m Text Source #

Parse a string with a custom quote character. Supports backslash-escaping.

doubleStrP :: Monad m => ParserT e m Text Source #

Parse a double-quoted string

singleStrP :: Monad m => ParserT e m Text Source #

Parse a single-quoted string

class HasErrMessage e where Source #

Implement this to format custom errors. The list will be indented and joined with unlines.

Methods

getErrMessage :: (Int -> Text) -> e -> [Text] Source #

Instances

Instances details
HasErrMessage Void Source # 
Instance details

Defined in Looksee

Methods

getErrMessage :: (Int -> Text) -> Void -> [Text] Source #

HasErrMessage e => HasErrMessage (Err e) Source # 
Instance details

Defined in Looksee

Methods

getErrMessage :: (Int -> Text) -> Err e -> [Text] Source #

errataE :: HasErrMessage e => FilePath -> (Int -> (Line, Column)) -> Err e -> [Errata] Source #

Create Errata formatting a parse error

renderE :: HasErrMessage e => FilePath -> Text -> Err e -> Text Source #

Render a formatted error to text

printE :: HasErrMessage e => FilePath -> Text -> Err e -> IO () Source #

Print a formatted error to stderr