Header menu logo Fabulous.AST

Fabulous.AST

Contents

What is AST?

AST stands for Abstract Syntax Tree. It is a tree representation of the abstract syntactic structure of source code written in a programming language. It is used by compilers to analyze, transform, and generate code.

Why Use AST for Code Generation?

You can generate code by just using strings and string interpolation. But there are several reasons why you should not do that:

ASTs offer several benefits for code generation:

Code Generation Approaches

String Interpolation

This is a simple example of generating code using StringBuilder and string interpolation:

open System.Text
let code = StringBuilder()
code.AppendLine("module MyModule =")
code.AppendLine("    let x = 12")
code |> string |> printfn "%s"

// produces the following code:
module MyModule =
    let x = 12

Quote from fantomas: For mercy's sake don't use string concatenation when generating F# code, use Fantomas instead. It is battle tested and proven technology!

Compiler AST

The official F# compiler AST:

You can see a live example using Fantomas tools

open Fantomas.FCS.Syntax
open Fantomas.FCS.SyntaxTrivia
open Fantomas.FCS.Text
open Fantomas.FCS.Xml

#r "../src/Fabulous.AST/bin/Release/netstandard2.1/publish/Fantomas.FCS.dll"
#r "../src/Fabulous.AST/bin/Release/netstandard2.1/publish/Fantomas.Core.dll"

ParsedInput.ImplFile(
    ParsedImplFileInput.ParsedImplFileInput(
        fileName = "tmp.fsx",
        isScript = true,
        qualifiedNameOfFile = QualifiedNameOfFile.QualifiedNameOfFile(Ident("Tmp$fsx", Range.Zero)),
        scopedPragmas = [],
        hashDirectives = [],
        contents =
            [ SynModuleOrNamespace.SynModuleOrNamespace(
                  longId = [ Ident("Tmp", Range.Zero) ],
                  isRecursive = false,
                  kind = SynModuleOrNamespaceKind.AnonModule,
                  decls =
                      [ SynModuleDecl.Let(
                            isRecursive = false,
                            bindings =
                                [ SynBinding.SynBinding(
                                      accessibility = None,
                                      kind = SynBindingKind.Normal,
                                      isInline = false,
                                      isMutable = false,
                                      attributes = [],
                                      xmlDoc = PreXmlDoc.Empty,
                                      valData =
                                          SynValData.SynValData(
                                              memberFlags = None,
                                              valInfo =
                                                  SynValInfo.SynValInfo(
                                                      curriedArgInfos = [],
                                                      returnInfo =
                                                          SynArgInfo.SynArgInfo(
                                                              attributes = [],
                                                              optional = false,
                                                              ident = None
                                                          )
                                                  ),
                                              thisIdOpt = None
                                          ),
                                      headPat =
                                          SynPat.Named(
                                              ident = SynIdent.SynIdent(ident = Ident("x", Range.Zero), trivia = None),
                                              isThisVal = false,
                                              accessibility = None,
                                              range = Range.Zero
                                          ),
                                      returnInfo = None,
                                      expr = SynExpr.Const(constant = SynConst.Int32(12), range = Range.Zero),
                                      range = Range.Zero,
                                      debugPoint = DebugPointAtBinding.Yes(Range.Zero),
                                      trivia =
                                          { LeadingKeyword = SynLeadingKeyword.Let(Range.Zero)
                                            InlineKeyword = None
                                            EqualsRange = Some(Range.Zero) }
                                  ) ],
                            range = Range.Zero
                        ) ],
                  xmlDoc = PreXmlDoc.Empty,
                  attribs = [],
                  accessibility = None,
                  range = Range.Zero,
                  trivia = { LeadingKeyword = SynModuleOrNamespaceLeadingKeyword.None }
              ) ],
        flags = (false, false),
        trivia =
            { ConditionalDirectives = []
              CodeComments = [] },
        identifiers = set []
    )
)

// produces the following code:
let x = 12

Fantomas Oak AST

It is a simplified version of the official AST that is used by Fantomas to format F# code.

You can see a live example using the online tool

#r "../src/Fabulous.AST/bin/Release/netstandard2.1/publish/Fantomas.FCS.dll"
#r "../src/Fabulous.AST/bin/Release/netstandard2.1/publish/Fantomas.Core.dll"

