8 people like it.

Simple C# Parser

Simple prototype C# AST and parser using the FParsec parser combinator library. Parses a subset of C# 1.1 constructs.

Abstract Syntax Tree

 1: 
 2: 
 3: 
 4: 
 5: 
 6: 
 7: 
 8: 
 9: 
10: 
11: 
12: 
13: 
14: 
15: 
16: 
17: 
18: 
19: 
20: 
21: 
22: 
23: 
24: 
25: 
26: 
27: 
28: 
29: 
30: 
31: 
32: 
33: 
34: 
35: 
36: 
37: 
38: 
39: 
40: 
41: 
42: 
43: 
44: 
45: 
46: 
47: 
48: 
49: 
50: 
51: 
52: 
53: 
54: 
55: 
56: 
57: 
58: 
59: 
60: 
type Name = string
type VarName = Name
type TypeName = Name
type MemberName = Name
type LabelName = Name
type Arg = Arg of TypeName * VarName
type Value = obj
type EnumValue = Name * Value
type Import = 
    | Import of Name
    | Abbreviation of Name * Name
type Access = Public | Private | Protected | Internal
type Modifier = Sealed | Static
type Expr = 
    | Literal of Value
    | Variable of VarName
    | MethodInvoke of MemberName * Expr list
    | PropertyGet of MemberName
    | InfixOperator of Expr * string * Expr
    | PrefixOperator of string * Expr
    | PostfixOperator of Expr * string
    | TernaryOperator of Expr * Expr * Expr
type From = TypeName * Name * Expr
type To = Expr
type Step = Expr list
type Statement =
    | Define of TypeName * VarName
    | Assignment of VarName * Expr
    | PropertySet of MemberName * Expr
    | If of Expr * Block
    | Else of Expr * Block
    | Switch of Expr * Case list
    | For of From * To * Step * Block
    | ForEach of TypeName * VarName * Expr    
    | While of Expr * Statement list
    | DoWhile of Statement List * Expr
    | Try of Statement list
    | Catch of TypeName * Block
    | Finally of TypeName * Block
    | Lock of Expr * Block    
    | Using of Expr * Block
    | Label of LabelName
    | Goto of LabelName
    | Break
    | Continue
    | Return of Expr
and Case = Case of Value option * Block
and Block = Statement list
type MemberInfo = MemberInfo of Access * Modifier option * TypeName * Name
type Member =
    | Field of MemberInfo * Expr option
    | Method of MemberInfo * Arg list * Block
    | Property of MemberInfo * Block
type CSharpType = 
    | Class of Access * Modifier option * Name * Member list
    | Struct of Access * Name * Member list
    | Enum of Access * TypeName * EnumValue list
type Scope =
    | Namespace of Import list * Name * Scope list
    | Types of Import list * CSharpType list

Parser

 1: 
 2: 
 3: 
 4: 
 5: 
 6: 
 7: 
 8: 
 9: 
10: 
11: 
12: 
13: 
14: 
15: 
16: 
17: 
18: 
19: 
20: 
21: 
22: 
23: 
24: 
25: 
26: 
27: 
28: 
29: 
30: 
31: 
32: 
33: 
34: 
35: 
36: 
37: 
38: 
39: 
40: 
41: 
42: 
43: 
44: 
45: 
46: 
47: 
48: 
49: 
50: 
51: 
52: 
53: 
54: 
55: 
56: 
57: 
58: 
59: 
60: 
61: 
62: 
63: 
64: 
65: 
66: 
67: 
68: 
69: 
70: 
71: 
72: 
73: 
74: 
75: 
76: 
77: 
78: 
79: 
80: 
81: 
82: 
83: 
84: 
85: 
open FParsec

let ws = spaces
let str_ws s = pstring s .>> ws
let str_ws1 s = pstring s .>> spaces1

type Lit = NumberLiteralOptions
let numberFormat = Lit.AllowMinusSign ||| Lit.AllowFraction ||| Lit.AllowExponent
let pnumber : Parser<Expr, unit> =
    numberLiteral numberFormat "number"
    |>> fun nl ->
            if nl.IsInteger then Literal(int nl.String)
            else Literal(float nl.String)

