gigaparsec
LicenseBSD-3-Clause
MaintainerJamie Willis, Gigaparsec Maintainers
Stabilityexperimental
Safe HaskellTrustworthy
LanguageHaskell2010

Text.Gigaparsec.Token.Patterns

Description

This module is currently experimental, and may have bugs depending on the version of Haskell, or the extensions enabled. Please report any issues to the maintainers.

Since: 0.2.2.0

Synopsis

Overloaded Strings

overloadedStrings Source #

Arguments

:: Q Exp

the quoted Lexer

-> Q [Dec]

a synthesised IsString instance.

When given a quoted reference to a Lexer, for example [|lexer|], this function will synthesise an IsString instance that will allow string literals to serve as Parsec (). These literals will parse symbols in the language associated with the lexer, followed by consuming valid whitespace.

Since: 0.2.2.0

Lexer Combinators

These functions will generate combinators for parsing things like identifiers, keywords, etc, as described by a Lexer.

The combinators will behave like their counterparts in Text.Gigaparsec.Token.Lexer, except they do not need to be given a lexer(/a subcomponent of a lexer) as an argument.

Examples:

Expand

The combinator "Text.Gigaparsec.Token.Lexer.identifier" is used for parsing identifiers, and has the type,

Lexer.identifier :: Lexer -> Parsec String

It is annoying to have to feed the lexer as the initial argument, as this will be fixed throughout the parser. Usually, one ends up writing their own combinator:

identifier :: Parsec String
identifier = Lexer.identifier lexer

Writing these by hand is tedious; especially if we wish to use multiple such combinators. This is where lexerCombinators comes in:

