megaparsec-7.0.5: Monadic parser combinators

Copyright© 2015–2019 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.

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.

showTokens :: Proxy s -> NonEmpty (Token s) -> String Source #

Pretty-print non-empty stream of tokens. This function is also used to print single tokens (represented as singleton lists).

Since: 7.0.0

reachOffset Source #

Arguments

:: Int

Offset to reach

-> PosState s

Initial PosState to use

-> (SourcePos, String, PosState s)

(See below)

Given an offset o and initial PosState, adjust the state in such a way that it starts at the offset.

Return three values (in order):

  • SourcePos which the given offset o points to.
  • String representing the line on which the given offset o is located. The line should satisfy a number of conditions that are described below.
  • The updated PosState which can be in turn used to locate another offset o' given that o' >= o.

The String representing the offending line in input stream should satisfy the following:

  • It should adequately represent location of token at the offset of interest, that is, character at sourceColumn of the returned SourcePos should correspond to the token at the offset o.
  • It should not include the newline at the end.
  • It should not be empty, if the line happens to be empty, it should be replaced with the string "<empty line>".
  • Tab characters should be replaced by appropriate number of spaces, which is determined by the pstateTabWidth field of PosState.

Since: 7.0.0

reachOffsetNoLine Source #

Arguments

:: Int

Offset to reach

-> PosState s

Initial PosState to use

-> (SourcePos, PosState s)

Reached source position and updated state

A version of reachOffset that may be faster because it doesn't need to fetch the line at which the given offset in located.

The default implementation is this:

reachOffsetNoLine o pst =
  let (spos, _, pst')=  reachOffset o pst
  in (spos, pst')

Since: 7.0.0

Instances
Stream String Source # 
Instance details

Defined in Text.Megaparsec.Stream

Associated Types

type Token String :: Type Source #

type Tokens String :: Type Source #

Stream ByteString Source # 
Instance details

Defined in Text.Megaparsec.Stream

Associated Types

type Token ByteString :: Type Source #

type Tokens ByteString :: Type Source #

Stream ByteString Source # 
Instance details

Defined in Text.Megaparsec.Stream

Associated Types

type Token ByteString :: Type Source #

type Tokens ByteString :: Type Source #

Stream Text Source # 
Instance details

Defined in Text.Megaparsec.Stream

Associated Types

type Token Text :: Type Source #

type Tokens Text :: Type Source #

Stream Text Source # 
Instance details

Defined in Text.Megaparsec.Stream

Associated Types

type Token Text :: Type Source #

type Tokens Text :: Type Source #