let pidentifier =
    let isIdentifierFirstChar c = isLetter c || c = '_'
    let isIdentifierChar c = isLetter c || isDigit c || c = '_'
    many1Satisfy2L isIdentifierFirstChar isIdentifierChar "identifier"
let pidentifier_ws = pidentifier .>> ws
let pvar = pidentifier |>> (fun x -> Variable(x))
let pexpr = pnumber <|> pvar

let passign = pipe3 pidentifier_ws (str_ws "=") pexpr
               (fun var _ expr -> Assignment(var,expr))

let pstatement = passign .>> str_ws ";"

let ppublic = str_ws1 "public" |>> (fun _ -> Public)
let pprivate = str_ws1 "private" |>> (fun _ -> Private)
let pprotected = str_ws1 "protected" |>> (fun _ -> Protected)
let pinternal = str_ws1 "internal" |>> (fun _ -> Internal)
let paccess = 
    opt (ppublic <|> pprivate <|> pprotected <|> pinternal)
    |>> (fun access -> defaultArg access Internal)
let psealed = str_ws1 "sealed" |>> (fun _ -> Sealed)
let pstatic = str_ws1 "static" |>> (fun _ -> Static)
let pmodifier = psealed <|> pstatic

let pstatementblock = between (str_ws "{") (str_ws "}") (many pstatement) 

let parg = pipe2 pidentifier_ws pidentifier_ws (fun ty name -> Arg(ty,name)) 
let pargs = str_ws "(" >>. sepBy parg (str_ws ",") .>> str_ws ")"

let pmemberinfo = 
    pipe4 paccess (opt pmodifier) pidentifier_ws pidentifier_ws
     (fun access modifier ty name -> MemberInfo(access,modifier,ty,name))

let pfield = pmemberinfo .>> str_ws ";" |>> (fun mi -> Field(mi, None))
let pproperty = 
    pipe2 pmemberinfo pstatementblock (fun mi block -> Property(mi,block))
let pmethod =
    pipe3 pmemberinfo pargs pstatementblock 
     (fun mi args block -> Method(mi,args,block))

let pmember = attempt pfield <|> attempt pproperty <|> attempt pmethod

let pmemberblock = between (str_ws "{") (str_ws "}") (many pmember) 
                   |>> (fun members -> members)
let penumblock = between (str_ws "{") (str_ws "}") ws |>> (fun _ -> [])

let pclass = 
    pipe5 paccess (opt pmodifier) (str_ws1 "class") pidentifier_ws pmemberblock
     (fun access modifier _ name block -> Class(access, modifier, name, block))
let pstruct =
    pipe4 paccess (str_ws1 "struct") pidentifier_ws pmemberblock
     (fun access _ name block -> Struct(access, name, block))
let penum =
    pipe4 paccess (str_ws1 "enum") pidentifier_ws penumblock
     (fun access _ name block -> Struct(access, name, block))
let ptypedeclaration = pclass <|> pstruct <|> penum

let pscope, pscopeimpl = createParserForwardedToRef()

let pscopesblock = between (str_ws "{") (str_ws "}") (many pscope) |>> (fun scopes -> scopes)

let pimport = str_ws1 "using" >>. pidentifier .>> str_ws ";" |>> (fun name -> Import(name))
let pnsblock =
    pipe3 (many pimport) (str_ws1 "namespace" >>. pidentifier_ws) pscopesblock
     (fun imports name block -> 
        let types = Types([],[])
        Namespace(imports,name,block))
let ptypes = 
    pipe2 (many pimport) (many1 ptypedeclaration)
     (fun imports classes -> Types(imports, classes))
pscopeimpl := pnsblock <|> (ptypes)

Example

 1: 
 2: 
 3: 
 4: 
 5: 
 6: 
 7: 
 8: 
 9: 
