Farkle


Quick Start: Creating a calculator

Hello everyone. This guide will help you use Farkle. We will be using F#, but during the process, you will learn some useful things about Farkle itself. There's another guide that explains what's different with C#. Familiarity with context-free grammars and parsing will be very helpful.

How Farkle works

While parser combinator libraries like FParsec combine many small parsers into a big parser, Farkle combines simple grammars (i.e. descriptions of languages) into more complex ones, and has a single, multi-purpose parser. These composable grammars are called designtime Farkles and implement the Farkle.Builder.DesigntimeFarkle interface.

Also, as with FParsec, a designtime Farkle can "return" something. In this case it also implements the DesigntimeFarkle<TResult> interface. For our calculator, our designtime Farkles will return a number, which is the numerical result of our mathematical expression.

Warning: Despite designtime Farkles being interfaces, implementing it in your code is not allowed and will throw an exception if a custom designtime Farkle implementation is somehow passed to Farkle.

To be able to use a designtime Farkle, we will first give it to a component called the builder. The builder will check the grammar for errors, create the necessary structures for the parser, and give us another special object called a runtime Farkle. With a runtime Farkle, we can parse text to our heart's desires, but in contrast with a designtime Farkle, we cannot compose it.

10: By the way, Farkle means "FArkle Recognizes Known Languages Easily".

20: And "FArkle" means (GOTO 10).

30: I guess you can't read this line.

Designing our grammar

We want to design a grammar that represents mathematical expressions on floating-point numbers. The supported operations will be addition, subtraction, multiplication, division, and unary negation. The operator precedence has to be honored, as well as parentheses.

A similar grammar but on the integers, can be found here

For those that don't know, a context-free grammar is made of terminals, nonterminals and productions.

* Nonterminals are composite symbols made of terminals and other nonterminals.

One of the nonterminals is designated as the _start symbol_, and it is the nonterminal from which parsing will start.

The terminals

We don't have to explicitly write a terminal for the mathematical symbols. They are just symbols that can have only one value and do not contain any meaningful information other than their presence. Farkle calls these types of symbols literals and treats them specially to reduce boilerplate.

So we are now left with one terminal to define; the terminal for our decimal numbers. In Farkle, terminals are made of a regular expression that specifies the text that can match to this terminal, and a delegate called transformer that converts the text to an arbitrary object.

There are three ways to create this terminal, starting from the simplest:


The Farkle.Builder.Terminals has functions that allow you to create some commonly needed terminals, like integers or floating-point numbers. We create our terminal this way:

open Farkle
open Farkle.Builder
open System

let number = Terminals.genericReal<float> false "Number"

