megaparsec-6.1.0: Monadic parser combinators

Copyright© 2015–2017 Megaparsec contributors
LicenseFreeBSD
MaintainerMark Karpov <markkarpov92@gmail.com>
Stabilityexperimental
Portabilityportable
Safe HaskellNone
LanguageHaskell2010

Text.Megaparsec.Stream

Description

Megaparsec's input stream facilities.

You probably do not want to import this module directly because Text.Megaparsec re-exports it anyway.

Since: 6.0.0

Synopsis

Documentation

class (Ord (Token s), Ord (Tokens s)) => Stream s where Source #

Type class for inputs that can be consumed by the library.

Associated Types

type Token s :: * Source #

Type of token in the stream.

type Tokens s :: * Source #

Type of “chunk” of the stream.

Methods

tokenToChunk :: Proxy s -> Token s -> Tokens s Source #

Lift a single token to chunk of the stream. The default implementation is:

tokenToChunk pxy = tokensToChunk pxy . pure

However for some types of stream there may be a more efficient way to lift.

tokensToChunk :: Proxy s -> [Token s] -> Tokens s Source #

The first method that establishes isomorphism between list of tokens and chunk of the stream. Valid implementation should satisfy:

chunkToTokens pxy (tokensToChunk pxy ts) == ts

chunkToTokens :: Proxy s -> Tokens s -> [Token s] Source #

The second method that establishes isomorphism between list of tokens and chunk of the stream. Valid implementation should satisfy:

tokensToChunk pxy (chunkToTokens pxy chunk) == chunk

chunkLength :: Proxy s -> Tokens s -> Int Source #

Return length of a chunk of the stream.

chunkEmpty :: Proxy s -> Tokens s -> Bool Source #

Check if a chunk of the stream is empty. The default implementation is in terms of the more general chunkLength:

chunkEmpty pxy ts = chunkLength pxy ts <= 0

However for many streams there may be a more efficient implementation.

positionAt1 :: Proxy s -> SourcePos -> Token s -> SourcePos Source #

Set source position at given token. By default, the given SourcePos (second argument) is just returned without looking at the token. This method is important when your stream is a collection of tokens where every token knows where it begins in the original input.

positionAtN :: Proxy s -> SourcePos -> Tokens s -> SourcePos Source #

The same as positionAt1, but for chunks of the stream. The function should return the position where the entire chunk begins. Again, by default the second argument is returned without modifications and the chunk is not looked at.

advance1 :: Proxy s -> Pos -> SourcePos -> Token s -> SourcePos Source #

Advance position given a single token. The returned position is the position right after the token, or the position where the token ends.

advanceN :: Proxy s -> Pos -> SourcePos -> Tokens s -> SourcePos Source #

Advance position given a chunk of stream. The returned position is the position right after the chunk, or the position where the chunk ends.

take1_ :: s -> Maybe (Token s, s) Source #

Extract a single token form the stream. Return Nothing if the stream is empty.

takeN_ :: Int -> s -> Maybe (Tokens s, s) Source #

takeN_ n s should try to extract a chunk of length n, or if the stream is too short, the rest of the stream. Valid implementation should follow the rules:

  • If the requested length n is 0 (or less), Nothing should never be returned, instead Just ("", s) should be returned, where "" stands for the empty chunk, and s is the original stream (second argument).
  • If the requested length is greater than 0 and the stream is empty, Nothing should be returned indicating end of input.
  • In other cases, take chunk of length n (or shorter if the stream is not long enough) from the input stream and return the chunk along with the rest of the stream.

takeWhile_ :: (Token s -> Bool) -> s -> (Tokens s, s) Source #

Extract chunk of the stream taking tokens while the supplied predicate returns True. Return the chunk and the rest of the stream.

For many types of streams, the method allows for significant performance improvements, although it is not strictly necessary from conceptual point of view.

Instances

Stream String Source # 
Stream ByteString Source # 
Stream ByteString Source # 
Stream Text Source # 
Stream Text Source #