gigaparsec-0.3.0.0: Refreshed parsec-style library for compatibility with Scala parsley
LicenseBSD-3-Clause
MaintainerJamie Willis, Gigaparsec Maintainers
Stabilityexperimental
Safe HaskellTrustworthy
LanguageHaskell2010

Text.Gigaparsec.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

Documentation

deriveLiftedConstructors Source #

Arguments

:: String

The prefix to be added to generated names

-> [Name]

The list of "ticked" constructors to generate for

-> Q [Dec] 

This function is used to automatically generate Lifted Constructors, which are one of the patterns in "Design Patterns for Parser Combinators". It is provided with a prefix, which is used to denote an application of the constructor, and then a list of "ticked" constructors to generate lifted constructors for. This means adding a single ' in front of the constructor name. For example:

{-# LANGUAGE TemplateHaskell #-}
data Foo a = Foo a | Bar Int String
$(deriveLiftedConstructors "mk" ['Foo, 'Bar])

Will generate two lifted constructors of the shape:

mkFoo :: Parsec a -> Parsec (Foo a)
mkBar :: Parsec Int -> Parsec String -> Parsec (Foo a)

Furthermore, if one of the arguments to the constructor has type Pos, the pos combinator will be applied automatically, and this will not be apparent in the signature of the generated constructor.

Pattern synonyms can be used to set type parameters to Pos:

{-# LANGUAGE PatternSynonyms #-}
pattern PosFoo :: Pos -> Foo Pos
pattern PosFoo p = Foo p
$(deriveLiftedConstructors "mk" ['PosFoo])

This will generate a lifted constructor of the shape:

mkPosFoo :: Parsec (Foo Pos)

The pos combinator will be applied automatically.

Since: 0.2.6.0

deriveDeferredConstructors Source #

Arguments

:: String

The prefix to be added to generated names

-> [Name]

The list of "ticked" constructors to generate for

-> Q [Dec] 

This function is used to automatically generate Deferred Constructors, which are one of the patterns in "Design Patterns for Parser Combinators". It is provided with a prefix, which is used to denote an application of the constructor, and then a list of "ticked" constructors to generate deferred constructors for. This means adding a single ' in front of the constructor name. For example:

{-# LANGUAGE TemplateHaskell #-}
data Foo a = Foo a | Bar Int String
$(deriveDeferredConstructors "mk" ['Foo, 'Bar])

Will generate two deferred constructors of the shape:

mkFoo :: Parsec (a -> Foo a)
mkBar :: Parsec (Int -> String -> Foo a)

Furthermore, if one of the arguments to the constructor has type Pos, the pos combinator will be applied automatically, and this will not be apparent in the signature of the generated constructor.

Pattern synonyms can be used to set type parameters to Pos:

{-# LANGUAGE PatternSynonyms #-}
pattern PosFoo :: Pos -> Foo Pos
pattern PosFoo p = Foo p
$(deriveLiftedConstructors "mk" ['PosFoo])

This will generate a lifted constructor of the shape:

mkPosFoo :: Parsec (Foo Pos)

The pos combinator will be applied automatically.

Since: 0.2.6.0