10: 
11: 
12: 
13: 
14: 
15: 
16: 
17: 
let program = """using X; 
using Y; 
namespace A { 
  namespace B { 
  class A { 
    float x;
    void foo(string arg) { 
      x = 1;
    }
  } 
  struct B { } 
  enum C { }
  } 
}
"""

run pscope program
Multiple items
val string : value:'T -> string

Full name: Microsoft.FSharp.Core.Operators.string

--------------------
type string = System.String

Full name: Microsoft.FSharp.Core.string
type VarName = Name

Full name: Script.VarName
type Name = string

Full name: Script.Name
type TypeName = Name

Full name: Script.TypeName
type MemberName = Name

Full name: Script.MemberName
type LabelName = Name

Full name: Script.LabelName
Multiple items
union case Arg.Arg: TypeName * VarName -> Arg

--------------------
type Arg = | Arg of TypeName * VarName

Full name: Script.Arg
type Value = obj

Full name: Script.Value
type obj = System.Object

Full name: Microsoft.FSharp.Core.obj
type EnumValue = Name * Value

Full name: Script.EnumValue
Multiple items
union case Import.Import: Name -> Import

--------------------
type Import =
  | Import of Name
  | Abbreviation of Name * Name

Full name: Script.Import
union case Import.Abbreviation: Name * Name -> Import
type Access =
  | Public
  | Private
  | Protected
  | Internal

Full name: Script.Access
union case Access.Public: Access
union case Access.Private: Access
union case Access.Protected: Access
union case Access.Internal: Access
type Modifier =
  | Sealed
  | Static

Full name: Script.Modifier
Multiple items
union case Modifier.Sealed: Modifier

--------------------
type SealedAttribute =
  inherit Attribute
  new : unit -> SealedAttribute
  new : value:bool -> SealedAttribute
  member Value : bool

Full name: Microsoft.FSharp.Core.SealedAttribute

--------------------
new : unit -> SealedAttribute
new : value:bool -> SealedAttribute
union case Modifier.Static: Modifier
type Expr =
  | Literal of Value
  | Variable of VarName
  | MethodInvoke of MemberName * Expr list
  | PropertyGet of MemberName
  | InfixOperator of Expr * string * Expr
  | PrefixOperator of string * Expr
  | PostfixOperator of Expr * string
  | TernaryOperator of Expr * Expr * Expr

Full name: Script.Expr
Multiple items
union case Expr.Literal: Value -> Expr

--------------------
type LiteralAttribute =
  inherit Attribute
  new : unit -> LiteralAttribute

Full name: Microsoft.FSharp.Core.LiteralAttribute

--------------------
new : unit -> LiteralAttribute
union case Expr.Variable: VarName -> Expr
union case Expr.MethodInvoke: MemberName * Expr list -> Expr
type 'T list = List<'T>

Full name: Microsoft.FSharp.Collections.list<_>
union case Expr.PropertyGet: MemberName -> Expr
union case Expr.InfixOperator: Expr * string * Expr -> Expr
union case Expr.PrefixOperator: string * Expr -> Expr
union case Expr.PostfixOperator: Expr * string -> Expr
union case Expr.TernaryOperator: Expr * Expr * Expr -> Expr
type From = TypeName * Name * Expr

Full name: Script.From
type To = Expr

Full name: Script.To
type Step = Expr list

Full name: Script.Step
type Statement =
  | Define of TypeName * VarName
  | Assignment of VarName * Expr
  | PropertySet of MemberName * Expr
  | If of Expr * Block
  | Else of Expr * Block
  | Switch of Expr * Case list
  | For of From * To * Step * Block
  | ForEach of TypeName * VarName * Expr
  | While of Expr * Statement list
  | DoWhile of List<Statement> * Expr
  ...

Full name: Script.Statement
union case Statement.Define: TypeName * VarName -> Statement
union case Statement.Assignment: VarName * Expr -> Statement
union case Statement.PropertySet: MemberName * Expr -> Statement
union case Statement.If: Expr * Block -> Statement
type Block = Statement list

Full name: Script.Block
union case Statement.Else: Expr * Block -> Statement
union case Statement.Switch: Expr * Case list -> Statement
type Case = | Case of Value option * Block