$(lexerCombinators [| lexer |] ['Lexer.identifier])

will generate the combinator,

identifier :: Parsec String
identifier = Lexer.identifier lexer

If we wish to use multiple combinators, we just add each one to the list. For example,

$(lexerCombinators [| lexer |] ['Lexer.identifier, 'Lexer.fully, 'Lexer.softKeyword, 'Lexer.softOperator])

lexerCombinators Source #

Arguments

:: Q Exp

The quoted Lexer.

-> [Name]

The combinators to generate.

-> Q [Dec]

Definitions of the generated combinators.

Generates the specified lexer combinators using a quoted Lexer, for example, [|lexer|].

The generated combinators will behave like their counterparts in Text.Gigaparsec.Token.Lexer, except they won't require a lexer (or subcomponents thereof) to be supplied as an argument.

Usage:

Expand
import Text.Gigaparsec.Token.Lexer qualified as Lexer
import Text.Gigaparsec.Token.Lexer (Lexer)
lexer :: Lexer
$(lexerCombinators [| lexer |] ['Lexer.lexeme, 'Lexer.fully, 'Lexer.identifier, 'Lexer.stringLiteral])

This will generate the following combinators/functions:

lexeme :: Lexeme
fully :: ∀ a . Parsec a -> Parsec a
identifier :: Parsec String
stringLiteral :: TextParsers String

These will behave like their counterparts in Text.Gigaparsec.Token.Lexer, except they will not need a Lexer (or its subcomponents) as an argument.

Since: 0.4.0.0

lexerCombinatorsWithNames Source #

Arguments

:: Q Exp

The quoted Lexer.

-> [(Name, String)]

The combinators to generate with the given name.

-> Q [Dec]

Definitions of the generated combinators.

Generates the specified lexer combinators with the given names using a quoted Lexer, for example, [|lexer|].

The generated combinators will behave like their counterparts in Text.Gigaparsec.Token.Lexer, except they won't require a lexer (or subcomponents thereof) to be supplied as an argument.

Usage:

Expand
import Text.Gigaparsec.Token.Lexer qualified as Lexer
import Text.Gigaparsec.Token.Lexer (Lexer)
lexer :: Lexer
$(lexerCombinatorsWithNames [| lexer |] [('Lexer.lexeme, "myLexeme"), ('Lexer.fully, "myFully")])

This will generate the following combinators/functions:

myLexeme :: Lexeme
myFully :: ∀ a . Parsec a -> Parsec a

These will behave like their counterparts in Text.Gigaparsec.Token.Lexer, except they will not need a Lexer (or its subcomponents) as an argument.

Since: 0.4.0.0

Integer Parsers

generateIntegerParsers Source #

Arguments

:: Q Exp

The quoted Lexer

-> IntegerParserConfig

The configuration describing what numeric combinators to produce.

-> Q [Dec]

The declarations of the specified combinators.

This function automatically generates lexer combinators for handling signed or unsigned integers.

See IntegerParserConfig for how to configure which combinators are generated.

Note: Due to staging restrictions in Template Haskell, the IntegerParserConfig must be defined in a separate module to where this function is used. Multiple configs can be defined in the same module.

Usage:

Expand

First, the config must be defined in another module. You can define multiple configs in the same module, as long as they are used in a different module.

{-# LANGUAGE TemplateHaskell, OverloadedLists #-}
module IntegerConfigs where
…
uIntCfg :: IntegerParserConfig
uIntCfg = emptyUnsignedIntegerParserConfig {
    prefix = "u",
    widths = [(B8, [t| Word8 |]), (B32, [t| Word32 |])],
    bases = [Hexadecimal, Decimal, Binary],
    includeUnbounded = False,
    signedOrUnsigned = Unsigned,
    collatedParser = Just "natural"
  }

Then, we can feed this config, along with a quoted lexer, to generateIntegerParsers:

{-# LANGUAGE TemplateHaskell #-}
module Lexer where
import IntegerConfigs (uIntCfg)
…
lexer :: Lexer
lexer = …

$(generateIntegerParsers [| lexer |] uIntCfg)

This will generate the following combinators,

   ubinary8 :: Parsec Word8
   udecimal8 :: Parsec Word8
   uhexadecimal8 :: Parsec Word8
   ubinary32 :: Parsec Word32
   udecimal3 :: Parsec Word32
   uhexadecimal32 :: Parsec Word32
   natural8 :: Parsec Word8
   natural32 :: Parsec Word32

Since: 0.4.0.0

IntegerParserConfig

data IntegerParserConfig Source #

This type describes how to generate numeric parsers with generateIntegerParsers. This includes configuration for which bases and bitwidths to support, and whether to generate parsers that can handle multiple bases.

See the emptyIntegerParserConfig smart constructor to define a IntegerParserConfig.

Since: 0.4.0.0

prefix :: IntegerParserConfig -> String Source #

The string to prepend to each generated parser's name (except for the collatedParser, if specified).

Since: 0.4.0.0

widths :: IntegerParserConfig -> Map Bits (Q Type) Source #

The fixed bit-widths (8-bit, 16-bit, etc/) for which to generate parsers.

Since: 0.4.0.0

bases :: IntegerParserConfig -> Set IntLitBase Source #

The numeric bases (binary, octal, etc) for which to generate parsers.

Since: 0.4.0.0

includeUnbounded :: IntegerParserConfig -> Bool Source #

When True, generate the unbounded integer parsers (e.g. decimal) for each base specified in bases.

Since: 0.4.0.0

signedOrUnsigned :: IntegerParserConfig -> SignedOrUnsigned Source #

Whether or not the parsers to generate are for Signed or Unsigned integers.

Since: 0.4.0.0

collatedParser :: IntegerParserConfig -> Maybe String Source #

Generate a generic integer parser with the given name, at each width (including unbounded) specified by widths, that is able to parse each base specified in bases.

Since: 0.4.0.0

Presets

emptyIntegerParserConfig :: IntegerParserConfig Source #

An empty IntegerParserConfig, which will generate nothing when given to generateIntegerParsers. Extend this using record updates, to tailor a config to your liking.

By default, the prefix field is the empty string, which will likely cause issues if you do not override this.

Since: 0.4.0.0

emptySignedIntegerParserConfig :: IntegerParserConfig Source #

An empty IntegerParserConfig for Signed integers, which will generate nothing when given to generateIntegerParsers. Extend this using record updates, to tailor a config to your liking.

By default, the prefix field is the empty string, which will likely cause issues if you do not override this.

Since: 0.4.0.0

emptyUnsignedIntegerParserConfig :: IntegerParserConfig Source #

An empty IntegerParserConfig for Unsigned integers, which will generate nothing when given to generateIntegerParsers. Extend this using record updates, to tailor a config to your liking.

By default, the prefix field is the empty string, which will likely cause issues if you do not override this.

Since: 0.4.0.0

Associated Types

data SignedOrUnsigned Source #

Determines if the combinators are for Signed or Unsigned int literals.

Since: 0.4.0.0

Constructors

Signed

The int literal is signed, so can be negative.

Since: 0.4.0.0

Unsigned

The literal is unsigned, so is always non-negative.

Since: 0.4.0.0

allBases :: Set IntLitBase Source #

Set of all possible IntLitBases.

Since: 0.4.0.0

data IntLitBase Source #

The base of a numeric literal.

Used in IntegerParserConfig to specify which parsers for which bases should be generated.

Since: 0.4.0.0

Constructors

Binary 
Octal 
Decimal 
Hexadecimal