open Fantomas.FCS.Text
open Fantomas.Core
open Fantomas.Core.SyntaxOak

Oak(
    [],
    [ ModuleOrNamespaceNode(
          None,
          [ BindingNode(
                None,
                None,
                MultipleTextsNode([ SingleTextNode("let", Range.Zero) ], Range.Zero),
                false,
                None,
                None,
                Choice1Of2(IdentListNode([ IdentifierOrDot.Ident(SingleTextNode("x", Range.Zero)) ], Range.Zero)),
                None,
                [],
                None,
                SingleTextNode("=", Range.Zero),
                Expr.Constant(Constant.FromText(SingleTextNode("12", Range.Zero))),
                Range.Zero
            )
            |> ModuleDecl.TopLevelBinding ],
          Range.Zero
      ) ],
    Range.Zero
)
|> CodeFormatter.FormatOakAsync
|> Async.RunSynchronously
|> printfn "%s"

// produces the following code:
let x = 12

Fabulous.AST DSL

Fabulous.AST provides a more user-friendly API to generate code using ASTs. It's built on top of Fantomas Oak AST and offers a more concise and easier-to-use API for code generation. It dramatically reduces the boilerplate code required to generate F# code.

You can configure code formatting using FormatConfig:

type FormatConfig =
    { IndentSize: Num
      MaxLineLength: Num
      EndOfLine: EndOfLineStyle
      InsertFinalNewline: bool
      SpaceBeforeParameter: bool
      SpaceBeforeLowercaseInvocation: bool
      SpaceBeforeUppercaseInvocation: bool
      SpaceBeforeClassConstructor: bool
      SpaceBeforeMember: bool
      SpaceBeforeColon: bool }

Here's the same example using Fabulous.AST:

#r "../src/Fabulous.AST/bin/Release/netstandard2.1/publish/Fabulous.AST.dll"
#r "../src/Fabulous.AST/bin/Release/netstandard2.1/publish/Fantomas.FCS.dll"

open Fabulous.AST
open type Fabulous.AST.Ast

Oak() { AnonymousModule() { Value("x", "12") } }
|> Gen.mkOak
|> Gen.run
|> printfn "%s"
// produces the following code:
let x = 12

Getting Started

To start using Fabulous.AST, first install the NuGet package:

dotnet add package Fabulous.AST

Then, in your code:

open Fabulous.AST
open type Fabulous.AST.Ast

// Generate a simple module with a value
let code = 
    Oak() { 
        AnonymousModule() { 
            Value("x", Int(42)) 
        } 
    }
    |> Gen.mkOak
    |> Gen.run

printfn "%s" code

Documentation Structure

Fabulous.AST documentation is organized by F# language features. Each page focuses on one specific aspect of F# code generation:

Each documentation page follows a consistent structure:

  1. Overview: Brief explanation of the concept
  2. Basic Usage: Simple examples of the most common usage
  3. API Reference: Available widget constructors and modifiers
  4. Examples: Practical examples showing different use cases
  5. Advanced Topics: More complex scenarios and customizations

What Widgets to Use to Generate Code?

Fabulous.AST maps to the Fantomas Oak AST nodes. You can use the online tool to examine the AST nodes and then use the corresponding widgets to generate the code.

For example, the following Oak AST node:

Oak (1,0-1,10)
    ModuleOrNamespaceNode (1,0-1,10)
        BindingNode (1,0-1,10)
            MultipleTextsNode (1,0-1,3)
                let (1,0-1,3)
            IdentListNode (1,4-1,5)
                x (1,4-1,5)
            = (1,6-1,7)
            12 (1,8-1,10)

Translates to the following Fabulous.AST code:

Oak() {
    AnonymousModule() {
        Value("x", "12")
    }
}

We've reduced the boilerplate code from 70 lines to just 5 lines of code, making it much easier to read and understand.