Full name: Script.Case
union case Statement.For: From * To * Step * Block -> Statement
union case Statement.ForEach: TypeName * VarName * Expr -> Statement
union case Statement.While: Expr * Statement list -> Statement
union case Statement.DoWhile: List<Statement> * Expr -> Statement
Multiple items
module List

from Microsoft.FSharp.Collections

--------------------
type List<'T> =
  | ( [] )
  | ( :: ) of Head: 'T * Tail: 'T list
  interface IEnumerable
  interface IEnumerable<'T>
  member Head : 'T
  member IsEmpty : bool
  member Item : index:int -> 'T with get
  member Length : int
  member Tail : 'T list
  static member Cons : head:'T * tail:'T list -> 'T list
  static member Empty : 'T list

Full name: Microsoft.FSharp.Collections.List<_>
union case Statement.Try: Statement list -> Statement
union case Statement.Catch: TypeName * Block -> Statement
union case Statement.Finally: TypeName * Block -> Statement
union case Statement.Lock: Expr * Block -> Statement
union case Statement.Using: Expr * Block -> Statement
union case Statement.Label: LabelName -> Statement
union case Statement.Goto: LabelName -> Statement
union case Statement.Break: Statement
union case Statement.Continue: Statement
union case Statement.Return: Expr -> Statement
Multiple items
union case Case.Case: Value option * Block -> Case

--------------------
type Case = | Case of Value option * Block

Full name: Script.Case
type 'T option = Option<'T>

Full name: Microsoft.FSharp.Core.option<_>
Multiple items
union case MemberInfo.MemberInfo: Access * Modifier option * TypeName * Name -> MemberInfo

--------------------
type MemberInfo = | MemberInfo of Access * Modifier option * TypeName * Name

Full name: Script.MemberInfo
type Member =
  | Field of MemberInfo * Expr option
  | Method of MemberInfo * Arg list * Block
  | Property of MemberInfo * Block

Full name: Script.Member
union case Member.Field: MemberInfo * Expr option -> Member
union case Member.Method: MemberInfo * Arg list * Block -> Member
union case Member.Property: MemberInfo * Block -> Member
type CSharpType =
  | Class of Access * Modifier option * Name * Member list
  | Struct of Access * Name * Member list
  | Enum of Access * TypeName * EnumValue list

Full name: Script.CSharpType
Multiple items
union case CSharpType.Class: Access * Modifier option * Name * Member list -> CSharpType

--------------------
type ClassAttribute =
  inherit Attribute
  new : unit -> ClassAttribute

Full name: Microsoft.FSharp.Core.ClassAttribute

--------------------
new : unit -> ClassAttribute
Multiple items
union case CSharpType.Struct: Access * Name * Member list -> CSharpType

--------------------
type StructAttribute =
  inherit Attribute
  new : unit -> StructAttribute

Full name: Microsoft.FSharp.Core.StructAttribute

--------------------
new : unit -> StructAttribute
union case CSharpType.Enum: Access * TypeName * EnumValue list -> CSharpType
type Scope =
  | Namespace of Import list * Name * Scope list
  | Types of Import list * CSharpType list

Full name: Script.Scope
union case Scope.Namespace: Import list * Name * Scope list -> Scope
union case Scope.Types: Import list * CSharpType list -> Scope
namespace FParsec
val ws : Parser<unit,'a>

Full name: Script.ws
val spaces : Parser<unit,'u>

Full name: FParsec.CharParsers.spaces
val str_ws : s:string -> Parser<string,'a>

Full name: Script.str_ws
val s : string
val pstring : string -> Parser<string,'u>

Full name: FParsec.CharParsers.pstring
val str_ws1 : s:string -> Parser<string,'a>

Full name: Script.str_ws1
val spaces1 : Parser<unit,'u>

Full name: FParsec.CharParsers.spaces1
type Lit = NumberLiteralOptions

