8 people like it.
Like the snippet!
Simple C# Parser
Simple prototype C# AST and parser using the FParsec parser combinator library. Parses a subset of C# 1.1 constructs.
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:
|
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 = EnumValue of Name * Value
type Import =
| Import of Name
| Abbreviation of Name * Name
type Access = Public | Private | Protected | Internal
type Modifier = Sealed | Static
type Literal = Literal of Value
type Expr =
| Value of Literal
| Variable of VarName
| MethodInvoke of MemberName * Expr list
| PropertyGet of MemberName
| InfixOp of Expr * string * Expr
| PrefixOp of string * Expr
| PostfixOp of Expr * string
| TernaryOp of Expr * Expr * Expr
type Define = Define of TypeName * VarName
type Init =
| Assign of Name * Expr
| Construct of TypeName * Name * Expr
type Condition = Expr
type Iterator = Expr
type Statement =
| Definition of Define
| Assignment of Init
| PropertySet of MemberName * Expr
| Invoke of MemberName * Expr list
| If of Expr * Block
| IfElse of Expr * Block * Block
| Switch of Expr * Case list
| For of Init list * Condition * Iterator list * Block
| ForEach of Define * Expr * Block
| While of Expr * Block
| DoWhile of Block * Expr
| Throw of Expr
| Try of Block
| Catch of TypeName * Block
| Finally of Block
| Lock of Expr * Block
| Using of Expr * Block
| Label of LabelName
| Goto of LabelName
| Break
| Continue
| Return of Expr
and Case =
| Case of Literal * Block
| Default of Block
and Block = Statement list
type MemberInfo = MemberInfo of Access * Modifier option * TypeName * Name
type Member =
| Field of MemberInfo * Expr option
| Constructor of MemberInfo
| Method of MemberInfo * Arg list * Block
| Property of MemberInfo * Block option * Block option
type Members = Member list
type Implements = Name list
type CSharpType =
| Class of Access * Modifier option * Name * Implements * Members
| Struct of Access * Name * Member list
| Interface of Access * Name * Implements * Member list
| Enum of Access * TypeName * EnumValue list
type Scope =
| Namespace of Import list * Name * Scope list
| Types of Import list * CSharpType list
|
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:
86:
87:
88:
89:
90:
91:
92:
93:
94:
95:
96:
97:
98:
99:
100:
101:
102:
103:
104:
105:
106:
107:
108:
109:
110:
111:
112:
113:
114:
115:
116:
117:
118:
119:
120:
121:
122:
123:
124:
125:
126:
127:
128:
129:
130:
131:
132:
133:
134:
135:
136:
137:
138:
139:
140:
141:
142:
143:
144:
145:
146:
147:
148:
149:
150:
151:
152:
153:
154:
155:
156:
157:
158:
159:
160:
161:
162:
163:
164:
165:
166:
167:
168:
169:
170:
171:
172:
173:
174:
175:
176:
177:
178:
179:
180:
181:
182:
183:
184:
185:
186:
187:
188:
189:
190:
191:
192:
193:
194:
195:
196:
197:
198:
199:
200:
201:
202:
203:
204:
205:
206:
207:
208:
209:
210:
211:
212:
213:
214:
215:
216:
217:
218:
219:
220:
221:
222:
223:
224:
225:
226:
227:
228:
229:
230:
231:
232:
233:
234:
235:
236:
237:
238:
239:
240:
241:
242:
243:
244:
245:
246:
247:
248:
249:
250:
251:
252:
253:
254:
255:
256:
257:
258:
259:
260:
261:
262:
263:
264:
265:
266:
267:
268:
269:
270:
271:
272:
273:
274:
275:
276:
277:
278:
279:
280:
281:
282:
283:
284:
285:
286:
287:
288:
289:
290:
291:
292:
293:
294:
295:
296:
|
open FParsec
// White space
let maxCount = System.Int32.MaxValue
let pcomment = pstring "//" >>. many1Satisfy ((<>) '\n')
let pspaces = spaces >>. many (spaces >>. pcomment >>. spaces)
let pmlcomment = pstring "/*" >>. skipCharsTillString "*/" true (maxCount)
let ws = pspaces >>. many (pspaces >>. pmlcomment >>. pspaces) |>> (fun _ -> ())
let ws1 = spaces1
let str_ws s = pstring s .>> ws
let str_ws1 s = pstring s .>> ws1
// Literals
type Lit = NumberLiteralOptions
let numberFormat = Lit.AllowMinusSign ||| Lit.AllowFraction ||| Lit.AllowExponent
let pnumber : Parser<Literal, unit> =
numberLiteral numberFormat "number"
|>> fun nl ->
if nl.IsInteger then Literal(int nl.String)
else Literal(float nl.String)
let ptrue = str_ws "true" |>> fun _ -> Literal(true)
let pfalse = str_ws "false" |>> fun _ -> Literal(false)
let pbool = ptrue <|> pfalse
let pstringliteral =
let normalChar = satisfy (fun c -> c <> '\\' && c <> '"')
let unescape c = match c with
| 'n' -> '\n'
| 'r' -> '\r'
| 't' -> '\t'
| c -> c
let escapedChar = pstring "\\" >>. (anyOf "\\nrt\"" |>> unescape)
between (pstring "\"") (pstring "\"")
(manyChars (normalChar <|> escapedChar))
|>> fun s -> Literal(s)
let pliteral = pnumber <|> pbool <|> pstringliteral
// Expressions
let reserved = ["default" (*;...*)] // "default:" collides with "label:"
let pidentifierraw =
let isIdentifierFirstChar c = isLetter c || c = '_'
let isIdentifierChar c = isLetter c || isDigit c || c = '_'
many1Satisfy2L isIdentifierFirstChar isIdentifierChar "identifier"
let pidentifier =
pidentifierraw
>>= fun s ->
if reserved |> List.exists ((=) s) then fail "keyword"
else preturn s
let pidentifier_ws = pidentifier .>> ws
let pvar = pidentifier |>> fun x -> Variable(x)
let pvalue = (pliteral |>> fun x -> Value(x)) <|> pvar
type Assoc = Associativity
let opp = OperatorPrecedenceParser<Expr,unit,unit>()
let pexpr = opp.ExpressionParser
let term = pvalue .>> ws <|> between (str_ws "(") (str_ws ")") pexpr
opp.TermParser <- term
let inops = ["+";"-";"*";"/";"==";"!=";"<=";">=";"<";">"]
for op in inops do
opp.AddOperator(InfixOperator(op, ws, 1, Assoc.Left, fun x y -> InfixOp(x, op, y)))
let preops = ["-";"++";"--"]
for op in preops do
opp.AddOperator(PrefixOperator(op, ws, 1, true, fun x -> PrefixOp(op, x)))
let postops = ["++";"--"]
for op in postops do
opp.AddOperator(PostfixOperator(op, ws, 1, true, fun x -> PostfixOp(x, op)))
let pexpr' = between (str_ws "(") (str_ws ")") pexpr
// Statement blocks
let pstatement, pstatementimpl = createParserForwardedToRef()
let psinglestatement = pstatement |>> fun statement -> [statement]
let pstatementblock =
psinglestatement <|>
between (str_ws "{") (str_ws "}") (many pstatement)
// Assignement statements
let pdefine = pipe2 (pidentifier .>> ws1) (pidentifier)
(fun ty name -> Define(ty,name))
let pdefinition = pdefine |>> fun d -> Definition(d)
let passign = pipe3 pidentifier_ws (str_ws "=") pexpr
(fun var _ expr -> Assign(var,expr))
let pconstruct =
pipe4
(pidentifier .>> ws1)
pidentifier_ws
(str_ws "=")
pexpr
(fun ty name _ e -> Construct(ty, name, e))
let passignment = attempt passign <|> attempt pconstruct |>> fun c -> Assignment(c)
// Selection statements
let pif =
pipe2 (str_ws "if" >>. pexpr') pstatementblock
(fun e block -> If(e,block))
let pifelse =
pipe3 (str_ws "if" >>. pexpr') pstatementblock (str_ws "else" >>. pstatementblock)
(fun e t f -> IfElse(e,t,f))
let pcase = str_ws1 "case" >>. pliteral .>> str_ws ":"
let pcaseblock = pipe2 pcase (many pstatement) (fun case block -> Case(case,block))
let pdefault = str_ws "default" >>. str_ws ":"
let pdefaultblock = pdefault >>. (many pstatement) |>> fun block -> Default(block)
let pcases' = many pcaseblock .>>. opt pdefaultblock
|>> fun (cases,d) -> cases@(Option.toList d)
let pcases = between (str_ws "{") (str_ws "}") pcases'
let pswitch =
pipe2 (str_ws "switch" >>. pexpr') pcases
(fun e cases -> Switch(e, cases))
// Iteration statements
let pforargs =
let pinit = attempt passign <|> attempt pconstruct
pipe3
(sepBy pinit (str_ws ",") .>> str_ws ";")
(pexpr .>> str_ws ";")
(sepBy pexpr (str_ws ","))
(fun from until steps -> from, until, steps)
let pfor =
pipe2
(str_ws "for" >>. between (str_ws "(") (str_ws ")") pforargs)
pstatementblock
(fun (inits,until,iterators) block -> For(inits,until,iterators,block))
let pforeachargs =
pipe3 pdefine (str_ws1 "in") pexpr
(fun define _ collection -> define, collection)
let pforeach =
pipe2 (str_ws "foreach" >>. pforeachargs) pstatementblock
(fun (define,collection) block -> ForEach(define,collection,block))
let pwhile =
pipe2 (str_ws "while" >>. pexpr') pstatementblock
(fun e block -> While(e,block))
let pdowhile =
pipe2
(str_ws "do" >>. pstatementblock)
(str_ws "while" >>. pexpr')
(fun block e -> DoWhile(block, e))
// Jump statements
let preturn = str_ws1 "return" >>. pexpr |>> fun e -> Return(e)
let pbreak = str_ws "break" |>> fun _ -> Break
let pcontinue = str_ws "continue" |>> fun _ -> Continue
let pgoto = str_ws1 "goto" >>. pidentifier_ws |>> fun label -> Goto(label)
let plabel =
pidentifier_ws .>> str_ws ":"
|>> fun label -> Label(label)
// Exception statements
let pthrow = str_ws1 "throw" >>. pexpr |>> fun e -> Throw(e)
let ptry = str_ws "try" >>. pstatementblock |>> fun block -> Try(block)
let pfinally = str_ws "finally" >>. pstatementblock |>> fun block-> Finally(block)
let pexception = between (str_ws "(") (str_ws ")") pidentifier_ws
let pcatch = str_ws "catch" >>. pexception .>>. pstatementblock
|>> fun (ex,block) -> Catch(ex, block)
// Lock statement
let plock =
str_ws "lock" >>. pexpr' .>>. pstatementblock
|>> (fun (e,block) -> Lock(e,block))
// Statement implementation
pstatementimpl :=
attempt (preturn .>> str_ws ";") <|>
attempt (pbreak .>> str_ws ";") <|>
attempt (pcontinue .>> str_ws ";") <|>
attempt (pgoto .>> str_ws ";") <|>
attempt (pdefinition .>> str_ws ";") <|>
attempt (passignment .>> str_ws ";") <|>
attempt plabel <|>
attempt pifelse <|> attempt pif <|>
attempt pswitch <|>
attempt pfor <|> attempt pforeach <|>
attempt pwhile <|> attempt pdowhile <|>
attempt pthrow <|>
attempt ptry <|> attempt pcatch <|> attempt pfinally
attempt plock
// Access
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)
// Modifiers
let psealed = str_ws1 "sealed" |>> (fun _ -> Sealed)
let pstatic = str_ws1 "static" |>> (fun _ -> Static)
let pmodifier = psealed <|> pstatic
// Arguments
let parg = pipe2 pidentifier_ws pidentifier_ws (fun ty name -> Arg(ty,name))
let pargs = str_ws "(" >>. sepBy parg (str_ws ",") .>> str_ws ")"
// Members
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 pget = str_ws "get" >>. pstatementblock
let pset = str_ws "set" >>. pstatementblock
let ppropertyblock =
between (str_ws "{") (str_ws "}") ((opt pget) .>>. (opt pset))
let pproperty =
pipe2 pmemberinfo ppropertyblock
(fun mi (gblock,sblock) -> Property(mi,gblock,sblock))
let pmethod =
pipe3 pmemberinfo pargs pstatementblock
(fun mi args block -> Method(mi,args,block))
let pmember = attempt pfield <|> attempt pmethod <|> attempt pproperty
let pmembersblock = between (str_ws "{") (str_ws "}") (many pmember)
|>> (fun members -> members)
let penumblock =
between (str_ws "{") (str_ws "}") (sepBy pidentifier_ws (str_ws ","))
|>> fun names -> names |> List.mapi (fun i name -> EnumValue(name,i))
// Types
let pclasspreamble =
paccess .>>. (opt pmodifier) .>> (str_ws1 "class")
let pimplements =
opt (str_ws ":" >>. sepBy1 (pidentifier_ws) (str_ws ","))
|>> function Some xs -> xs | None -> []
let pclass =
pipe4 pclasspreamble pidentifier_ws pimplements pmembersblock
(fun (access,modifier) name implements block ->
Class(access, modifier, name, implements, block))
let pstruct =
pipe4 paccess (str_ws1 "struct") pidentifier_ws pmembersblock
(fun access _ name block -> Struct(access, name, block))
let pinterface =
pipe5 paccess (str_ws1 "interface") pidentifier_ws pimplements pmembersblock
(fun access _ name implements block ->
Interface(access, name, implements, block))
let penum =
pipe4 paccess (str_ws1 "enum") pidentifier_ws penumblock
(fun access _ name block -> Enum(access, name, block))
let ptypedeclaration = pclass <|> pstruct <|> pinterface <|> penum
// Scopes
let pscope, pscopeimpl = createParserForwardedToRef()
let pscopesblock = between (str_ws "{") (str_ws "}") (many pscope)
let pimport = str_ws1 "using" >>. pidentifier_ws .>> 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 := ws >>. (pnsblock <|> ptypes)
|
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:
|
let program = """
using X;
using Y;
namespace A {
namespace B {
/* My class */
class MyClass : IMarker {
float y;
// My foo
bool foo(string arg) {
string s = "hello"; // assign string lit
for(int i = 1; i<=100; i++) { }
switch(y) { case 0: break; case 1: y = 1; default: }
bool x;
x = true;
while(x) {
if (true) { x = false; } else if (false) { goto end; }
}
end:
return true;
}
bool MyProp {
get { }
set { y = value; }
}
}
struct MyStruct { }
interface IMarker { }
enum MyEnum { One, Two, Three }
}
}
"""
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
Multiple items
union case EnumValue.EnumValue: Name * Value -> EnumValue
--------------------
type EnumValue = | EnumValue of 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
Multiple items
union case Literal.Literal: Value -> Literal
--------------------
type Literal = | Literal of Value
Full name: Script.Literal
--------------------
type LiteralAttribute =
inherit Attribute
new : unit -> LiteralAttribute
Full name: Microsoft.FSharp.Core.LiteralAttribute
--------------------
new : unit -> LiteralAttribute
type Expr =
| Value of Literal
| Variable of VarName
| MethodInvoke of MemberName * Expr list
| PropertyGet of MemberName
| InfixOp of Expr * string * Expr
| PrefixOp of string * Expr
| PostfixOp of Expr * string
| TernaryOp of Expr * Expr * Expr
Full name: Script.Expr
Multiple items
union case Expr.Value: Literal -> Expr
--------------------
type Value = obj
Full name: Script.Value
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.InfixOp: Expr * string * Expr -> Expr
union case Expr.PrefixOp: string * Expr -> Expr
union case Expr.PostfixOp: Expr * string -> Expr
union case Expr.TernaryOp: Expr * Expr * Expr -> Expr
Multiple items
union case Define.Define: TypeName * VarName -> Define
--------------------
type Define = | Define of TypeName * VarName
Full name: Script.Define
type Init =
| Assign of Name * Expr
| Construct of TypeName * Name * Expr
Full name: Script.Init
union case Init.Assign: Name * Expr -> Init
union case Init.Construct: TypeName * Name * Expr -> Init
type Condition = Expr
Full name: Script.Condition
type Iterator = Expr
Full name: Script.Iterator
type Statement =
| Definition of Define
| Assignment of Init
| PropertySet of MemberName * Expr
| Invoke of MemberName * Expr list
| If of Expr * Block
| IfElse of Expr * Block * Block
| Switch of Expr * Case list
| For of Init list * Condition * Iterator list * Block
| ForEach of Define * Expr * Block
| While of Expr * Block
...
Full name: Script.Statement
union case Statement.Definition: Define -> Statement
union case Statement.Assignment: Init -> Statement
union case Statement.PropertySet: MemberName * Expr -> Statement
union case Statement.Invoke: MemberName * Expr list -> Statement
union case Statement.If: Expr * Block -> Statement
type Block = Statement list
Full name: Script.Block
union case Statement.IfElse: Expr * Block * Block -> Statement
union case Statement.Switch: Expr * Case list -> Statement
type Case =
| Case of Literal * Block
| Default of Block
Full name: Script.Case
union case Statement.For: Init list * Condition * Iterator list * Block -> Statement
union case Statement.ForEach: Define * Expr * Block -> Statement
union case Statement.While: Expr * Block -> Statement
union case Statement.DoWhile: Block * Expr -> Statement
union case Statement.Throw: Expr -> Statement
union case Statement.Try: Block -> Statement
union case Statement.Catch: TypeName * Block -> Statement
union case Statement.Finally: 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: Literal * Block -> Case
--------------------
type Case =
| Case of Literal * Block
| Default of Block
Full name: Script.Case
union case Case.Default: Block -> Case
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 'T option = Option<'T>
Full name: Microsoft.FSharp.Core.option<_>
type Member =
| Field of MemberInfo * Expr option
| Constructor of MemberInfo
| Method of MemberInfo * Arg list * Block
| Property of MemberInfo * Block option * Block option
Full name: Script.Member
union case Member.Field: MemberInfo * Expr option -> Member
union case Member.Constructor: MemberInfo -> Member
union case Member.Method: MemberInfo * Arg list * Block -> Member
union case Member.Property: MemberInfo * Block option * Block option -> Member
type Members = Member list
Full name: Script.Members
type Implements = Name list
Full name: Script.Implements
type CSharpType =
| Class of Access * Modifier option * Name * Implements * Members
| Struct of Access * Name * Member list
| Interface of Access * Name * Implements * Member list
| Enum of Access * TypeName * EnumValue list
Full name: Script.CSharpType
Multiple items
union case CSharpType.Class: Access * Modifier option * Name * Implements * Members -> 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
Multiple items
union case CSharpType.Interface: Access * Name * Implements * Member list -> CSharpType
--------------------
type InterfaceAttribute =
inherit Attribute
new : unit -> InterfaceAttribute
Full name: Microsoft.FSharp.Core.InterfaceAttribute
--------------------
new : unit -> InterfaceAttribute
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 maxCount : int
Full name: Script.maxCount
namespace System
type Int32 =
struct
member CompareTo : value:obj -> int + 1 overload
member Equals : obj:obj -> bool + 1 overload
member GetHashCode : unit -> int
member GetTypeCode : unit -> TypeCode
member ToString : unit -> string + 3 overloads
static val MaxValue : int
static val MinValue : int
static member Parse : s:string -> int + 3 overloads
static member TryParse : s:string * result:int -> bool + 1 overload
end
Full name: System.Int32
field int.MaxValue = 2147483647
val pcomment : Parser<string,unit>
Full name: Script.pcomment
val pstring : string -> Parser<string,'u>
Full name: FParsec.CharParsers.pstring
val many1Satisfy : (char -> bool) -> Parser<string,'u>
Full name: FParsec.CharParsers.many1Satisfy
val pspaces : Parser<unit list,unit>
Full name: Script.pspaces
val spaces : Parser<unit,'u>
Full name: FParsec.CharParsers.spaces
val many : Parser<'a,'u> -> Parser<'a list,'u>
Full name: FParsec.Primitives.many
val pmlcomment : Parser<unit,unit>
Full name: Script.pmlcomment
val skipCharsTillString : string -> skipString:bool -> maxCount:int -> Parser<unit,'u>
Full name: FParsec.CharParsers.skipCharsTillString
val ws : Parser<unit,unit>
Full name: Script.ws
val ws1 : Parser<unit,'a>
Full name: Script.ws1
val spaces1 : Parser<unit,'u>
Full name: FParsec.CharParsers.spaces1
val str_ws : s:string -> Parser<string,unit>
Full name: Script.str_ws
val s : string
val str_ws1 : s:string -> Parser<string,'a>
Full name: Script.str_ws1
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<Literal,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 ptrue : Parser<Literal,unit>
Full name: Script.ptrue
val pfalse : Parser<Literal,unit>
Full name: Script.pfalse
val pbool : Parser<Literal,unit>
Full name: Script.pbool
val pstringliteral : Parser<Literal,unit>
Full name: Script.pstringliteral
val normalChar : Parser<char,unit>
val satisfy : (char -> bool) -> Parser<char,'u>
Full name: FParsec.CharParsers.satisfy
val c : char
val unescape : (char -> char)
val escapedChar : Parser<char,unit>
val anyOf : seq<char> -> Parser<char,'u>
Full name: FParsec.CharParsers.anyOf
val between : Parser<'a,'u> -> Parser<'b,'u> -> Parser<'c,'u> -> Parser<'c,'u>
Full name: FParsec.Primitives.between
val manyChars : Parser<char,'u> -> Parser<string,'u>
Full name: FParsec.CharParsers.manyChars
val pliteral : Parser<Literal,unit>
Full name: Script.pliteral
val reserved : string list
Full name: Script.reserved
val pidentifierraw : Parser<string,unit>
Full name: Script.pidentifierraw
val isIdentifierFirstChar : (char -> bool)
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 : Parser<string,unit>
Full name: Script.pidentifier
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<_>
val exists : predicate:('T -> bool) -> list:'T list -> bool
Full name: Microsoft.FSharp.Collections.List.exists
val fail : string -> Parser<'a,'u>
Full name: FParsec.Primitives.fail
val preturn : 'a -> Parser<'a,'u>
Full name: FParsec.Primitives.preturn
val pidentifier_ws : Parser<string,unit>
Full name: Script.pidentifier_ws
val pvar : Parser<Expr,unit>
Full name: Script.pvar
val x : string
val pvalue : Parser<Expr,unit>
Full name: Script.pvalue
val x : Literal
type Assoc = Associativity
Full name: Script.Assoc
type Associativity =
| None = 0
| Left = 1
| Right = 2
Full name: FParsec.Associativity
val opp : OperatorPrecedenceParser<Expr,unit,unit>
Full name: Script.opp
Multiple items
type OperatorPrecedenceParser<'TTerm,'TAfterString,'TUserState> =
inherit FSharpFunc<CharStream<'TUserState>, Reply<'TTerm>>
new : unit -> OperatorPrecedenceParser<'TTerm, 'TAfterString, 'TUserState>
member AddOperator : op:Operator<'TTerm, 'TAfterString, 'TUserState> -> unit
member ExpressionParser : FSharpFunc<CharStream<'TUserState>, Reply<'TTerm>>
member Invoke : stream:CharStream<'TUserState> -> Reply<'TTerm>
member MissingTernary2ndStringErrorFormatter : FSharpFunc<Tuple<Position, Position, TernaryOperator<'TTerm, 'TAfterString, 'TUserState>, 'TAfterString>, ErrorMessageList> with get, set
member OperatorConflictErrorFormatter : FSharpFunc<Tuple<Position, Operator<'TTerm, 'TAfterString, 'TUserState>, 'TAfterString>, FSharpFunc<Tuple<Position, Operator<'TTerm, 'TAfterString, 'TUserState>, 'TAfterString>, ErrorMessageList>> with get, set
member Operators : IEnumerable<Operator<'TTerm, 'TAfterString, 'TUserState>>
member RemoveInfixOperator : opString:string -> bool
member RemoveOperator : op:Operator<'TTerm, 'TAfterString, 'TUserState> -> bool
member RemovePostfixOperator : opString:string -> bool
...
Full name: FParsec.OperatorPrecedenceParser<_,_,_>
--------------------
OperatorPrecedenceParser() : unit
val pexpr : (CharStream<unit> -> Reply<Expr>)
Full name: Script.pexpr
property OperatorPrecedenceParser.ExpressionParser: CharStream<unit> -> Reply<Expr>
val term : Parser<Expr,unit>
Full name: Script.term
property OperatorPrecedenceParser.TermParser: CharStream<unit> -> Reply<Expr>
val inops : string list
Full name: Script.inops
val op : string
OperatorPrecedenceParser.AddOperator(op: Operator<Expr,unit,unit>) : unit
Multiple items
type InfixOperator<'TTerm,'TAfterString,'TUserState> =
inherit Operator<'TTerm, 'TAfterString, 'TUserState>
new : operatorString:string * afterStringParser:FSharpFunc<CharStream<'TUserState>, Reply<'TAfterString>> * precedence:int * associativity:Associativity * mapping:FSharpFunc<'TTerm, FSharpFunc<'TTerm, 'TTerm>> -> InfixOperator<'TTerm, 'TAfterString, 'TUserState> + 1 overload
Full name: FParsec.InfixOperator<_,_,_>
--------------------
InfixOperator(operatorString: string, afterStringParser: CharStream<'TUserState> -> Reply<'TAfterString>, precedence: int, associativity: Associativity, mapping: 'TTerm -> 'TTerm -> 'TTerm) : unit
InfixOperator(operatorString: string, afterStringParser: CharStream<'TUserState> -> Reply<'TAfterString>, precedence: int, associativity: Associativity, dummy: Unit, mapping: 'TAfterString -> 'TTerm -> 'TTerm -> 'TTerm) : unit
field Associativity.Left = 1
val x : Expr
val y : Expr
val preops : string list
Full name: Script.preops
Multiple items
type PrefixOperator<'TTerm,'TAfterString,'TUserState> =
inherit Operator<'TTerm, 'TAfterString, 'TUserState>
new : operatorString:string * afterStringParser:FSharpFunc<CharStream<'TUserState>, Reply<'TAfterString>> * precedence:int * isAssociative:bool * mapping:FSharpFunc<'TTerm, 'TTerm> -> PrefixOperator<'TTerm, 'TAfterString, 'TUserState> + 1 overload
Full name: FParsec.PrefixOperator<_,_,_>
--------------------
PrefixOperator(operatorString: string, afterStringParser: CharStream<'TUserState> -> Reply<'TAfterString>, precedence: int, isAssociative: bool, mapping: 'TTerm -> 'TTerm) : unit
PrefixOperator(operatorString: string, afterStringParser: CharStream<'TUserState> -> Reply<'TAfterString>, precedence: int, isAssociative: bool, dummy: Unit, mapping: 'TAfterString -> 'TTerm -> 'TTerm) : unit
val postops : string list
Full name: Script.postops
Multiple items
type PostfixOperator<'TTerm,'TAfterString,'TUserState> =
inherit Operator<'TTerm, 'TAfterString, 'TUserState>
new : operatorString:string * afterStringParser:FSharpFunc<CharStream<'TUserState>, Reply<'TAfterString>> * precedence:int * isAssociative:bool * mapping:FSharpFunc<'TTerm, 'TTerm> -> PostfixOperator<'TTerm, 'TAfterString, 'TUserState> + 1 overload
Full name: FParsec.PostfixOperator<_,_,_>
--------------------
PostfixOperator(operatorString: string, afterStringParser: CharStream<'TUserState> -> Reply<'TAfterString>, precedence: int, isAssociative: bool, mapping: 'TTerm -> 'TTerm) : unit
PostfixOperator(operatorString: string, afterStringParser: CharStream<'TUserState> -> Reply<'TAfterString>, precedence: int, isAssociative: bool, dummy: Unit, mapping: 'TAfterString -> 'TTerm -> 'TTerm) : unit
val pexpr' : Parser<Expr,unit>
Full name: Script.pexpr'
val pstatement : Parser<Statement,unit>
Full name: Script.pstatement
val pstatementimpl : Parser<Statement,unit> ref
Full name: Script.pstatementimpl
val createParserForwardedToRef : unit -> Parser<'a,'u> * Parser<'a,'u> ref
Full name: FParsec.Primitives.createParserForwardedToRef
val psinglestatement : Parser<Statement list,unit>
Full name: Script.psinglestatement
val statement : Statement
val pstatementblock : Parser<Statement list,unit>
Full name: Script.pstatementblock
val pdefine : Parser<Define,unit>
Full name: Script.pdefine
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 pdefinition : Parser<Statement,unit>
Full name: Script.pdefinition
val d : Define
val passign : Parser<Init,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 pconstruct : Parser<Init,unit>
Full name: Script.pconstruct
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 e : Expr
val passignment : Parser<Statement,unit>
Full name: Script.passignment
val attempt : Parser<'a,'u> -> Parser<'a,'u>
Full name: FParsec.Primitives.attempt
val c : Init
val pif : Parser<Statement,unit>
Full name: Script.pif
val block : Statement list
val pifelse : Parser<Statement,unit>
Full name: Script.pifelse
val t : Statement list
val f : Statement list
val pcase : Parser<Literal,unit>
Full name: Script.pcase
val pcaseblock : Parser<Case,unit>
Full name: Script.pcaseblock
val case : Literal
val pdefault : Parser<string,unit>
Full name: Script.pdefault
val pdefaultblock : Parser<Case,unit>
Full name: Script.pdefaultblock
val pcases' : Parser<Case list,unit>
Full name: Script.pcases'
val opt : Parser<'a,'u> -> Parser<'a option,'u>
Full name: FParsec.Primitives.opt
val cases : Case list
val d : Case option
module Option
from Microsoft.FSharp.Core
val toList : option:'T option -> 'T list
Full name: Microsoft.FSharp.Core.Option.toList
val pcases : Parser<Case list,unit>
Full name: Script.pcases
val pswitch : Parser<Statement,unit>
Full name: Script.pswitch
val pforargs : Parser<(Init list * Expr * Expr list),unit>
Full name: Script.pforargs
val pinit : Parser<Init,unit>
val sepBy : Parser<'a,'u> -> Parser<'b,'u> -> Parser<'a list,'u>
Full name: FParsec.Primitives.sepBy
val from : Init list
val until : Expr
val steps : Expr list
val pfor : Parser<Statement,unit>
Full name: Script.pfor
val inits : Init list
val iterators : Expr list
val pforeachargs : Parser<(Define * Expr),unit>
Full name: Script.pforeachargs
val define : Define
val collection : Expr
val pforeach : Parser<Statement,unit>
Full name: Script.pforeach
val pwhile : Parser<Statement,unit>
Full name: Script.pwhile
val pdowhile : Parser<Statement,unit>
Full name: Script.pdowhile
val preturn : Parser<Statement,unit>
Full name: Script.preturn
val pbreak : Parser<Statement,unit>
Full name: Script.pbreak
val pcontinue : Parser<Statement,unit>
Full name: Script.pcontinue
val pgoto : Parser<Statement,unit>
Full name: Script.pgoto
val label : string
val plabel : Parser<Statement,unit>
Full name: Script.plabel
val pthrow : Parser<Statement,unit>
Full name: Script.pthrow
val ptry : Parser<Statement,unit>
Full name: Script.ptry
val pfinally : Parser<Statement,unit>
Full name: Script.pfinally
val pexception : Parser<string,unit>
Full name: Script.pexception
val pcatch : Parser<Statement,unit>
Full name: Script.pcatch
val ex : string
val plock : Parser<Statement,unit>
Full name: Script.plock
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 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 parg : Parser<Arg,unit>
Full name: Script.parg
val pargs : Parser<Arg list,unit>
Full name: Script.pargs
val pmemberinfo : Parser<MemberInfo,unit>
Full name: Script.pmemberinfo
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 pget : Parser<Statement list,unit>
Full name: Script.pget
val pset : Parser<Statement list,unit>
Full name: Script.pset
val ppropertyblock : Parser<(Statement list option * Statement list option),unit>
Full name: Script.ppropertyblock
val pproperty : Parser<Member,unit>
Full name: Script.pproperty
val gblock : Statement list option
val sblock : Statement list option
val pmethod : Parser<Member,unit>
Full name: Script.pmethod
val args : Arg list
val pmember : Parser<Member,unit>
Full name: Script.pmember
val pmembersblock : Parser<Member list,unit>
Full name: Script.pmembersblock
val members : Member list
val penumblock : Parser<EnumValue list,unit>
Full name: Script.penumblock
val names : string list
val mapi : mapping:(int -> 'T -> 'U) -> list:'T list -> 'U list
Full name: Microsoft.FSharp.Collections.List.mapi
val i : int
val pclasspreamble : Parser<(Access * Modifier option),unit>
Full name: Script.pclasspreamble
val pimplements : Parser<string list,unit>
Full name: Script.pimplements
val sepBy1 : Parser<'a,'u> -> Parser<'b,'u> -> Parser<'a list,'u>
Full name: FParsec.Primitives.sepBy1
union case Option.Some: Value: 'T -> Option<'T>
val xs : string list
val pclass : Parser<CSharpType,unit>
Full name: Script.pclass
val implements : string list
val block : Member list
val pstruct : Parser<CSharpType,unit>
Full name: Script.pstruct
val pinterface : Parser<CSharpType,unit>
Full name: Script.pinterface
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 penum : Parser<CSharpType,unit>
Full name: Script.penum
val block : EnumValue list
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 pscopesblock : Parser<Scope list,unit>
Full name: Script.pscopesblock
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
More information