namespace System
namespace System.Text
val code: StringBuilder
Multiple items
type StringBuilder = interface ISerializable new: unit -> unit + 5 overloads member Append: value: bool -> StringBuilder + 25 overloads member AppendFormat: provider: IFormatProvider * format: string * arg0: obj -> StringBuilder + 12 overloads member AppendJoin: separator: char * [<ParamArray>] values: obj array -> StringBuilder + 5 overloads member AppendLine: unit -> StringBuilder + 3 overloads member Clear: unit -> StringBuilder member CopyTo: sourceIndex: int * destination: char array * destinationIndex: int * count: int -> unit + 1 overload member EnsureCapacity: capacity: int -> int member Equals: span: ReadOnlySpan<char> -> bool + 1 overload ...
<summary>Represents a mutable string of characters. This class cannot be inherited.</summary>

--------------------
StringBuilder() : StringBuilder
StringBuilder(capacity: int) : StringBuilder
StringBuilder(value: string) : StringBuilder
StringBuilder(capacity: int, maxCapacity: int) : StringBuilder
StringBuilder(value: string, capacity: int) : StringBuilder
StringBuilder(value: string, startIndex: int, length: int, capacity: int) : StringBuilder
StringBuilder.AppendLine() : StringBuilder
StringBuilder.AppendLine(handler: byref<StringBuilder.AppendInterpolatedStringHandler>) : StringBuilder
StringBuilder.AppendLine(value: string) : StringBuilder
StringBuilder.AppendLine(provider: System.IFormatProvider, handler: byref<StringBuilder.AppendInterpolatedStringHandler>) : StringBuilder
Multiple items
val string: value: 'T -> string

--------------------
type string = System.String
val printfn: format: Printf.TextWriterFormat<'T> -> 'T
namespace Fantomas
namespace Fantomas.FCS
namespace Fantomas.FCS.Syntax
namespace Fantomas.FCS.SyntaxTrivia
namespace Fantomas.FCS.Text
namespace Fantomas.FCS.Xml
type ParsedInput = | ImplFile of ParsedImplFileInput | SigFile of ParsedSigFileInput member FileName: string member Identifiers: Set<string> member QualifiedName: QualifiedNameOfFile member Range: range member ScopedPragmas: ScopedPragma list
union case ParsedInput.ImplFile: ParsedImplFileInput -> ParsedInput
Multiple items
union case ParsedImplFileInput.ParsedImplFileInput: fileName: string * isScript: bool * qualifiedNameOfFile: QualifiedNameOfFile * scopedPragmas: ScopedPragma list * hashDirectives: ParsedHashDirective list * contents: SynModuleOrNamespace list * flags: bool * bool * trivia: ParsedImplFileInputTrivia * identifiers: Set<string> -> ParsedImplFileInput

--------------------
type ParsedImplFileInput = | ParsedImplFileInput of fileName: string * isScript: bool * qualifiedNameOfFile: QualifiedNameOfFile * scopedPragmas: ScopedPragma list * hashDirectives: ParsedHashDirective list * contents: SynModuleOrNamespace list * flags: bool * bool * trivia: ParsedImplFileInputTrivia * identifiers: Set<string> member Contents: SynModuleOrNamespace list member FileName: string member HashDirectives: ParsedHashDirective list member IsExe: bool member IsLastCompiland: bool member IsScript: bool member QualifiedName: QualifiedNameOfFile member ScopedPragmas: ScopedPragma list member Trivia: ParsedImplFileInputTrivia
union case ParsedImplFileInput.ParsedImplFileInput: fileName: string * isScript: bool * qualifiedNameOfFile: QualifiedNameOfFile * scopedPragmas: ScopedPragma list * hashDirectives: ParsedHashDirective list * contents: SynModuleOrNamespace list * flags: bool * bool * trivia: ParsedImplFileInputTrivia * identifiers: Set<string> -> ParsedImplFileInput
Multiple items
union case QualifiedNameOfFile.QualifiedNameOfFile: Ident -> QualifiedNameOfFile

--------------------
type QualifiedNameOfFile = | QualifiedNameOfFile of Ident member Id: Ident member Range: range member Text: string
union case QualifiedNameOfFile.QualifiedNameOfFile: Ident -> QualifiedNameOfFile
Multiple items
[<Struct>] type Ident = new: text: string * range: range -> Ident member idRange: range member idText: string

--------------------
Ident ()
new: text: string * range: range -> Ident
Multiple items
module Range from Fantomas.FCS.Text