The boolean parameter specifies whether to allow a minus sign at the beginning (we don't). The last parameter is the terminal's name, used for error reporting.

The Terminals module has more functions. You can see them all in the documentation.


If Farkle doesn't have a ready to use function for your terminal, we have to create the terminal ourselves. The most easy way to do it is to write a regex using a string:

let numberStringRegex =
    Regex.regexString @"\d+(\.\d+)?(e[+-]?\d+)?"
    |> terminal "Number" (T(fun _ x -> float (x.ToString())))

The regexString function uses a quite familiar regex syntax. You can learn more about it at its own documentation page.

Let's take a look at the terminal function. Its last parameter is the regex, which we passed at the beggining for convenience and its first parameter is the terminal's name; nothing unusual here. Its second parameter is called a transformer and is a delegate that converts the characters matched by our regex to an arbitrary object; in our case an integer.

Writing a transformer

The transformer's first parameter is an object of type ITransformerContext and is useful if you want to access the token's position or share some state between transformers, and its second parameter is a ReadOnlySpan of the characters matched by our regex, which will be converted to a floating-point number by our transformer.

T is the delegate's F# name. Because you have to specify it due to the language's limitations it was shortened to one letter for brevity.

You can view transformers as little parsers that always parse well-formatted text. In our example, the transformer for Number does not usually have to worry about exceptions from invalid input since the regex we specified guarantees the kind of input it expects. There are exceptions to this, like the user passing an extremely high integer. Such inputs will cause an exception to be raised. The built-in terminals the Farkle.Builder.Terminals module provides will handle the exception a little more gracefully but still fail the parsing.

Speaking of graceful errors, you can raise errors in your transformer by calling the error function, or the errorf function if you want formatted strings. If you are using C# or want to customize the exact position of the error, you can directly throw a Farkle.ParserApplicationException. They will be caught by the parser and can be uniformly handled like Farkle's own errors, as we will see later.


For the most advanced use cases, Farkle allows you to construct a regex from code. Directly constructing a regex from code is rarely useful for the average user of Farkle, but might come in handy when for example the regex's structure is not known at compile time, or it is complex enough to merit some code reuse.

open Farkle.Builder.Regex

let numberConstructedRegex =
    // Regexes are composable!
    let atLeastOneNumber = chars PredefinedSets.Number |> atLeast 1
    // You can freely mix string regexes and constructed regexes.
    // let atLeastOneNumber = regexString @"\d+"
    concat [
        atLeastOneNumber
        optional <| (char '.' <&> atLeastOneNumber)
        [chars "eE"; chars "+-" |> optional; atLeastOneNumber]
        |> concat
        |> optional
    ]
    |> terminal "Number" (T(fun _ x -> float (x.ToString())))

You can learn more about the functions above at the documentation. More character sets of the Farkle.Builder.PredefinedSets module can also be found at the documentation

Note: The regexes' type is Farkle.Builder.Regex. They are totally unrelated to .NET's System.Text.RegularExpressions.Regex. We can't convert between these two types, or directly match text against Farkle's regexes.

The terminal we created is of type DesigntimeFarkle<float>. This means that we can use it to parse floating-point numbers from text, but we want to create something bigger than that. As we are going to see, we can compose designtime Farkles into bigger ones, using nonterminals.

The nonterminals.

Writing simple nonterminals.

Because the calculator's nonterminals are a bit complicated, we have to take a brief interlude and tell how to create simpler ones.

Say we want to make a very simple calculator that can either add or subtract two numbers together. And let's say that an empty string would result to zero. This is the grammar of our calculator in Backus-Naur Form:

<Exp> ::= Number + Number
<Exp> ::= Number - Number
<Exp> ::= <>

For those that don't understand the snippet above, we define a nonterminal named Exp, that has three productions associated with it, meaning an Exp can be made in three ways: either by taking a sequence of the Number terminal, either the + or the - terminal, and another Number terminal, or by no symbols at all.

Writing the same thing in Farkle is actually surprisingly simple:

let justTwoNumbers = "Exp" ||= [
    !@ number .>> "+" .>>. number => (fun x1 x2 -> x1 + x2)
    !@ number .>> "-" .>>. number => (fun x1 x2 -> x1 - x2)
    empty =% 0.0
]

Let's explain what was going here. With the ||= operator, we define a nonterminal with its productions. In its left side goes its name, and in its right side go the productions that can produce it.

See these strange symbols inside the list? They chain designtime Farkles together and signify which of them have information we care about. !@ starts defining a production with its first member carrying significant information (the first operand). To start a production with a designtime Farkle that does not carry significant information, we can use !%.

The .>> and .>>. operators resemble FParsec's ones. .>> chains a new designtime Farkle we don't care what contains, and .>>. chains one we do.

With .>>, we can also chain string literals, instead of creating a terminal for each. We can also start a production with a literal using the !& operator.

The => operator finishes the creation of a production with a function that combines its members that we marked as significant. Such functions are called fusers. In the first production we added the numbers and in the second we subtracted them. So, depending on the expression we entered, _justTwoNumbers would return either the sum, or the difference of them. Obviously, all productions of a nonterminal have to return the same type.

In the third case, we defined an empty production using empty (what a coincidence!) We used empty =% 0.0 as a shortcut instead of writing empty => (fun () -> 0.0).

An unfinished production is called a production builder. You can mark up to 16 significant members in a production builder.

You can pass an empty list in the right hand of the ||= operator but the grammar will be invalid. A nonterminal must always have at least one production.

Writing more complex nonterminals

We want our calculator to implement the following grammar taken from Bison's documentation:

%left '-' '+'
%left '*' '/'
%precedence NEG
%right '^'

exp:
    NUM
    | exp '+' exp        { $$ = $1 + $3;      }
    | exp '-' exp        { $$ = $1 - $3;      }
    | exp '*' exp        { $$ = $1 * $3;      }
    | exp '/' exp        { $$ = $1 / $3;      }
    | '-' exp  %prec NEG { $$ = -$2;          }
    | exp '^' exp        { $$ = pow ($1, $3); }
    | '(' exp ')'        { $$ = $2;           }
;

And this is how to implement it in Farkle:

open Farkle.Builder.OperatorPrecedence

let expression =
    let NEG = obj()

    let expression = nonterminal "Expression"
    expression.SetProductions(
        !@ number |> asIs,
        !@ expression .>> "+" .>>. expression => (fun x1 x2 -> x1 + x2),
        !@ expression .>> "-" .>>. expression => (fun x1 x2 -> x1 - x2),
        !@ expression .>> "*" .>>. expression => (fun x1 x2 -> x1 * x2),
        !@ expression .>> "/" .>>. expression => (fun x1 x2 -> x1 / x2),
        !& "-" .>>. expression |> prec NEG => (fun x -> -x),
        !@ expression .>> "^" .>>. expression => (fun x1 x2 -> Math.Pow(x1, x2)),
        // We use |> asIs instead of => (fun x -> x).
        !& "(" .>>. expression .>> ")" |> asIs
    )

    let opScope =
        OperatorScope(
            LeftAssociative("+", "-"),
            LeftAssociative("*", "/"),
            PrecedenceOnly(NEG),
            RightAssociative("^")
        )

    DesigntimeFarkle.withOperatorScope opScope expression

As you see, our grammar in Farkle looks pretty similar to the one in Bison. Let's take a look at some newly introduced things:

Defining recursive nonterminals

The nonterminal function is useful for recursive nonterminals. It creates a nonterminal whose productions will be set later with the SetProductions method. We can only once set them, all together. Calling the method again will have no effect.

Our nonterminal is of type Nonterminal<float>, but implements the DesigntimeFarkle<float> interface.

Operator Precedence

We specify the operator associativity and precedence using an operator scope that is made of associativity groups. There are four associativity group types: LeftAssociative, RightAssociative, NonAssociative and PrecedenceOnly that behave similarly to Bison's %left, %right, %nonassoc and %precedence. Their difference is best explained at Bison's documentation.

The groups in an operator scope are sorted by precedence in ascending order. In our grammar, the + and - symbols have the lowest precedence, followed by * and /. Until now, all these operators are left-associative, meaning that 1 + 2 + 3 is interpreted as (1 + 2) + 3.

Next in the precedence hierarchy is the unary negation. We can't define - again; instead we use the prec function to assign the unary negation's production a contextual reflection token, which is a dummy object that represents the production in the operator scope. This way, Farkle will recognize that - has higher precedence in unary negation than in subtraction. That new group is of type PrecedenceOnly, meaning that it doesn't specify associativity; only precedence.

And at the highest priority we have the exponentiation operator, which is right associative, meaning that 2 ^ 3 ^ 4 is interpreted as 2 ^ (3 ^ 4).

We set this operator scope to our designtime Farkle using the DesigntimeFarkle.withOperatorScope function. There are some more things to be careful about when using operator scopes:

Building our grammar

With our nonterminals being ready, it's time to create a runtime Farkle that can parse mathematical expressions. The builder will create tables for the parser using the LALR algorithm, and a Deterministic Finite Automaton (DFA) for the tokenizer. It also creates a special object called a post-processor that is responsible for executing the transformers and fusers.

All that stuff can be done with a single line of code:

let myMarvelousRuntimeFarkle = RuntimeFarkle.build expression

Using the runtime Farkle

Now that we got it, it's time to put it to action. Farkle supports parsing text from various sources, namely strings, arbitrary character buffers on the heap (like substrings, arrays or parts of arrays) using System.ReadOnlyMemory<char>, files and System.IO.TextReaders.

The functions return an F# Result type whose error value (if it unfortunately exists), can show exactly what did go wrong.

Note: If a grammar is invalid (has an LALR conflict, two terminals are indistinguishable or something else), building would still succeed, but parsing would fail every time.

Let's look at some some examples:

open System.IO

// You can consume the parsing result like this:
match RuntimeFarkle.parseString myMarvelousRuntimeFarkle "103 + 137+281" with
| Ok result -> printfn "The answer is %f" result
// The %O format specifier (or alternatively, calling ToString())
// will create human-readable error messages.
| Error err -> printfn "Error: %O" err

// You can parse any Memory<char>, such a substring or even an array of characters!
let mem = "The answer is 45".AsMemory().Slice(14)
RuntimeFarkle.parseMemory myMarvelousRuntimeFarkle mem

RuntimeFarkle.parseFile myMarvelousRuntimeFarkle "example.txt"

let myStringReader = new StringReader("45 + 198 - 647 + 2 * 478 - 488 + 801 - 248")
RuntimeFarkle.parseTextReader myMarvelousRuntimeFarkle myStringReader

Customizing our designtime Farkle

Before we finish, let's take a look at one more thing; how to further customize a designtime Farkle.

We will see some customizations as an example:

let _customized =
    expression
    // You can add as many types of block or line comments as you want.
    |> DesigntimeFarkle.addBlockComment "/*" "*/"
    |> DesigntimeFarkle.addLineComment "//"
    |> DesigntimeFarkle.caseSensitive true
    // Whether to ignore whitespace between terminals; true by default.
    |> DesigntimeFarkle.autoWhitespace false
    // Adds an arbitrary symbol that will be ignored by Farkle.
    // It needs a regex, and a name for diagnostics purposes.
    |> DesigntimeFarkle.addNoiseSymbol "Letters" (chars AllLetters)

Note: These customizations have to be done at the top-level designtime Farkle that is going to be built (or they will have no effect) and always apply to the entire grammar.


So, I hope you enjoyed this little tutorial. If you did, don't forget to give Farkle a try, and maybe you have any question, found a bug, or want a feature, and want to open a GitHub issue as well. I hope that all of you have a wonderful day and to see you soon. Goodbye!

namespace Farkle
namespace Farkle.Builder
namespace System
val number: DesigntimeFarkle<float>
module Terminals from Farkle.Builder
<summary>Some designtime Farkles that are commonly used in many grammars.</summary>
<remarks> These functions take a name and create a designtime Farkle which is meant to be reused everywhere it is needed in the grammar. Creating and using many designtime Farkles of the same or similar kind will almost certainly lead to an error.</remarks>
val genericReal: allowSign: bool -> name: string -> DesigntimeFarkle<'TReal> (requires member Parse)
<summary> Creates a designtime Farkle that parses a real number into the desired number type. No bounds checking is performed. Using this function from a language other than F# will throw an exception. </summary>
Multiple items
val float: value: 'T -> float (requires member op_Explicit)

--------------------
type float = Double

--------------------
type float<'Measure> = float
val numberStringRegex: DesigntimeFarkle<float>
Multiple items
module Regex from Farkle.Builder
<summary> F#-friendly members of the `Regex` class. Please consult the members of the `Regex` class for documentation. </summary>

--------------------
type Regex = private | Concat of Regex list | Alt of Regex list | Star of Regex | Chars of Set<char> | AllButChars of Set<char> | RegexString of RegexStringHolder member And: x2: Regex -> Regex member AtLeast: num: int -> Regex member Between: from: int -> upTo: int -> Regex member Optional: unit -> Regex member Or: x2: Regex -> Regex member Repeat: num: int -> Regex member ZeroOrMore: unit -> Regex static member Choice: [<ParamArray>] regexes: Regex array -> Regex static member FromRegexString: x: string -> Regex static member Join: [<ParamArray>] regexes: Regex array -> Regex ...
<summary>A regular expression that is used to specify a tokenizer symbol.</summary>
<remarks>Checking two regular expressions for equality does not mean that they recognize the same symbols, but that their internal structure is the same.</remarks>
val regexString: x: string -> Regex
val terminal: name: string -> fTransform: T<'a> -> regex: Regex -> DesigntimeFarkle<'a>
<summary> Creates a terminal with the given name, specified by the given `Regex`. Its content will be post-processed by the given `T` delegate. </summary>
T (ITransformerContext -> ReadOnlySpan<char> -> float)
<summary>A delegate that transforms the content of a terminal to an arbitrary object.</summary>
<param name="context">An <see cref="ITransformerContext" /> that provides additional info about the terminal.</param>
<param name="data">A read-only span of the terminal's characters.</param>
<remarks><para>In F# this type is shortened to <c>T</c> to avoid clutter in user code.</para><para>A .NET delegate was used because read-only spans are incompatible with F# functions.</para></remarks>
val x: ReadOnlySpan<char>
ReadOnlySpan.ToString() : string
val numberConstructedRegex: DesigntimeFarkle<float>
val atLeastOneNumber: Regex
val chars: str: char seq -> Regex
<summary> An alias for `Regex.OneOf`. </summary>
module PredefinedSets from Farkle.Builder
<summary> Some common character sets that were imported from GOLD Parser. </summary>
val Number: PredefinedSet
val atLeast: num: int -> x: Regex -> Regex
val concat: xs: Regex seq -> Regex
val optional: x: Regex -> Regex
Multiple items
val char: c: char -> Regex
<summary> An alias for `Regex.Literal` that takes a character. </summary>

--------------------
type char = Char
val justTwoNumbers: DesigntimeFarkle<float>
val x1: float
val x2: float
val empty: ProductionBuilder
<summary> An alias for `ProductionBuilder.Empty`. </summary>
val exp: value: 'T -> 'T (requires member Exp)
namespace Farkle.Builder.OperatorPrecedence
val expression: Nonterminal<float>
val NEG: obj
type obj = Object
val nonterminal: name: string -> Nonterminal<'a>
<summary> Creates a `Nonterminal` whose productions must be later set with `SetProductions`, or it will raise an error on building. Useful for recursive productions. </summary>
abstract Nonterminal.SetProductions: firstProd: Production<'T> * [<ParamArray>] prods: Production<'T> array -> unit
val asIs: pb: ProductionBuilders.ProductionBuilder<'T> -> Production<'T>
<summary> An alias for ``ProductionBuilder`1.AsIs``. </summary>
val prec: token: obj -> pb: 'TBuilder -> 'TBuilder (requires member WithPrecedence)
<summary> An alias for the `WithPrecedence` method of production builders. </summary>
val x: float
type Math = static member Abs: value: decimal -> decimal + 7 overloads static member Acos: d: float -> float static member Acosh: d: float -> float static member Asin: d: float -> float static member Asinh: d: float -> float static member Atan: d: float -> float static member Atan2: y: float * x: float -> float static member Atanh: d: float -> float static member BigMul: a: int * b: int -> int64 + 2 overloads static member BitDecrement: x: float -> float ...
<summary>Provides constants and static methods for trigonometric, logarithmic, and other common mathematical functions.</summary>
Math.Pow(x: float, y: float) : float
val opScope: OperatorScope
Multiple items
type OperatorScope = new: resolvesReduceReduceConflicts: bool * assocGroups: AssociativityGroup seq -> OperatorScope + 2 overloads member ResolvesReduceReduceConflict: bool static member Empty: OperatorScope
<summary>A group of associativity groups sorted by precedence.</summary>
<remarks><para>A symbol in an operator scope has higher precedence than another one if it appears in a group below the former symbol's group.</para><para>If the same symbol is specified in multiple associativity groups, it will have the precedence of the earliest group in which it appeared.</para><para>Symbols from multiple operator scopes cannot be compared for precedence.</para><para>A symbol can belong in only one operator scope; if it belongs in more, the operator scope to which the symbol will be assigned is undefined.</para><para>Operator scopes are used to automatically resolve Shift-Reduce conflicts. Resolving Reduce-Reduce conflicts can also happen but it must be explicitly opt-in by passing a boolean argument of <see langword="true" /> in the first argument of the appropriate operator scope's constructor overloads.</para></remarks>


--------------------
new: [<ParamArray>] assocGroups: AssociativityGroup array -> OperatorScope
new: resolvesReduceReduceConflicts: bool * assocGroups: AssociativityGroup seq -> OperatorScope
new: resolveReduceReduceConflicts: bool * [<ParamArray>] assocGroups: AssociativityGroup array -> OperatorScope
Multiple items
type LeftAssociative = inherit AssociativityGroup new: [<ParamArray>] symbols: obj array -> LeftAssociative
<summary> A shortcut for creating left-associative groups. </summary>

--------------------
new: [<ParamArray>] symbols: obj array -> LeftAssociative
Multiple items
type PrecedenceOnly = inherit AssociativityGroup new: [<ParamArray>] symbols: obj array -> PrecedenceOnly
<summary> A shortcut for creating associativity groups with only precedence and no associativity between them. </summary>

--------------------
new: [<ParamArray>] symbols: obj array -> PrecedenceOnly
Multiple items
type RightAssociative = inherit AssociativityGroup new: [<ParamArray>] symbols: obj array -> RightAssociative
<summary> A shortcut for creating right-associative groups. </summary>

--------------------
new: [<ParamArray>] symbols: obj array -> RightAssociative
Multiple items
module DesigntimeFarkle from Farkle.Builder
<summary> Functions to set metadata for designtime Farkles. With few exceptions, these functions will have to be applied to the topmost designtime Farkle that will get build, or they will have no effect. Designime Farkles that were applied the functions of this module must not be used with the original designtime Farkles in the same context; only one grammar symbol will be created, with undefined behavior. </summary>

--------------------
type DesigntimeFarkle = abstract Metadata: GrammarMetadata abstract Name: string
<summary>The base interface of <see cref="DesigntimeFarkle{T}" />.</summary>
<remarks><para>In contrast with its typed descendant, untyped designtime Farkles do not return any value. They typically represent literal symbols that can only take one value. Building an untyped designtime Farkle will result in a syntax-checking runtime Farkle with no custom post-processor.</para><para>User code must not implement this interface, or an exception might be thrown.</para></remarks>
<seealso cref="DesigntimeFarkle{T}" />


--------------------
type DesigntimeFarkle<'T> = inherit DesigntimeFarkle
<summary>An object representing a grammar symbol created by Farkle.Builder. It corresponds to either a standalone terminal or a nonterminal that contains other designtime Farkles.</summary>
<remarks><para>Designtime Farkles cannot be used to parse text but can be composed into larger designtime Farkles. To actually use them, they have to be converted to a <see cref="RuntimeFarkle{T}" /> which however is not composable. This one-way conversion is performed by the <c>RuntimeFarkle.build</c> function or the <c>Build</c> extension method.</para><para>This interface has no members on its own; they are inherited from <see cref="DesigntimeFarkle" />.</para><para>User code must not implement this interface, or an exception might be thrown.</para></remarks>
<typeparam name="T">The type of the objects this grammar generates.</typeparam>
<seealso cref="DesigntimeFarkle" />
val withOperatorScope: opScope: OperatorScope -> df: 'a -> 'a (requires 'a :> DesigntimeFarkle)
<summary> Sets an `OperatorScope` object to a designtime Farkle. This function can be applied in designtime Farkles that are not the topmost ones. Applying this function many times will discard the existing operator scope. </summary>
val myMarvelousRuntimeFarkle: RuntimeFarkle<float>
Multiple items
module RuntimeFarkle from Farkle
<summary> Functions to create and use `RuntimeFarkle`s. </summary>

--------------------
type RuntimeFarkle<'TResult> = private { Grammar: Result<Grammar,BuildError list> PostProcessor: PostProcessor<'TResult> TokenizerFactory: TokenizerFactory } interface IGrammarProvider member Cast: unit -> RuntimeFarkle<obj> member ChangePostProcessor: pp: PostProcessor<'TNewResult> -> RuntimeFarkle<'TNewResult> member ChangeTokenizer: tokenizerFactory: TokenizerFactory -> RuntimeFarkle<'TResult> + 1 overload member GetBuildErrorMessage: unit -> string member GetBuildErrors: unit -> BuildError list member GetGrammar: unit -> Grammar member Parse: input: CharStream -> Result<'TResult,FarkleError> + 3 overloads member ParseFile: path: string -> Result<'TResult,FarkleError> member SyntaxCheck: unit -> RuntimeFarkle<obj> ...
<summary>A reusable parser and post-processor, created for a specific grammar, and returning a specific type of object that best describes an expression of the language of this grammar.</summary>
<remarks><para>Its parsing methods return an F# result type containing either the post-processed return type, or a type describing what did wrong and where.</para><para>Exceptions during post-processing (apart from <see cref="ParserApplicationException" />) are thrown after being wrapped in a <see cref="PostProcessorException" />.</para></remarks>
val build: df: DesigntimeFarkle<'a> -> RuntimeFarkle<'a>
<summary> Creates a `RuntimeFarkle` from the given `DesigntimeFarkle&amp;lt;'T&amp;gt;`. In case there is a problem with the grammar, the `RuntimeFarkle` will fail every time it is used. If the designtime Farkle is marked for precompilation and a suitable precompiled grammar is found, it will be ignored. </summary>
namespace System.IO
val parseString: rf: RuntimeFarkle<'a> -> inputString: string -> Result<'a,FarkleError>
<summary> Parses and post-processes a string. </summary>
union case Result.Ok: ResultValue: 'T -> Result<'T,'TError>
val result: float
val printfn: format: Printf.TextWriterFormat<'T> -> 'T
union case Result.Error: ErrorValue: 'TError -> Result<'T,'TError>
val err: FarkleError
val mem: ReadOnlyMemory<char>
val parseMemory: rf: RuntimeFarkle<'a> -> input: ReadOnlyMemory<char> -> Result<'a,FarkleError>
<summary> Parses and post-processes a `ReadOnlyMemory` of characters. </summary>
val parseFile: rf: RuntimeFarkle<'a> -> path: string -> Result<'a,FarkleError>
<summary> Parses and post-processes a file at the given path. </summary>
val myStringReader: StringReader
Multiple items
type StringReader = inherit TextReader new: s: string -> unit member Close: unit -> unit member Peek: unit -> int member Read: unit -> int + 2 overloads member ReadAsync: buffer: char array * index: int * count: int -> Task<int> + 1 overload member ReadBlock: buffer: Span<char> -> int member ReadBlockAsync: buffer: char array * index: int * count: int -> Task<int> + 1 overload member ReadLine: unit -> string member ReadLineAsync: unit -> Task<string> + 1 overload ...
<summary>Implements a <see cref="T:System.IO.TextReader" /> that reads from a string.</summary>

--------------------
StringReader(s: string) : StringReader
val parseTextReader: rf: RuntimeFarkle<'a> -> textReader: TextReader -> Result<'a,FarkleError>
<summary> Parses and post-processes a .NET `TextReader`. Its content is lazily read. </summary>
val _customized: Nonterminal<float>
val addBlockComment: commentStart: string -> commentEnd: string -> df: 'a -> 'a (requires 'a :> DesigntimeFarkle)
<summary> Adds a block comment to the given `DesigntimeFarkle`. </summary>
val addLineComment: commentStart: string -> df: 'a -> 'a (requires 'a :> DesigntimeFarkle)
<summary> Adds a line comment to the given `DesigntimeFarkle`. </summary>
val caseSensitive: flag: bool -> df: 'a -> 'a (requires 'a :> DesigntimeFarkle)
<summary> Sets the `CaseSensitive` field of a `DesigntimeFarkle`'s metadata. </summary>
val autoWhitespace: flag: bool -> df: 'a -> 'a (requires 'a :> DesigntimeFarkle)
<summary> Sets the `AutoWhitespace` field of a `DesigntimeFarkle`'s metadata. </summary>
val addNoiseSymbol: name: string -> regex: Regex -> df: 'a -> 'a (requires 'a :> DesigntimeFarkle)
<summary> Adds a name-`Regex` pair of noise symbols to the given `DesigntimeFarkle`. </summary>
val AllLetters: PredefinedSet