Full name: Script.Lit
type NumberLiteralOptions =
  | None = 0
  | AllowSuffix = 1
  | AllowMinusSign = 2
  | AllowPlusSign = 4
  | AllowFraction = 8
  | AllowFractionWOIntegerPart = 16
  | AllowExponent = 32
  | AllowHexadecimal = 64
  | AllowBinary = 128
  | AllowOctal = 256
  | AllowInfinity = 512
  | AllowNaN = 1024
  | IncludeSuffixCharsInString = 2048
  | DefaultInteger = 454
  | DefaultUnsignedInteger = 448
  | DefaultFloat = 1646

Full name: FParsec.CharParsers.NumberLiteralOptions
val numberFormat : NumberLiteralOptions

Full name: Script.numberFormat
NumberLiteralOptions.AllowMinusSign: NumberLiteralOptions = 2
NumberLiteralOptions.AllowFraction: NumberLiteralOptions = 8
NumberLiteralOptions.AllowExponent: NumberLiteralOptions = 32
val pnumber : Parser<Expr,unit>

Full name: Script.pnumber
type Parser<'Result,'UserState> = CharStream<'UserState> -> Reply<'Result>

Full name: FParsec.Primitives.Parser<_,_>
type unit = Unit

Full name: Microsoft.FSharp.Core.unit
val numberLiteral : NumberLiteralOptions -> string -> Parser<NumberLiteral,'u>

Full name: FParsec.CharParsers.numberLiteral
val nl : NumberLiteral
property NumberLiteral.IsInteger: bool
Multiple items
val int : value:'T -> int (requires member op_Explicit)

Full name: Microsoft.FSharp.Core.Operators.int

--------------------
type int = int32

Full name: Microsoft.FSharp.Core.int

--------------------
type int<'Measure> = int

Full name: Microsoft.FSharp.Core.int<_>
property NumberLiteral.String: string
Multiple items
val float : value:'T -> float (requires member op_Explicit)

Full name: Microsoft.FSharp.Core.Operators.float

--------------------
type float = System.Double

Full name: Microsoft.FSharp.Core.float

--------------------
type float<'Measure> = float

Full name: Microsoft.FSharp.Core.float<_>
val pidentifier : Parser<string,unit>

Full name: Script.pidentifier
val isIdentifierFirstChar : (char -> bool)
val c : char
val isLetter : char -> bool

Full name: FParsec.CharParsers.isLetter
val isIdentifierChar : (char -> bool)
val isDigit : char -> bool

Full name: FParsec.CharParsers.isDigit
val many1Satisfy2L : (char -> bool) -> (char -> bool) -> string -> Parser<string,'u>

Full name: FParsec.CharParsers.many1Satisfy2L
val pidentifier_ws : Parser<string,unit>

Full name: Script.pidentifier_ws
val pvar : Parser<Expr,unit>

Full name: Script.pvar
val x : string
val pexpr : Parser<Expr,unit>

Full name: Script.pexpr
val passign : Parser<Statement,unit>

Full name: Script.passign
val pipe3 : Parser<'a,'u> -> Parser<'b,'u> -> Parser<'c,'u> -> ('a -> 'b -> 'c -> 'd) -> Parser<'d,'u>

Full name: FParsec.Primitives.pipe3
val var : string
val expr : Expr
val pstatement : Parser<Statement,unit>

Full name: Script.pstatement
val ppublic : Parser<Access,unit>

Full name: Script.ppublic
val pprivate : Parser<Access,unit>

Full name: Script.pprivate
val pprotected : Parser<Access,unit>

Full name: Script.pprotected
val pinternal : Parser<Access,unit>

Full name: Script.pinternal
Multiple items
union case Access.Internal: Access

--------------------
namespace FParsec.Internal
val paccess : Parser<Access,unit>

Full name: Script.paccess
val opt : Parser<'a,'u> -> Parser<'a option,'u>

Full name: FParsec.Primitives.opt
val access : Access option
val defaultArg : arg:'T option -> defaultValue:'T -> 'T

Full name: Microsoft.FSharp.Core.Operators.defaultArg
val psealed : Parser<Modifier,unit>