--------------------
[<Struct>] type Range = member End: pos member EndColumn: int member EndLine: int member EndRange: range member FileName: string member IsSynthetic: bool member Start: pos member StartColumn: int member StartLine: int member StartRange: range ...
property Range.Zero: range with get
Multiple items
union case SynModuleOrNamespace.SynModuleOrNamespace: longId: LongIdent * isRecursive: bool * kind: SynModuleOrNamespaceKind * decls: SynModuleDecl list * xmlDoc: PreXmlDoc * attribs: SynAttributes * accessibility: SynAccess option * range: range * trivia: SynModuleOrNamespaceTrivia -> SynModuleOrNamespace

--------------------
type SynModuleOrNamespace = | SynModuleOrNamespace of longId: LongIdent * isRecursive: bool * kind: SynModuleOrNamespaceKind * decls: SynModuleDecl list * xmlDoc: PreXmlDoc * attribs: SynAttributes * accessibility: SynAccess option * range: range * trivia: SynModuleOrNamespaceTrivia member Range: range
union case SynModuleOrNamespace.SynModuleOrNamespace: longId: LongIdent * isRecursive: bool * kind: SynModuleOrNamespaceKind * decls: SynModuleDecl list * xmlDoc: PreXmlDoc * attribs: SynAttributes * accessibility: SynAccess option * range: range * trivia: SynModuleOrNamespaceTrivia -> SynModuleOrNamespace
[<Struct>] type SynModuleOrNamespaceKind = | NamedModule | AnonModule | DeclaredNamespace | GlobalNamespace member Equals: SynModuleOrNamespaceKind * IEqualityComparer -> bool member IsModule: bool
union case SynModuleOrNamespaceKind.AnonModule: SynModuleOrNamespaceKind
type SynModuleDecl = | ModuleAbbrev of ident: Ident * longId: LongIdent * range: range | NestedModule of moduleInfo: SynComponentInfo * isRecursive: bool * decls: SynModuleDecl list * isContinuing: bool * range: range * trivia: SynModuleDeclNestedModuleTrivia | Let of isRecursive: bool * bindings: SynBinding list * range: range | Expr of expr: SynExpr * range: range | Types of typeDefns: SynTypeDefn list * range: range | Exception of exnDefn: SynExceptionDefn * range: range | Open of target: SynOpenDeclTarget * range: range | Attributes of attributes: SynAttributes * range: range | HashDirective of hashDirective: ParsedHashDirective * range: range | NamespaceFragment of fragment: SynModuleOrNamespace member Range: range
union case SynModuleDecl.Let: isRecursive: bool * bindings: SynBinding list * range: range -> SynModuleDecl
Multiple items
union case SynBinding.SynBinding: accessibility: SynAccess option * kind: SynBindingKind * isInline: bool * isMutable: bool * attributes: SynAttributes * xmlDoc: PreXmlDoc * valData: SynValData * headPat: SynPat * returnInfo: SynBindingReturnInfo option * expr: SynExpr * range: range * debugPoint: DebugPointAtBinding * trivia: SynBindingTrivia -> SynBinding

--------------------
type SynBinding = | SynBinding of accessibility: SynAccess option * kind: SynBindingKind * isInline: bool * isMutable: bool * attributes: SynAttributes * xmlDoc: PreXmlDoc * valData: SynValData * headPat: SynPat * returnInfo: SynBindingReturnInfo option * expr: SynExpr * range: range * debugPoint: DebugPointAtBinding * trivia: SynBindingTrivia member RangeOfBindingWithRhs: range member RangeOfBindingWithoutRhs: range member RangeOfHeadPattern: range
union case SynBinding.SynBinding: accessibility: SynAccess option * kind: SynBindingKind * isInline: bool * isMutable: bool * attributes: SynAttributes * xmlDoc: PreXmlDoc * valData: SynValData * headPat: SynPat * returnInfo: SynBindingReturnInfo option * expr: SynExpr * range: range * debugPoint: DebugPointAtBinding * trivia: SynBindingTrivia -> SynBinding
union case Option.None: Option<'T>
type SynBindingKind = | StandaloneExpression | Normal | Do member Equals: SynBindingKind * IEqualityComparer -> bool
union case SynBindingKind.Normal: SynBindingKind
type PreXmlDoc = member ToXmlDoc: check: bool * paramNamesOpt: string list option -> XmlDoc static member Create: unprocessedLines: string array * range: range -> PreXmlDoc static member Merge: a: PreXmlDoc -> b: PreXmlDoc -> PreXmlDoc member IsEmpty: bool member Range: Range static member Empty: PreXmlDoc
property PreXmlDoc.Empty: PreXmlDoc with get
Multiple items
union case SynValData.SynValData: memberFlags: SynMemberFlags option * valInfo: SynValInfo * thisIdOpt: Ident option -> SynValData

