inchworm-1.0.2.3: Inchworm Lexer Framework

Safe HaskellSafe
LanguageHaskell98

Text.Lexer.Inchworm.Source

Synopsis

Documentation

data Source m loc input Source #

An abstract source of input tokens that we want to perform lexical analysis on.

Each token is associated with a source location loc. A a sequence of tokens has type input, and a single token type (Elem input).

Constructors

Source 

Fields

  • sourceSkip :: (Elem input -> Bool) -> m ()

    Skip over values from the source that match the given predicate.

  • sourceTry :: forall a. m (Maybe a) -> m (Maybe a)

    Try to evaluate the given computation that may pull values from the source. If it returns Nothing then rewind the source to the original position.

  • sourcePull :: (Elem input -> Bool) -> m (Maybe (loc, Elem input))

    Pull a value from the source, provided it matches the given predicate.

  • sourcePulls :: forall s. Maybe Int -> (Int -> Elem input -> s -> Maybe s) -> s -> m (Maybe (loc, input))

    Use a fold function to select a some consecutive tokens from the source that we want to process, also passing the current index to the fold function.

    The maximum number of tokens to select is set by the first argument, which can be set to Nothing for no maximum.

  • sourceBumpLoc :: Elem input -> loc -> loc

    Bump the source location using the given element.

  • sourceRemaining :: m (loc, input)

    Get the remaining input.

data Location Source #

A location in a source file.

Constructors

Location !Int !Int 
Instances
Show Location Source # 
Instance details

Defined in Text.Lexer.Inchworm.Source

class Sequence is where Source #

Class of sequences of things.

Minimal complete definition

length

Associated Types

type Elem is Source #

An element of a sequence.

Methods

length :: is -> Int Source #

Yield the length of a sequence.

Instances
Sequence [a] Source # 
Instance details

Defined in Text.Lexer.Inchworm.Source

Associated Types

type Elem [a] :: * Source #

Methods

length :: [a] -> Int Source #

makeListSourceIO Source #

Arguments

:: Eq i 
=> loc

Starting source location.

-> (i -> loc -> loc)

Function to bump the current location by one input token.

-> [i]

List of input tokens.

-> IO (Source IO loc [i]) 

Make a source from a list of input tokens, maintaining the state in the IO monad.