Full name: Script.psealed
val pstatic : Parser<Modifier,unit>

Full name: Script.pstatic
val pmodifier : Parser<Modifier,unit>

Full name: Script.pmodifier
val pstatementblock : Parser<Statement list,unit>

Full name: Script.pstatementblock
val between : Parser<'a,'u> -> Parser<'b,'u> -> Parser<'c,'u> -> Parser<'c,'u>

Full name: FParsec.Primitives.between
val many : Parser<'a,'u> -> Parser<'a list,'u>

Full name: FParsec.Primitives.many
val parg : Parser<Arg,unit>

Full name: Script.parg
val pipe2 : Parser<'a,'u> -> Parser<'b,'u> -> ('a -> 'b -> 'c) -> Parser<'c,'u>

Full name: FParsec.Primitives.pipe2
val ty : string
val name : string
val pargs : Parser<Arg list,unit>

Full name: Script.pargs
val sepBy : Parser<'a,'u> -> Parser<'b,'u> -> Parser<'a list,'u>

Full name: FParsec.Primitives.sepBy
val pmemberinfo : Parser<MemberInfo,unit>

Full name: Script.pmemberinfo
val pipe4 : Parser<'a,'u> -> Parser<'b,'u> -> Parser<'c,'u> -> Parser<'d,'u> -> ('a -> 'b -> 'c -> 'd -> 'e) -> Parser<'e,'u>

Full name: FParsec.Primitives.pipe4
val access : Access
val modifier : Modifier option
val pfield : Parser<Member,unit>

Full name: Script.pfield
val mi : MemberInfo
union case Option.None: Option<'T>
val pproperty : Parser<Member,unit>

Full name: Script.pproperty
val block : Statement list
val pmethod : Parser<Member,unit>

Full name: Script.pmethod
val args : Arg list
val pmember : Parser<Member,unit>

Full name: Script.pmember
val attempt : Parser<'a,'u> -> Parser<'a,'u>

Full name: FParsec.Primitives.attempt
val pmemberblock : Parser<Member list,unit>

Full name: Script.pmemberblock
val members : Member list
val penumblock : Parser<Member list,unit>

Full name: Script.penumblock
val pclass : Parser<CSharpType,unit>

Full name: Script.pclass
val pipe5 : Parser<'a,'u> -> Parser<'b,'u> -> Parser<'c,'u> -> Parser<'d,'u> -> Parser<'e,'u> -> ('a -> 'b -> 'c -> 'd -> 'e -> 'f) -> Parser<'f,'u>

Full name: FParsec.Primitives.pipe5
val block : Member list
val pstruct : Parser<CSharpType,unit>

Full name: Script.pstruct
val penum : Parser<CSharpType,unit>

Full name: Script.penum
val ptypedeclaration : Parser<CSharpType,unit>

Full name: Script.ptypedeclaration
val pscope : Parser<Scope,unit>

Full name: Script.pscope
val pscopeimpl : Parser<Scope,unit> ref

Full name: Script.pscopeimpl
val createParserForwardedToRef : unit -> Parser<'a,'u> * Parser<'a,'u> ref

Full name: FParsec.Primitives.createParserForwardedToRef
val pscopesblock : Parser<Scope list,unit>

Full name: Script.pscopesblock
val scopes : Scope list
val pimport : Parser<Import,unit>

Full name: Script.pimport
val pnsblock : Parser<Scope,unit>

Full name: Script.pnsblock
val imports : Import list
val block : Scope list
val types : Scope
val ptypes : Parser<Scope,unit>

Full name: Script.ptypes
val many1 : Parser<'a,'u> -> Parser<'a list,'u>

Full name: FParsec.Primitives.many1
val classes : CSharpType list
val program : string

Full name: Script.program
val run : Parser<'Result,unit> -> string -> ParserResult<'Result,unit>

Full name: FParsec.CharParsers.run
Next Version Raw view Test code New version

More information

Link:http://fssnip.net/lf
Posted:4 years ago
Author:Phillip Trelford
Tags: c# , fparsec , parsing , ast