--------------------
type SynValData = | SynValData of memberFlags: SynMemberFlags option * valInfo: SynValInfo * thisIdOpt: Ident option member SynValInfo: SynValInfo
union case SynValData.SynValData: memberFlags: SynMemberFlags option * valInfo: SynValInfo * thisIdOpt: Ident option -> SynValData
Multiple items
union case SynValInfo.SynValInfo: curriedArgInfos: SynArgInfo list list * returnInfo: SynArgInfo -> SynValInfo

--------------------
type SynValInfo = | SynValInfo of curriedArgInfos: SynArgInfo list list * returnInfo: SynArgInfo member ArgNames: string list member CurriedArgInfos: SynArgInfo list list
union case SynValInfo.SynValInfo: curriedArgInfos: SynArgInfo list list * returnInfo: SynArgInfo -> SynValInfo
Multiple items
union case SynArgInfo.SynArgInfo: attributes: SynAttributes * optional: bool * ident: Ident option -> SynArgInfo

--------------------
type SynArgInfo = | SynArgInfo of attributes: SynAttributes * optional: bool * ident: Ident option member Attributes: SynAttributes member Ident: Ident option
union case SynArgInfo.SynArgInfo: attributes: SynAttributes * optional: bool * ident: Ident option -> SynArgInfo
type SynPat = | Const of constant: SynConst * range: range | Wild of range: range | Named of ident: SynIdent * isThisVal: bool * accessibility: SynAccess option * range: range | Typed of pat: SynPat * targetType: SynType * range: range | Attrib of pat: SynPat * attributes: SynAttributes * range: range | Or of lhsPat: SynPat * rhsPat: SynPat * range: range * trivia: SynPatOrTrivia | ListCons of lhsPat: SynPat * rhsPat: SynPat * range: range * trivia: SynPatListConsTrivia | Ands of pats: SynPat list * range: range | As of lhsPat: SynPat * rhsPat: SynPat * range: range | LongIdent of longDotId: SynLongIdent * extraId: Ident option * typarDecls: SynValTyparDecls option * argPats: SynArgPats * accessibility: SynAccess option * range: range ... member Range: range
union case SynPat.Named: ident: SynIdent * isThisVal: bool * accessibility: SynAccess option * range: range -> SynPat
Multiple items
union case SynIdent.SynIdent: ident: Ident * trivia: IdentTrivia option -> SynIdent

--------------------
type SynIdent = | SynIdent of ident: Ident * trivia: IdentTrivia option member Range: range
union case SynIdent.SynIdent: ident: Ident * trivia: IdentTrivia option -> SynIdent
type range = Range
type SynExpr = | Paren of expr: SynExpr * leftParenRange: range * rightParenRange: range option * range: range | Quote of operator: SynExpr * isRaw: bool * quotedExpr: SynExpr * isFromQueryExpression: bool * range: range | Const of constant: SynConst * range: range | Typed of expr: SynExpr * targetType: SynType * range: range | Tuple of isStruct: bool * exprs: SynExpr list * commaRanges: range list * range: range | AnonRecd of isStruct: bool * copyInfo: (SynExpr * BlockSeparator) option * recordFields: (SynLongIdent * range option * SynExpr) list * range: range * trivia: SynExprAnonRecdTrivia | ArrayOrList of isArray: bool * exprs: SynExpr list * range: range | Record of baseInfo: (SynType * SynExpr * range * BlockSeparator option * range) option * copyInfo: (SynExpr * BlockSeparator) option * recordFields: SynExprRecordField list * range: range | New of isProtected: bool * targetType: SynType * expr: SynExpr * range: range | ObjExpr of objType: SynType * argOptions: (SynExpr * Ident option) option * withKeyword: range option * bindings: SynBinding list * members: SynMemberDefns * extraImpls: SynInterfaceImpl list * newExprRange: range * range: range ... member IsArbExprAndThusAlreadyReportedError: bool member Range: range member RangeOfFirstPortion: range member RangeWithoutAnyExtraDot: range
union case SynExpr.Const: constant: SynConst * range: range -> SynExpr
type SynConst = | Unit | Bool of bool | SByte of sbyte | Byte of byte | Int16 of int16 | UInt16 of uint16 | Int32 of int32 | UInt32 of uint32 | Int64 of int64 | UInt64 of uint64 ... member Range: dflt: range -> range
union case SynConst.Int32: int32 -> SynConst
type DebugPointAtBinding = | Yes of range: range | NoneAtDo | NoneAtLet | NoneAtSticky | NoneAtInvisible member Combine: y: DebugPointAtBinding -> DebugPointAtBinding member Equals: DebugPointAtBinding * IEqualityComparer -> bool
union case DebugPointAtBinding.Yes: range: range -> DebugPointAtBinding
type SynLeadingKeyword = | Let of letRange: range | LetRec of letRange: range * recRange: range | And of andRange: range | Use of useRange: range | UseRec of useRange: range * recRange: range | Extern of externRange: range | Member of memberRange: range | MemberVal of memberRange: range * valRange: range | Override of overrideRange: range | OverrideVal of overrideRange: range * valRange: range ... member Range: range
union case SynLeadingKeyword.Let: letRange: range -> SynLeadingKeyword
union case Option.Some: Value: 'T -> Option<'T>
type SynModuleOrNamespaceLeadingKeyword = | Module of moduleRange: range | Namespace of namespaceRange: range | None
union case SynModuleOrNamespaceLeadingKeyword.None: SynModuleOrNamespaceLeadingKeyword
val set: elements: 'T seq -> Set<'T> (requires comparison)
val x: int
namespace Fantomas.Core
module SyntaxOak from Fantomas.Core
Multiple items
type Oak = inherit NodeBase new: parsedHashDirectives: ParsedHashDirectiveNode list * modulesOrNamespaces: ModuleOrNamespaceNode list * m: range -> Oak override Children: Node array member ModulesOrNamespaces: ModuleOrNamespaceNode list member ParsedHashDirectives: ParsedHashDirectiveNode list

--------------------
new: parsedHashDirectives: ParsedHashDirectiveNode list * modulesOrNamespaces: ModuleOrNamespaceNode list * m: range -> Oak
Multiple items
type ModuleOrNamespaceNode = inherit NodeBase new: header: ModuleOrNamespaceHeaderNode option * decls: ModuleDecl list * range: range -> ModuleOrNamespaceNode override Children: Node array member Declarations: ModuleDecl list member Header: ModuleOrNamespaceHeaderNode option member IsNamed: bool

--------------------
new: header: ModuleOrNamespaceHeaderNode option * decls: ModuleDecl list * range: range -> ModuleOrNamespaceNode
Multiple items
type BindingNode = inherit NodeBase new: xmlDoc: XmlDocNode option * attributes: MultipleAttributeListNode option * leadingKeyword: MultipleTextsNode * isMutable: bool * inlineNode: SingleTextNode option * accessibility: SingleTextNode option * functionName: Choice<IdentListNode,Pattern> * genericTypeParameters: TyparDecls option * parameters: Pattern list * returnType: BindingReturnInfoNode option * equals: SingleTextNode * expr: Expr * range: range -> BindingNode member Accessibility: SingleTextNode option member Attributes: MultipleAttributeListNode option override Children: Node array member Equals: SingleTextNode member Expr: Expr member FunctionName: Choice<IdentListNode,Pattern> member GenericTypeParameters: TyparDecls option member Inline: SingleTextNode option ...

--------------------
new: xmlDoc: XmlDocNode option * attributes: MultipleAttributeListNode option * leadingKeyword: MultipleTextsNode * isMutable: bool * inlineNode: SingleTextNode option * accessibility: SingleTextNode option * functionName: Choice<IdentListNode,Pattern> * genericTypeParameters: TyparDecls option * parameters: Pattern list * returnType: BindingReturnInfoNode option * equals: SingleTextNode * expr: Expr * range: range -> BindingNode
Multiple items
type MultipleTextsNode = inherit NodeBase new: content: SingleTextNode list * range: range -> MultipleTextsNode override Children: Node array member Content: SingleTextNode list

--------------------
new: content: SingleTextNode list * range: range -> MultipleTextsNode
Multiple items
type SingleTextNode = inherit NodeBase new: idText: string * range: range -> SingleTextNode override Children: Node array member Text: string

--------------------
new: idText: string * range: range -> SingleTextNode
union case Choice.Choice1Of2: 'T1 -> Choice<'T1,'T2>
Multiple items
type IdentListNode = inherit NodeBase new: content: IdentifierOrDot list * range: range -> IdentListNode override Children: Node array member Content: IdentifierOrDot list member IsEmpty: bool static member Empty: IdentListNode

--------------------
new: content: IdentifierOrDot list * range: range -> IdentListNode
type IdentifierOrDot = | Ident of SingleTextNode | KnownDot of SingleTextNode | UnknownDot member Equals: IdentifierOrDot * IEqualityComparer -> bool member Range: range option
union case IdentifierOrDot.Ident: SingleTextNode -> IdentifierOrDot
type Expr = | Lazy of ExprLazyNode | Single of ExprSingleNode | Constant of Constant | Null of SingleTextNode | Quote of ExprQuoteNode | Typed of ExprTypedNode | New of ExprNewNode | Tuple of ExprTupleNode | StructTuple of ExprStructTupleNode | ArrayOrList of ExprArrayOrListNode ... static member Node: x: Expr -> Node member HasParentheses: bool
union case Expr.Constant: Constant -> Expr
type Constant = | FromText of SingleTextNode | Unit of UnitNode | Measure of ConstantMeasureNode static member Node: c: Constant -> NodeBase
union case Constant.FromText: SingleTextNode -> Constant
type ModuleDecl = | OpenList of OpenListNode | HashDirectiveList of HashDirectiveListNode | Attributes of ModuleDeclAttributesNode | DeclExpr of Expr | Exception of ExceptionDefnNode | ExternBinding of ExternBindingNode | TopLevelBinding of BindingNode | ModuleAbbrev of ModuleAbbrevNode | NestedModule of NestedModuleNode | TypeDefn of TypeDefn ... static member Node: x: ModuleDecl -> Node
union case ModuleDecl.TopLevelBinding: BindingNode -> ModuleDecl
type CodeFormatter = static member FormatASTAsync: ast: ParsedInput -> Async<string> + 2 overloads static member FormatDocumentAsync: isSignature: bool * source: string -> Async<FormatResult> + 2 overloads static member FormatOakAsync: oak: Oak -> Async<string> + 1 overload static member FormatSelectionAsync: isSignature: bool * source: string * selection: range -> Async<string * range> + 1 overload static member GetVersion: unit -> string static member IsValidFSharpCodeAsync: isSignature: bool * source: string -> Async<bool> static member MakePosition: line: int * column: int -> pos static member MakeRange: fileName: string * startLine: int * startCol: int * endLine: int * endCol: int -> range static member ParseAsync: isSignature: bool * source: string -> Async<(ParsedInput * string list) array> static member ParseOakAsync: isSignature: bool * source: string -> Async<(Oak * string list) array> ...
static member CodeFormatter.FormatOakAsync: oak: Oak -> Async<string>
static member CodeFormatter.FormatOakAsync: oak: Oak * config: FormatConfig -> Async<string>
Multiple items
module Async from Fantomas.Core

--------------------
type Async = static member AsBeginEnd: computation: ('Arg -> Async<'T>) -> ('Arg * AsyncCallback * obj -> IAsyncResult) * (IAsyncResult -> 'T) * (IAsyncResult -> unit) static member AwaitEvent: event: IEvent<'Del,'T> * ?cancelAction: (unit -> unit) -> Async<'T> (requires delegate and 'Del :> Delegate) static member AwaitIAsyncResult: iar: IAsyncResult * ?millisecondsTimeout: int -> Async<bool> static member AwaitTask: task: Task<'T> -> Async<'T> + 1 overload static member AwaitWaitHandle: waitHandle: WaitHandle * ?millisecondsTimeout: int -> Async<bool> static member CancelDefaultToken: unit -> unit static member Catch: computation: Async<'T> -> Async<Choice<'T,exn>> static member Choice: computations: Async<'T option> seq -> Async<'T option> static member FromBeginEnd: beginAction: (AsyncCallback * obj -> IAsyncResult) * endAction: (IAsyncResult -> 'T) * ?cancelAction: (unit -> unit) -> Async<'T> + 3 overloads static member FromContinuations: callback: (('T -> unit) * (exn -> unit) * (OperationCanceledException -> unit) -> unit) -> Async<'T> ...

--------------------
type Async<'T>
static member Async.RunSynchronously: computation: Async<'T> * ?timeout: int * ?cancellationToken: System.Threading.CancellationToken -> 'T
type FormatConfig = { IndentSize: obj MaxLineLength: obj EndOfLine: obj InsertFinalNewline: bool SpaceBeforeParameter: bool SpaceBeforeLowercaseInvocation: bool SpaceBeforeUppercaseInvocation: bool SpaceBeforeClassConstructor: bool SpaceBeforeMember: bool SpaceBeforeColon: bool }
type bool = System.Boolean
namespace Fabulous
namespace Fabulous.AST
type Ast = class end
Multiple items
static member Ast.Oak: unit -> CollectionBuilder<Oak,'marker>

--------------------
module Oak from Fabulous.AST

--------------------
type Oak = inherit NodeBase new: parsedHashDirectives: ParsedHashDirectiveNode list * modulesOrNamespaces: ModuleOrNamespaceNode list * m: range -> Oak override Children: Node array member ModulesOrNamespaces: ModuleOrNamespaceNode list member ParsedHashDirectives: ParsedHashDirectiveNode list

--------------------
new: parsedHashDirectives: ParsedHashDirectiveNode list * modulesOrNamespaces: ModuleOrNamespaceNode list * m: range -> Oak
static member Ast.AnonymousModule: unit -> CollectionBuilder<ModuleOrNamespaceNode,ModuleDecl>
static member Ast.Value: name: string * value: string * returnType: string -> WidgetBuilder<BindingNode>
   (+0 other overloads)
static member Ast.Value: name: string * value: string * returnType: WidgetBuilder<Type> -> WidgetBuilder<BindingNode>
   (+0 other overloads)
static member Ast.Value: name: string * value: string -> WidgetBuilder<BindingNode>
   (+0 other overloads)
static member Ast.Value: name: string * value: WidgetBuilder<Constant> * returnType: string -> WidgetBuilder<BindingNode>
   (+0 other overloads)
static member Ast.Value: name: string * value: WidgetBuilder<Constant> * returnType: WidgetBuilder<Type> -> WidgetBuilder<BindingNode>
   (+0 other overloads)
static member Ast.Value: name: string * value: WidgetBuilder<Constant> -> WidgetBuilder<BindingNode>
   (+0 other overloads)
static member Ast.Value: name: string * value: WidgetBuilder<Expr> * returnType: string -> WidgetBuilder<BindingNode>
   (+0 other overloads)
static member Ast.Value: name: string * value: WidgetBuilder<Expr> * returnType: WidgetBuilder<Type> -> WidgetBuilder<BindingNode>
   (+0 other overloads)
static member Ast.Value: name: string * value: WidgetBuilder<Expr> -> WidgetBuilder<BindingNode>
   (+0 other overloads)
static member Ast.Value: name: WidgetBuilder<Constant> * value: WidgetBuilder<Constant> * returnType: string -> WidgetBuilder<BindingNode>
   (+0 other overloads)
module Gen from Fabulous.AST
<summary> It takes the root of the widget tree and create the corresponding Fantomas node, and recursively creating all children nodes </summary>
val mkOak: root: WidgetBuilder<'node> -> 'node
val run: oak: Oak -> string
val code: string

Type something to start searching.