|
F# Manual
- Contents
The F# Programming Language Informal Specification
F# is a scalable, script-like, type-safe, efficiently executing functional/imperative/object-oriented programming language. It aims to be the premier type-safe symbolic programming language for the .NET platform. This manual describes the F# language through a mixture of informal and semi-formal techniques. F# is similar to the Caml programming language family, and was partially inspired by it. See F# and OCaml for more details. Comments. Comments are delimited by (* and *) and may be nested. In addition, C#/C++-style // single-line comments may be used and extend to the end of a line. Strings embedded within comments are parsed without looking for closing *) marks, e.g., (* Here's a code snippet: let s = "*)" *) is a valid comment. Conditional Compilation. #if ident/#endif directives delimit conditional compilation sections. Text in a #if section is included in the compilation if the given ident is defined in the compilation environment, typically via the command line option --define. F# also allows code to be cross-compiled as both F# and OCaml code. Sections marked (*IF-FSHARP ... ENDIF-FSHARP*) or (*F# ... F#*) are included when compiling with the F# compiler, and text surrounded by (*IF-CAML*) ... (*ENDIF-CAML*) or (*IF-OCAML*) ... (*ENDIF-OCAML*) is excluded when compiling with the F# compiler. Of course the converse holds when compiling programs using an OCaml compiler. Keywords. The keywords of the F# language are shown below. abstract and as assert begin class default delegate do done downcast downto else end enum exception extern false finally for fun function if in inherit interface land lazy let match member module mutable namespace new null of open or override rec sig static struct then to true try type val when inline upcast while with void The following identifiers are also keywords because they are keywords in OCaml. However their use is not recommended in F# code, since symbolic alternatives are available. asr land lor lsl lsr lxor mod The symbols act as keywords: | -> ->> <- . : ( ) [ ] [< >] [| |] { } # The following identifiers are used in OCaml and/or C# and are reserved for future use by F#. The --ml-compatibility option permits OCaml identifiers to be used. async atomic break checked component const constraint constructor continue decimal eager event external fixed functor include method mixin object process property protected public pure readonly return sealed virtual volatile {< >} Operators and Symbolic Keywords. Operator names are sequences of characters as shown below, except where a combination of characters is used as a symbol elsewhere in the language. Precedence is specified below. first-op-char := !$%&*+-./<=>?@^|~ op-char := first-op-char | : operator := first-op-char op-char* For example, &&& and ||| are valid operators. These have default definitions as overloaded bitwise manipulations on integer types. Certain Unicode characters may also be included in the operator set. The final choice of such characters is as yet unspecified, though it may be specified in the change notices with each compiler release. In addition, the following operators correspond to syntactic forms for expressions. .[] (expression form "a.[i]") .[]<- (expression form "a.[i] <- x") .[,] (expression form "a.[i,j]") .[,]<- (expression form "a.[i,j] <- x") .[,,] (expression form "a.[i,j,k]") .[,,]<- (expression form "a.[i,j,k] <- x") .() (expression form "a.(i)") .()<- (expression form "a.(i) <- x") .(,) (expression form "a.(i,j)") .(,)<- (expression form "a.(i,j) <- x") .(,,) (expression form "a.(i,j,k)") .(,,)<- (expression form "a.(i,j,k) <- x") The .[] forms have default definitions as overloaded lookup and assignment on arrays, dictionarys, maps and any value supporting an Item property. The .() forms have default definitions as array lookup. In theory the operators can be redefined, e.g., the example below shows how to do this for byte arrays, but this is rarely used in practice: let (.[]) s n = Bytearray.get s n let (.[]<-) s n m = Bytearray.set s n m For compatibility with OCaml the following identifiers are parsed as infix operators, corresponding to logical bitwise manipulations: land lor lsl lsr lxor mod However the corresponding overloaded symbolic operators (&&& etc.) are often preferred. The following operators are assigned a meaning via lifted term quotation: quotation-operator-left := | <@ op-char* | « op-char* quotation-operator-right := | op-char* @> | op-char* » Identifiers. Identifiers follow the specification: letter-char := [ A-Z a-z ] ident-start-char := | letter-char | unicode-letter-char | _ ident-char := | letter-or-digit-char | unicode-letter-or-digit-char | _ | ' ident := ident-start-char ident-char* Unicode characters include those within the standard ranges. All input files are currently assumed to be UTF-8-encoded. See the C# specification for the definition of Unicode characters accepted for the above classes of characters. Note: as of v1.1.14 the compiler fsc.exe will not correctly output error messages in an appropriate encoded format, and may drop characters from identifiers containing Unicode formats. Strings and characters. String-like literals may be specified for two types: Unicode strings (type string = System.String) and unsigned byte arrays (type byte[] = bytearray). Literals may also be specified using C#-like verbatim forms that interpret "\" as a literal character rather than an escape sequence. escape-char := ["\'ntbr] simple-string-char := (any char except \ and ") string-char := | trigraph | unicodegraph-short | unicodegraph-long | newline | \ newline whitespace* | \ escape-char | simple-string-char verbatim-string-char := simple-string-char | \ | "" string := " string-char* " verbatim-string := @" verbatim-string-char* " bytearray := " string-char* "B verbatim-bytearray := @" verbatim-string-char* "B Unicode characters in UTF-8-encoded files may be directly embedded in strings, as for identifiers (see above), as may trigraph-like specifications of Unicode characters in an identical manner to C#: unicodegraph-short := '\\' 'u' hex hex hex hex unicodegraph-long := '\\' 'U' hex hex hex hex hex hex hex hex The precedence of operators and expression constructs is as follows, from lowest (least tightly binding) to highest (most tightly binding). The marker OP indicates the class of operator names beginning with the given prefix. Leading . and $ characters are ignored when determining precedence, so, for example, .* and $* have the same precedence as *. as %right when %right | %left ; %right let %nonassoc function, fun, match, try %nonassoc if %nonassoc -> %right := %right , %nonassoc or || %left & && %left not %nonassoc <OP >OP $OP = |OP &OP %left ^OP %right :: %right :?> :? %nonassoc -OP +OP -. %left *OP /OP %OP %left **OP %right ?? %left "f x" "lazy x" "assert x" %left "| rule" %right -- pattern match rules !OP ?OP ~OP %prefix . %left "f(x)" %left Where not specified the precedence is in the order of grammatical rules given in each section of this specification. Precedence of application with respect to the dot notation:: The entry "f x" in the table above refers to function application where the function and argument are separated by spaces. The entry "f(x)" indicates that in expressions and patterns, identifiers followed immediately by a parentheses without intervening whitespace form a "high precedence" application. These are parsed with higher precedence (i.e. binding more tightly) than prefix and dot-notation operators. This means that Example 1: B(e).C Example 2: B (e).C are parsed as Example 1: (B(e)).C Example 2: B ((e).C) respectively. Furthermore, arbitrary chains of method applications, property lookups, indexer lookups (.[]), field lookups and function applications can be used in sequence as long as the arguments of method applications are parenthesized and come immediately after the method name, without spaces, e.g., e.Meth1(arg1,arg2).Prop1.[3].Prop2.Meth2() Although strictly allowed by the grammar and the precedence rules above, a sanity check ensures that high-precedence application expressions may not be used as directly arguments, and must instead be surrounded by parentheses, e.g., f e.Meth1(arg1,arg2) e.Meth2(arg1,arg2) must be written f (e.Meth1(arg1,arg2)) (e.Meth2(arg1,arg2)) However indexer, field and property dot-notation lookups may be use as arguments without adding parentheses, e.g., f e.Prop1 e.Prop2.[3] Precedence of prefix operators with respect to the dot notation:: The precedence specification above largely follows the same rules as the OCaml language. One significant exception is the high-precedence application rule above. Another is that the expression "!x.y" parses as "!(x.y)" rather than "(!x).y". This is because the OCaml grammar uses uppercase/lowercase distinctions to make disambiguations like the following at parse time: Ocaml: !A.b.C.d == (!(A.b)).(C.d) Ocaml: !a.b.c.d == (((!a).b).c).d F#: !A.b.C.d == !(A.b.C.d) F#: !a.b.c.d == !(a.b.c.d) Note that in the first example '!' binds two elements of a long-identifier chain, and in the second it only binds one. Thus the parsing depends on the fact that 'A' is upper case and OCaml uses this fact to know that it represents a module name. F# deliberately allows values and module names to be both upper and lower case, and so F# cannot resolve the status of identifiers (i.e. whether an identifier is a module, value, constructor etc.) at parse-time, and instead does this when parsing long identifiers chains during typechecking (just as C# does). The above alteration means that parsing continues to remain independent on identifier status. In addition, F# ignores leading "."'s when determining precedence, to ensure operators such as ".*" (used for pointwise-operation on matrices) have the expected precedence. The lexical specification of constants is as follows: int := | digit+ -- e.g., 34 xint := | int -- e.g., 34 | 0 (x|X) hexdigit+ -- e.g., 0x22 | 0 (o|O) octaldigit+ -- e.g., 0o42 | 0 (b|B) bitdigit+ -- e.g., 0b10010 sbyte := xinty -- e.g., 34y byte := xintuy -- e.g., 34uy int16 := xints -- e.g., 34s uint16 := xintus -- e.g., 34us int32 := xintl -- e.g., 34l uint32 := xintul -- e.g., 34ul nativeint := xintn -- e.g., 34n unativeint := xintun -- e.g., 34un int64 := xintL -- e.g., 34L uint64 := xintUL -- e.g., 34UL ieee32 := float{F|f} -- e.g., 3.0F or 3.0f ieee64 := float -- e.g., 3.0 bigint := intI -- e.g., 34742626263193832612536171I bignum := intN -- e.g., 34742626263193832612536171N // Note: bigint and bignum constants specified using hexadecimals // and/or rationals are scheduled for inclusion but are not yet // implemented. // Note: Decimal constants are scheduled for inclusion but are not yet // implemented. bytestring := stringB bytechar := bytecharB float := -? digit+ . digit* -? digit+ (. digit* )? (e|E) (+|-)? digit+ Negative integers are specified using the approriate integer negation operator, e.g., -3. F# supports the optional use of lightweight syntax through the use of whitespace to make indentation significant. At the time of this release this is an experimental feature, though it is assumed that its use will become widespread. The indentation-aware syntax option is a conservative extension of the explicit language syntax, in the sense that it simply lets you leave out certain tokens such as in and ;; by having the parser take indentation into account. This can make a surprising difference to the readability of code. Compiling your code with the indentation-aware syntax option is useful even if you continue to use explicit tokens, as it reports many indentation problems with your code and ensures a regular, clear formatting style. The F# library is written in this way. Note:
In this documentation we will call the indentation-aware syntax option the "light" syntax option. It is also occasionally called the "hardwhite" or "white" option (because whitespace is "hard", i.e. significant as far as the lexer and the parser is concerned). The light syntax option is enabled using the #light directive in a source file. This directive scopes over all of the subsequent text of a file. When the light syntax option is enabled, comments are considered pure whitespace. This means the indentation position of comments is irrelevant and ignored. Comments act entirely as if they were replaced by whitespace characters. TAB characters may not be used when the light syntax option is enabled. You should ensure your editor is configured to replace TAB characters with spaces, e.g., in Visual Studio 2005 go to "Tools\Options\Text Editor\F#\Tabs" and select "Insert spaces". The basic rules applied when the light syntax option is activated are shown below, illustrated by example.
Here are some examples of the offside rule being applied to F# code:
In general, nested expressions must occur at increasing column positions in indentation-aware code, called the "incremental indentation" rule. Warnings or syntax errors will be given where this is not the case. However, for certain constructs "undentation" is permitted. In particular, undentation is permitted in the following situations:
Offside lines and contexts.Indentation-aware syntax is sometimes called the "offside rule". In F# code offside lines occur at column positions. For example, a = token associated with let introduces an offside line at the column of the first token after the = token. When a token occurs prior to an offside line, one of three things happens:
When a token occurs directly on an offside line, an extra delimiting token may be inserted. For example, when a token occurs directly on the offside line of a context introduced by a let, an appropriate delimiting separator token is inserted i.e. an in token. Offside lines are also introduced by other structured constructs, in particular at the column of the first token after the then in an if/then/else construct, and likewise after try, else, -> and with (in a match/with or try/with) and with (in a type augmentation). "Opening" bracketing tokens (, { and begin also introduce an offside line. In all these cases the offside line introduced is determined by the column number of the first token following the significant token. Offside lines are also introduced by let, if and module. In this cases the offside line occurs at the start of the identifier. The Pre-Parse Stack. The "light" syntax option is implemented as a pre-parse of the token stream coming from a lexical analysis of the input text (according to the lexical rules above), and uses a stack of contexts. When a column position becomes an offside line a "context" is pushed. "Closing" bracketing tokens (")", "}" and "end") automatically terminate offside contexts up to and including the context introduced by the corresponding "opening" token. Full List of Offside Contexts. The full list of contexts kept on the pre-parse stack is as follows. First, the following context is the primary context of the analysis: | SeqBlock -- Indicates a sequence of items which must be columned aligned, and where delimiters such as 'in' and ';' are automatically inserted as necessary between the elements. Pushed when 1. immediately after a '=' token is encountered in a Let or Member context 2. immediately after a Paren, Then, Else, WithAugment, Try, Finally, Do context is pushed 3. immediately after any infix token is encountered. 4. immediately after a '->' token is encountered when in a MatchClauses context 5. immediately after an 'interface', 'class', or 'struct' token is encountered in a type declaration Here "immediately after" refers to the fact that the column position associated with the SeqBlock is first token following the significant token. The following contexts are associated with particular nested constructs introduced by particular keywords: | Let -- pushed when a 'let' keyword is encountered | If -- pushed when an 'if' or 'elif' keyword is encountered | Try -- pushed when a 'try' keyword is encountered | Fun -- pushed when an 'fun' keyword is encountered | Function -- pushed when an 'function' keyword is encountered | WithLet -- pushed when a 'with' is encountered as part of a record expression or an object expression whose members use the syntax { new Foo with M() = 1 and N() = 2 } | WithAugment -- pushed when a 'with' is encountered as part of an augmentation, interface or object expression whose members use the syntax { new Foo member x.M() = 1 member x. N() = 2 } | Match -- pushed when an 'match' keyword is encountered | For -- pushed when a 'for' keyword is encountered | While -- pushed when a 'while' keyword is encountered | Then -- pushed when a 'then' keyword is encountered | Else -- pushed when a 'else' keyword is encountered | Do -- pushed when a 'do' keyword is encountered | Type -- pushed when a 'type' keyword is encountered | Namespace -- pushed when a 'namespace' keyword is encountered | Module -- pushed when a 'module' keyword is encountered | Member -- pushed when 1. a 'member', 'abstract', 'default' or 'override' keyword is encountered, (though only when not already in a Member context, as multiple tokens may be present) 2. a 'new' keyword is encountered, though only if the next token is '(' NOTE : this distinguishes the member declaration new(x) = ... from the expression new x() | Paren -- pushed when a '(', 'begin', 'struct', 'sig', '{', '[', '[|' or quotation-operator-left is encountered | MatchClauses -- pushed when 1. a 'with' keyword is encountered when in a Try or Match context 2. immediately after a 'function' keyword is encountered | Vanilla -- pushed whenever an otherwise unprocessed keyword is encounted in a SeqBlock context Exceptions to when tokens are offside .A set of fairly simple and essentially obvious exceptions are made when determining if a token is offside from the current context: When in a SeqBlock context, an infix token may be offside by the size of the token plus one. That is, in the following examples the infix tokens : let x = expr + expr + expr + expr // note: this plus looks 'offside' but isn't treated as such let x = expr |> f expr // note: this '|>' operator looks 'offside' but isn't treated as such |> f expr Similarly, when in a SeqBlock context, any infix token is permitted to align precisely with the offside line of the SeqBlock, without being considered offside, e.g.,: let someFunction(someCollection) = someCollection |> List.map (fun x -> x + 1) In particular, the infix token |> that begins the last line is not considered to be a new element in the sequence block on the right hand side of the definition. The same also applies to end, and, with, then, and right-parenthetical operators. For example, new MenuItem("&Open...", new EventHandler(fun _ _ -> ... )) In particular, the first ')' token here does not indicate a new element in a sequence of items, despite the fact that it's precisely aligned with the sequence block started at the start of the argument list. When in a Let context, an and token is permitted to align precisely with the let, without being considered offside, e.g.,: let x = expr and y = expr expr When in a Type context, and and | tokens are permitted to align precisely with the type, without being considered offside, e.g.,: type X = | A | B and Y = | D | E NOTE: while this formatting is permitted, but not considered terribly good style. Indent the type representation instead. When in a For context, a done token is permitted to align precisely with the for, without being considered offside, e.g.,: for i = 1 to 3 do expr done When in a Interface context, an end token is permitted to align precisely with the interface, without being considered offside, e.g.,: interface IDisposable with member x.Dispose() = printf "disposing!\n" done When in a If context, then, elif and else tokens are permitted to align precisely with the if, without being considered offside, e.g.,: if big then callSomeFunction() elif small then callSomeOtherFunction() else doSomeCleanup() When in a Try context, finally and with tokens are permitted to align precisely with the try, without being considered offside, e.g.,: try callSomeFunction() finally doSomeCleanup() and try callSomeFunction() with Failure(s) -> doSomeCleanup() When in a Do context, a done token is permitted to align precisely with the do, without being considered offside, e.g.,: for i = 1 to 3 do expr done This section describes the language elements of the F# language via fragments of the overall grammar and informal descriptions of the semantics of the constructs. Where appropriate quotes have been used to indicate concrete syntax, if the symbol is also used in the specification of the grammar itself, e.g., '<' and '|'. Constructs with lower precedence are given first. The notation { ... } indicates an optional element. The notation ... indicates repetition of the preceding non-terminal construct, with the optional repetition extending to surrounding delimiters e.g., expr ',' ... ',' expr means a sequence of one or more exprs separated by commas. ident := see above textual description of identifiers infix := see above textual description of operators prefix := see above textual description of operators string := see above textual description of strings char := see above textual description of chars longident := ident '.' ... '.' ident See the lexical section above for descriptions of the valid constant formats. const := | int -- 32-bit signed integer | sbyte | int16 | int32 | int64 -- 8, 16, 32 and 64-bit signed integers | byte | uint16 | int32 | uint64 -- 8, 16, 32 and 64-bit unsigned integers | ieee32 -- 32-bit floating-point number of type "float32" | ieee64 -- 64-bit floating-point number of type "float" | bigint -- Arbitrarily sized integer number of type "bigint" (aka "big_int") | bignum -- Arbitrarily sized rational number of type "bignum" (aka "num") | ieee64 -- 64-bit "Single" floating-point number of type "float32" | char -- Unicode character of type "char" | string -- String of type "string" (i.e. System.String) | bytestring -- String of type "byte[]" | bytechar -- Char of type "byte" The expression forms and related elements are as follows: expr := | expr ; expr -- sequence expression | begin expr end -- block expression | ( expr ) -- block expression | ( expr : type ) -- type annotation | let [inline] val-defns in expr -- locally bind values | let rec val-defns in expr -- locally bind mutually referential values | fun pat ... pat -> expr -- a function expression | function rules -- a function value that executes the given pattern matching | match expr with rules -- match a value and execute the resulting target | try expr with rules -- execute an exit block if an exception is raised | try expr finally expr -- always execute an exit block | if expr then expr else expr -- conditional | if expr then expr -- conditional statement | while expr do expr done -- while loop | for ident = expr to expr do expr done -- simple for loop | for pat in expr do expr done -- enumerable for loop | lazy expr -- delayed computation | assert expr -- checked computation | expr := expr -- assignment to reference cell | expr <- expr -- property and field assignment | expr.[expr] -- overloaded Item property lookup (operator ".[]") | expr.[expr] <- expr -- overloaded Item property lookup (operator ".[]") | expr.(expr) -- array lookup (operator ".()") | expr.(expr) <- expr -- array assignment (operator ".()<-") | expr , ... , expr -- tuple expression | { field-exprs } -- record expression | { expr with field-exprs } -- copy-and-update record expression | expr infix expr -- infix expression | prefix expr -- prefix expression | expr expr -- application/invocation | expr '.' expr -- member access | ident -- a value | () -- the "unit" value | { comprehension } -- enumerable or range comprehension | [ expr ; ... ; expr ] -- list expression | [ comprehension ] -- list comprehension | [| expr ; ... ; expr |] -- array expression | [| comprehension |] -- array comprehension | false | true -- boolean constant | const -- a constant value | new object-construction -- simple object expression | { new object-construction -- object expression with overrides and interfaces with val-or-member-defns interface-defns} | null -- the "null" value for a .NET type | ( expr :? type ) -- dynamic type test | ( expr : type ) -- static upcast coercion | ( expr :?> type ) -- dynamic downcast coercion | upcast expr -- static upcast coercion to inferred type | downcast expr -- dynamic downcast coercion to inferred type | (type type) -- reified type (C# 'typeof') | quotation-operator-left expr quotation-operator-right -- lifted term quotation | _ -- hole in a lifted term quotation val-defn := | pat ... pat {: type} = expr -- bind a value according to patterns | do expr -- execute a statement as a binding field-expr := | longident = expr -- specify a value for a field object-construction := | type(exprs) -- constructor call for an object expression for a class | type -- an object expression for an interface | object-construction as ident -- name the "base" object interface-defn := | type with val-or-member-defns -- specify an implemented interface val-or-member-defns := | val-defns -- an implemented interface or set of object overrides | member-defns -- same, with alternative syntax exprs := expr ',' ... ',' expr val-defns := val-defn and ... and val-defn field-exprs := field-expr ; ... ; field-expr interface-defns := interface-defn ... interface-defn The informal typing and evaluation semantics of expressions are as follows: Constant expressions. Constant expressions have the corresponding type and evaluate to the corresponding simple constant value. Sequence expressions. e1; e2 is a sequence expression and evaluates e1 and returns the result of evaluating e2 and has the same type as e2. A warning may be reported if e1 does not have type unit. Parenthesized expressions. (e1) is a parentheses expression and evaluates e1 and has the same type as e1. Block expressions. begin e1 end is a block expression and evaluates e1 and has the same type as e1. Binding expressions. let binds in expr is a binding expression and establishes bindings within the local lexical scope of expr and has the same type as e1. Mutually referential bindings are established using let rec. let may bind arbitrary patterns, whereas let rec may only bind named values. Note: The in token is optional when the #light syntax option is enabled and expr occurs on a subsequent line on the same column as the let. The in token is automatically inserted when the pre-parse context associated with the let token is closed. Function expressions. fun pat_1 ... pat_n -> e is a function expression and is of function type and evaluates to a function value. If only one pattern is present, then whenever the function value is invoked at some later point the input argument will be matched against the pattern, any results from the match will be bound and the expression e will be evaluated and its value will be the result of the corresponding funciton invocation. If multiple patterns are present, then the function expression evaluates to a curried function value. The result of applying the curried function value to one argument is a residual function value accepting n-1 arguments. Whenever n arguments have been recieved in total the arguments are matched against the input patterns, any results from the match are bound and the expression e is evaluated and returned as the result of the application. Multiple iterated arguments can be used, each specified by a pattern, e.g., fun x1 (x2,x3) -> e1 and pattern arguments (fun (MyData(x1,x2)) -> x1+x2+x3). No pattern matching is performed until all arguments have been recieved. Pattern matching expressions. match e1 with rules is a pattern matching expression and evaluates the given expression and selects a rule via pattern matching (see next section). Multiple values are efficiently matched using tuple expressions and tuple patterns. Pattern matching functions function rules are equivalent to single argument lambda expressions followed by immediate matches on the argument. Try-catch expressions. try e1 with rules is a try-catch expression. The expression e1 is evaluated and if an exception occurs then the pattern rules are executed against the resulting exception value. If no rule matches the exception is rethrown. The type ty of the overall expression is the same as the type of e1, and each rule of a try/with expression must match values of type exn (equivalent to System.Exception) and return values of type ty. Try-finally expressions. try e1 finally e2 is a try-finally expression. e1 is evaluated and the finally expression is executed regardless of whether an exception was by evaluation of e1. The overall expression has the same type as e1, and a warning is given if the type of e2 is not unit. Conditional expression. if e1 then e2 else e3 is a conditional expression. When evaluated the expression e1 is first evaluated. If it evaluates to true, expression e2 is evaluated and the result is the result of the overall expression. If it evaluates to false, expression e3 is evaluated and the result is the result of the overall expression. Both branches of conditional expressions must have equivalent (and not simply compatible) types. if e1 then e2 is a sequential conditional expression equivalent to if e1 then e2 else (). While expression. while e1 do e2 done is a while loop expression. Expression e1 is evaluated. If its value is true expression e2 is evaluated, and the loop is evaluated once more. If expression e1 evaluates to false the loop terminates. The overall type of the expression is unit. A warning will be reported if the body e2 of the while loop does not have static type unit. Note: The done token is optional when the #light syntax option is enabled and e2 occurs indented from the column position of the while and on a subsequent line. The done token is automatically inserted when the pre-parse context associated with the while token is closed. Simple for loops. for var = e1 to e2 do e3 done is a simple for loop expression. Expressions e1 and e2 are evaluated once, then expression e3 is evaluated repeatedly with the variable var bound to successive values in the range of e1 up to but not including e2+1. If e1 is greater than or e2+1 then e3 is never evaluated. The overall type of the expression is unit. A warning will be reported if the body e3 of the for loop does not have static type unit. Note: The evaluation of the construct is identical to let start = e1 in let finish = e2 + 1 in let rec f var = if var < finish then (e3; f (var+1)) in f start for fresh variables start, finish and f. Note: The done token is optional when the #light syntax option is enabled and e2 occurs indented from the column position of the for and on a subsequent line. The done token is automatically inserted when the pre-parse context associated with the for token is closed. Tuple expressions. e1,...,en is a tuple expression and is of tuple type (t1 * ... * tn) according to the types of the components. Each expression is evaluated in order, and the expression evaluates to the resulting tuple value. List expressions. [e1;...;en] is a list expression and is of list type ty list (see the type Microsoft.FSharp.Collections.List<ty>) according to the type of the components, each of which must have the same type. It evaluates each of the expressions in turn, returning the resulting list value. Array expressions. [| e1;...;en |] is an array expression and is of array type ty array according to the mutual type of the components and evaluates each of the expressions in turn, returning a new array containing the given values. See the advanced features for a discussion on how array types relate to .NET array types. Record expressions. { field-exprs } is a record construction expression. The expressions are evaluated in the order given and a record value of the appropriate type is generated. The labels of the fields must resolve to a unique record type given local type information (e.g., type annotations on the record expression itself) and the field names in scope. Copy-and-update record expressions. { expr with field-exprs } is a copy-and-update record expression. The expressions are evaluated in the order given and a copy of the record is made with the given values replaced by new values. The labels of the fields must resolve to a unique record type given local type information (e.g., the inferred type of the original expression and type annotations on the overall record expression itself) and the field names in scope. Application expressions. f e1 .. en is an application expression.
Long identifier expressions. id1. ... .idn is a long identifier expression. These may evaluate to values, method groups, fields or properties depending on the left-to-right resolution of the names taking into account open declarations and referenced external assemblies. Resolution may result in a residue long path that then gives rise to a member access expression. If the long identifier resolves to a value name then evaluation returns the result of the value. If a value or field is generic (polymorphic) then an instantiation for the flexible type variables in the polymorphism will statically inferred. If the long identifier resolves to a local mutable variable or byref-typed value then evaluation dereferences the location holding the value of the variable. A long identifier may also resolve to a method group or property. See the dot notation section for a discussion on how the dot notation is resolved in these cases. Member access expressions. expr1.id1 .. idn is a member access expression. These may evaluate to values, method groups, fields or properties. Resolution may result in a residue long path that then gives rise to a further member access expression. See the dot notation section for a discussion on how the dot notation is resolved. Lazy expressions. lazy e1 is a lazy expression, where e1 is evaluated on demand in response to a Lazy.force operation on the lazy value. Assignment expressions. e1 <- e2 is an assignment expression. e1 may evaluate to be a property, field or local mutable variable. e2 must be of the precise type required for the mutable location. Operators expressions. e1 op e2, op e1, e1.[e2], e1.(e2) and e1.(e2) < e3 are operator expressions (infix, prefix, string lookup, array lookup and array assignment respectively). Standard interepretations for operators are defined in Microsoft.FSharp.Core.Operators. Most operators are overloaded by default. Simple object expressions. new ty(e1 ... en) is a simple object expression where no overrides or interface implementations are specified. See the advanced section for details. If ty is a delegate type (i.e. a proper subtype of System.MulticastDelegate) then this is a delegate implementation expression. Such a delegate type will necessarily have an Invoke method with a signature Invoke(ty1,...,tyn) -> rty. In this case, the expression must be of the form new ty(e1) where e1 has type ty1 -> ... -> tyn -> rty. If tyn is a .NET void type then the standard translation to F#'s unit type is performed. See the interoperability section for more details. Object expressions. { new ty(e1 ... en) with val-defns interface-defns} is an object expression. The arguments may be omitted if ty is an interface type. See the advanced section for details. Enumerable loops. for pat in enum do e2 done is a enumerable loop expression. Typically enum is a value compatible with the type IEnumerable<ty>, for some type ty. In this case the loop is evaluated as follows, where v is of type IEnumerator<ty> and pat is a pattern of type ty. let v = enum.GetEnumerator() in try while (v.MoveNext()) do match v.Current with | pat -> e2 | _ -> () done finally (v :> System.IDisposable).Dispose() However, enum may also be any value that satisfies the 'collection pattern' of .NET, in which case it is enumerated via a process known as enumerable extraction. In particular, enum may be any value that has an accessible GetEnumerator method accepting one argument and returning a value with accessible MoveNext and Current properties. In this case the loop is evaluated in much the same way, except a dynamic check is inserted to detect if the enumerator satisfies IDisposable. The type of pat is typically determined by the return type of the Current property on the enumerator value. However Current property has return type obj and the collection type ty has an Item property with a more specific (non-object) return type ty2, then that type is used instead, and a dynamic cast is inserted to convert v.Current to ty2. let v = enum.GetEnumerator() in try while (v.MoveNext()) do match v.Current with | pat -> e2 | _ -> () done finally match box(v) with | :? System.IDisposable as d -> d.Dispose() | _ -> () Note: The done token is optional when the #light syntax option is enabled and e2 occurs indented from the column position of the for and on a subsequent line. The done token is automatically inserted when the pre-parse context associated with the for token is closed. Enumerable comprehensions. { for pat in enum ... }, { when ... } and { -> ... } are all enumerable comprehension expressions. See comprehensions below. Null expressions. null is a null expression. The is induces a null reference type constraint on the type of the term that the type directly supports the value null. See the interoperability section for a discussion on how nullness is treated. Type-annotated expressions. (e1 : ty) is an type annotated expression where ty is an inflexible type constraint and statically constrains the type of the given expression to be precisely the given type. Information from the annotation will be used to resolve overloading within e1 itself. Static coercion expressions. e1 :> ty is a static coercion expression, i.e. a flexible type constraint. The expression types to ty, but the type of e1 can be any type that is coercible to ty. See the upcasts and downcasts section for more information. Dynamic type test expressions. e1 :? ty is a dynamic type test expression. See the upcasts and downcasts section for more information. upcast(e1) is a static coercion expression where the target type is inferred from the local context. See the upcasts and downcasts section for more information. Use of the upcast expression form is deprecated. Dynamic coercion expressions. e1 :?> ty is a dynamic coercion expression. See the upcasts and downcasts section for more information. downcast(e1) is a dynamic coercion expression where the target type is inferred from the local context. Use of the downcast expression form is deprecated. Assertion expressions. assert(e) is an assert expression and evaluates the given expression, which must be of type bool, then raises an Microsoft.FSharp.Core.AssertionFailureException if the expression is false. Normally this expression is given type unit, however the syntactic form assert(false) is given a type 'a (it never returns). Note: the specification of the behaviour of assert may change in a future release. In particular, the behaviour may change to call System.Diagnostics.Debug.Assert prior to failing. Lifted term quotation expressions. The lifted term quotation forms capture a typed abstract syntax tree form of the typechecked quoted expression and invoke the given operator on the result. See the term quotation section for more detail. The permitted syntactic forms for types are as follows: type := | type -> type -- function type | type * ... * type -- tuple type | ( type ) -- parenthesized type | ident. ... .ident -- named type | typar -- variable type | type longident -- constructed type, e.g int list | ( types ) longident -- constructed type, e.g (int,string) map | longident'<';type'>' -- alternative syntax for constructed types, e.g., list<int> | type[] -- .NET array type | type[,] -- .NET two-dimensional array type | type lazy -- lazy type | typar :> type -- constrained type | #type -- anonymous constrained type | typar-defns. type -- first-class generic type, only for record field types typar := | _ -- anonymous type variable | 'id -- type variable | ^id -- static head-type type variable typar-defn := 'id Several forms are discussed in the section on constrained types. The semantics associated with the other forms are as follows:
The following terms are used elsewhere in this language specification:
Patterns are used to perform simultaneous case analysis and decomposition on values in conjunction with the match, try, function, fun and let expression and declaration constructs. Rules are attempted in order, left-to-right. when guards on rules are executed only once the match value has matched the pattern associated with a rule. rule := | pat {when expr} -> expr -- pattern, optional guard and action | pat {when expr} ->> expr -- yield rule, used only in comprehensions pat := | const -- constant pattern | longident -- variable binding, nullary data discriminant, nullary active discriminator or named literal | longident pat -- unary data discriminantor or active discriminator pattern | longident pat-exprs pat -- parameterized active discriminator pattern | pat as ident -- name the matched expression | pat '|' pat -- "or" (union) pattern | pat '&' pat -- "and" pattern | pat :: pat -- "cons" pattern | [pat ; ... ; pat] -- list pattern | [|pat ; ... ; pat|] -- array pattern | (pat,...,pat) -- tuple pattern | {field-pat ; ... ; field-pat} -- record pattern | _ -- wildcard pattern | pat : type -- pattern with equational type constraint | pat :> type -- pattern with subtyping constraint | :? type -- dynamic type test pattern | :? type as ident -- dynamic type test pattern, with named result | null -- null-test pattern field-pat := longident = pat pats := pat , ... , pat field-pats := field-pat ; ... ; field-pat rules := {'|'} rule '|' ... '|' rule
comprehension := | range-comprehension -- range comprehension | seq-comprehension -- enumerable comprehension range-comprehension := | expr '..' expr -- range comprehension | expr '..' expr '..' expr -- range comprehension with skip seq-comprehension := | for pat in enum seq-comprehension -- iterated comprehension | when expr seq-comprehension -- filter comprehension | match expr rule -- match comprehension | let pat = expr in seq-comprehension -- binding comprehension | -> expr -- single-yield comprehension | ->> expr -- multi-yield comprehension Range comprehensions.
Enumerable comprehensions. (comprehension) is an enumerable comprehension, and must be either a range comprehension or a iterated comprehension. The parentheses are required. The complete comprehension is translated as follows and then evaluated:
List comprehensions. [ comprehension ] is a list comprehension. It evaluates as IEnumerable.of_list(comprehension), where comprehension is treated as an enumrable comprehension as above. Array comprehensions. [| comprehension |] is an array comprehension. It evaluates as IEnumerable.to_array(comprehension), where comprehension is treated as an enumrable comprehension as above. Note: The overall type returned by an enumerable comprehension is determined by the yield clauses. A future version of F# may permit the use of this syntax in conjunction with other monadic constructs. Type definitions define new type constructors. Each type constructor is either an type abbreviation, record type constructor, discriminated union type constructor or class type constructor (see class definitions). type-defn := | type-name -- existing type (see type augmentations) | type-name simple-type-defn -- simple type definition | type-name class-or-interface-or-struct-defn -- class type definition type-name := | typar-defns id | id '<' typar-defns '>' simple-type-defn := | type -- type abbreviation declaration | {|} constr-defn | ... | constr-defn -- discriminated union type declaration | {|} enum-const-defn | ... | enum-const-defn -- enumeration definition | '{' recd-defn '}' -- record type declaration | delegate of type -- .NET-compatible delegate definition constr-defn := | id -- nullary constructor | id of type * ... * type -- n-ary constructor (anonymous record fields) | id of recd-defn -- n-ary constructor (named record fields) recd-defn := | '{' recd-field-defn ; ... ; recd-field-defn '}' recd-field-defn := | {mutable} id : type enum-const-defn := | id = const -- enum constant definition type-defns := type-defn and ... and type-defn All type definitions except type abbreviations define fresh, named types, distinct from other types. Examples: Many simple objects can be modelled as records, e.g. type Point = { x:int; y:int } Record fields may be labelled as mutable: type MutablePoint = { mutable x:int; mutable y:int } Record members may have function type: type PrintItem= { getNextChunk : unit -> string; format : string } Further examples are given in the QuickTour and elsewhere. Exception definitions define new data constructors that generate values that inhabit the arbitrarily extensible type exn (equivalent to System.Exception). Values of this and related types may also be generated by defining and using classes that extend System.Exception. Exception definitions may also abbreviate existing exception constructors, including existing .NET exception types where the exception type has a default constructor (a constructor with no arguments). exception-defn := | constr-defn -- exception constructor | id '.' ... '.' id -- exception abbreviation exception-defns := exception-defn and ... and exception-defn For exception definitions, abbreviations and nullary constructors are disambiguated according to resolution of the given identifier. Class definitions are used to define both class types and type augmentations associated with other named type definitions. Only a subset of constructs may appear as part of a type augmentation. class-or-interface-or-struct-defn := | class member-defns end -- .NET-compatible class definition | interface member-defns end -- .NET-compatible interface definition | struct member-defns end -- .NET-compatible struct definition member-defn := | inherit type {as id} -- inheritance definition | val recd-field-defn -- field definition | new {for {inherit|val}} pat {as id} = constr-expr -- constructor definition | member member-defn-body -- non-virtual method or property definition | static member member-defn-body -- static method or property definition | static type type-defn -- statically nested type | interface type -- interface member definition | interface type { with member-defns end } -- interface member default implementation | abstract member-spec-body -- dispatch method definition | (override|default) member-defn-body -- dispatch method default implementation member-defn-body := | val-defn -- static method or property definition | ident '.' val-defn -- instance method or property definition | ident with val-defns -- static property definition | ident '.' ident with val-defns -- instance property definition (must define get and/or set) member-defnsM := member-defn ... member-defn (NOTE: constr-expr is a simplified form of expr) constr-expr := | stmt ';' constr-expr -- sequence expression (action before) | constr-expr then stmt -- sequence expression (action after) | if expr then constr-expr else constr-expr | let val-decls in constr-expr | object-initialization-expr object-initialization-expr := | '{' field-exprs '}' | '{' inherit expr; field-exprs '}' Property definitions must define a get or set method. A get method is assumes for the short syntax, e.g. type Data = { first: string; second: string; third: string; } with // short syntax: a read property member x.First = x.first // long syntax: a read/write property member x.Second with get() = x.second and set(v) = x.second <- v // long syntax: a read property member x.TwiceThird with get() = x.third * 2 end Indexer properties are properties accepting arguments. By convention only the Item property accepts arguments. This property can be accessed using the overloaded operator .[], e.g. here is the definition of an Item property on the type CTest that wraps an instance of the type Dictionary: open System.Collections.Generic type CTest = class val data : Dictionary An inherits member specifies that a type should extend both the interface and implementation of the given type. If no inheritance clause is given for a class then the default is System.Object. Multiple inheritance clauses may be given for interfaces. No inheritance clauses may be given for value classes (structs), delegates or enumerations. A member new pat = constr-expr is a constructor and represents a way of initializing the val fields of a class. It can be used to create values associated with an object and to partially initialize the object from a subclass. Constructors must be implemented by construction expressions, which are a subset of expression forms. Side effects can be performed after the initialization of the fields of the object by using the constr-expr then stmt form. The object expressions that terminate each branch of a construction expression must initialize the fields of the object and specify a call to a superclass constructor. No call to a superclass constructor is required if the superclass is System.Object. A new member may not by default access the object being constructed, because doing so would permit access to uninitialized fields. To access the object being constructed use new(...) as id = .... A warning may be reported to the user when this construct is used. Any evaluation of a reference to this variable prior to the completion of execution of the object-initialization-expr within the constr-expr is to throw an exception, e.g., a NullReferenceException. Delayed values such as function values that capture the variable will not cause an error. After the completion of the execution of the object-initialization-expr references to this variable produce the correct results. See also reactive recursion. An interface member indicates that objects of the given type support the given interface. Interface implementations may be given in augmentations. A val member is a value associated with values of the class and is configured by constructors. An abstract method or property member represents a way of invoking configurable functionality (note that a field holding a function value may also be used for this purpose, though these are configured by constructors and not subclasses, and may not be given default values). Abstract members may be given default values using override and/or default members (these are currently synonyms, though override should be used in subclasses and default in the class where the original declaration of the abstract member is given). Other members are not configurable either by subclasses or constructors. A static method or property member is associated with the type, rather than any particular object. A non-virtual method or property member acts on a given instance of an object of the given class. Method or property definition bodies (member-defn-body) admit only limited syntactic forms. The first pattern of a simple member definition or member role definition must be either a simple identifier or of the form id '.' id, the first corresponding to a static member and the second an instance member. In the latter case the identifier is bound to the "this" of "self" variable associated with the object. An explicit property definition such as member x.MyName with get() = "Alfie" is used to define the implementation of the get or set semantics of a property. The val-defn part of the member-defn-body must define a value called get or set. Sample immutable and mutable properties are as follows: type MyClass = class val instanceField: string val mutable adjustableInstanceField: string member x.InstanceProperty = x.instanceField + ".InstanceProperty" member x.MutableInstanceProperty with get() = x.adjustableInstanceField and set(v:string) = x.adjustableInstanceField <- v end Property members of all kinds may be indexer properties. Sample indexer properties are as follows: type MyClass = class ... member x.InstanceIndexer with get(idx) = x.instanceArray.(idx) member x.InstanceIndexer2 with get(idx1,idx2) = x.instanceArray2.(idx1).(idx2) member x.MutableInstanceIndexer with get (idx1) = x.adjustableInstanceArray.(idx1) and set (idx1) (v:string) = x.adjustableInstanceArray.(idx1) <- v static member StaticIndexer with get(idx) = staticArray.(idx) val instanceArray: string[] val instanceArray2: string[,] val adjustableInstanceArray: string[] ... end Indexer properties called Item are special in the sense that they are accessible via the .[] notation. An Item property taking one argument is accessed using x.[i], and when taking two arguments via x.[i,j] etc. Methods are normally written taking multiple arguments using a tuple syntax. Methods are normally written taking multiple arguments using a tuple syntax. Among other things this ensures that the method has the expected signature when used from other .NET languages. type TestClass class ... val instanceField : string member x.InstanceMethod(s1) = Printf.sprintf "In %s.InstanceMethod(%s)" x.instanceField s1 static member StaticMethod(s1,s2) = Printf.sprintf "In StaticMethod(%s,%s)" s1 s2 ... end Methods may also be written taking multiple arguments in iterated ("curried") form. However, these are really methods accepting one argument and returning a function value as a result. That is the sample: type TestClass class ... static member StaticMethod2 s1 s2 = Printf.sprintf "In StaticMethod(%s,%s)" s1 s2 ... end is equivalent to: type TestClass class ... static member StaticMethod2 s1 = fun s2 -> Printf.sprintf "In StaticMethod(%s,%s)" s1 s2 ... end Multiple methods of the same name may appear in the same class definition or augmentation. Methods must be uniquely identified by name and number of arguments, or else annotated with an Microsoft.FSharp.Core.OverloadIDAttribute, and in any cases methods must also be distinct based on their name and fully inferred types. Adding an OverloadID attribute to a member permits it to be part of a group overloaded by the same name and arity. The string argument to the attribute must be a unique name amongst those in the overload set. Any overrides of this method, if permitted, must be given the same OverloadID, and the OverloadID must be specified in both signature and implementation files if a signature file is provided for the definition. type MyForm = class inherit System.Windows.Form [<OverloadID("1")>] new(s: string) = { inherit Form(); x = "abc" } [<OverloadID("2")>] new(i: int) = { inherit Form(); x = string_of_int i } end TBD TBD TBD Type augmentations associate instance and static members with an existing type. type-defn := | ... | type-defn with type-augmentation-defn end -- augmented type type-augmentation-defn := class-or-interface-or-struct-defn
The process of defining class types, interface types and type augmentations specifies an implementation mapping for each type. This maps implemented interface methods and implemented class abstract method slots (collectively known as "dispatch slots") to values. Interface member slots are qualified by the particular interface type being implemented, thus a type may supply different implementations for I.m() and I2.m(), despite the fact that the members have the same names. The construction of this mapping for any particular type is straight-forward: where an augmentation gives an implementation of an interface then mappings are added for each member of the interface, and where an augmentation gives a default or override member then a mapping is added for the associated abstract member slot being implemented. Modules and Implementation Files (.ml or .fs). Modules are named collections of definitions. Items in modules are accessed via long identifiers. An implementation file may contain a single collection of definitions that is treated as a module. A name for that module can be given at the head of the file, or it can be implicitly inferred from the file name. An implementation file may also contain multiple such module fragments. A namespace to contain these module fragments may be optionally given at the head of the file. A module may also contain multiple such namespace fragments (thus a single file may contribute constructs to multiple namespaces) module-member-defn := | let {rec} val-defns -- top level value definitions | type type-defns -- type definitions | exception exception-defns -- exception definitions | module longident = longident -- locally alias a module | module longident = submodule-spec -- declare a submodule | open longident -- provide implicit access to the given module | do expr -- module initialization expression submodule-spec := | ( module-member-defns ) | begin module-member-defns end | struct module-member-defns end -- OCaml-compatible syntax module-member-defns := module-member-defn ... module-member-defn module-defn := | module longident module-member-defns -- named module | module-member-defns -- anonymous module namespace-fragment := | namespace longident module-defns -- modules within a namespace | module-defns -- modules without namespaces namespace-fragments := namespace-fragment ... namespace-fragment implementation-file := namespace-fragments -- The do in a module initialization expression can be omitted when using the #light syntax option. Anonymous modules are those without either a leading module or namespace declaration. The names of these modules are implicit from the name of the source file that contains the module, with the extension removed and the first letter capitalized. Module Signatures and Signature Files (.mli or .fsi). Signature files give a precis of the functionality implemented by a corresponding implementation file. Essentially all constructs and sub-constructs can be hidden by signatures, with the following exceptions:
val-spec := | ident: type -- value specifciation type-spec := | type-name -- abstract type specification | type-name = simple-type-defn -- simple type specification | type-name = class-spec -- class type specification class-spec := | class member-specs end | struct member-specs end -- not yet implemented in this release | interface member-specs end member-spec := | interface type | inherit type | val recd-field-defn | {abstract} new : type -- constructor specification | abstract member-spec-body -- dispatch slot definition | member member-spec-body -- method or property definition | static member member-spec-body -- static method or property definition | (override|default) member-spec-body -- override/default method or property definition | static type type-spec -- statically nested type member-specs := member-spec ... member-spec member-spec-body := | ident: type -- method or property definition | ident: type with {get|set|get,set} -- explicit property specification exception-spec := | constr-spec -- exception constructor | id '.' ... '.' id -- exception abbreviation | exception-spec with class-spec end -- augmented exception specification type-specs := type-spec ; ... and ... ; type-spec module-member-spec := | val val-spec -- value specifciation | type type-specs -- type(s) specifciation | exception exception-spec -- exception specifciation | module id : sig module-specs end -- submodule specifciation | module longident = longident -- locally alias a module module-member-specs := module-member-spec ... module-member-spec submodule-spec := | ( module-member-specs ) | begin module-member-specs end | struct module-member-specs end -- OCaml-compatible syntax module-spec := | module longident module-member-specs -- specification of named module | module-member-specs -- specification of anonymous module namespace-fragment-spec := | namespace longident module-specs -- specification of modules within a namespace | module-specs -- specification of modules without a namespace namespace-fragments-spec := namespace-fragment-spec ... namespace-fragment-spec module-signature-file := namespace-fragments-spec Anonymous module specifications are those without either a leading module or namespace declaration. The names of these module specifications are implicit from the name of the source file that contains the module, with the extension removed and the first letter capitalized. Note: types for value specifications are syntactically identical to types except the parenthesization has additional significance for typechecking and interoperability. See the advanced section of the manual for more details. Type checking is the process of enforcing the typing rules for each construct through a top-to-bottom, inside-out,left-to-right analysis of the constructs in a file or fragment of interactive input. Most constructs exhibit simple, standard type checking rules, requiring, for example, that actual arguments have the same type as formal arguments, or that the two branches of an if ... then ... else (or all the branches of a match) have identical types. The full informal specification of type inference is under development. For now, please see the informal specifications of the generalization, the dot notation, subtype constraints, operator overload constraints and constraint solving and checking for subtype constraints. Generalization is the process of giving certain constructs generic (i.e. polymorphic or type-parameterized) types if possible, thereby making the construct re-usable at multiple different types. Generalization is applied by default at all let, member and let rec bindings, with the exceptions listed below. Generalization is also applied to expressions that provide the initial values for fields that have first-class generic types. Generalization is only applied to values (i.e. lambda expressions, references to other F# values and constructed data). Generalization typically gives a construct a maximally generalized type, i.e. whenever a type variable (normally introduced by type inference, though perhaps by a type annotation) occurs in the inferred type of a bound value, up to equational constraints, then then that type variable will become a "type parameter" of the value(s). Bindings on the right of a let rec are typically functions (i.e., lambda expressions), and thus qualify for generalization, though see also reactive recursion, where limitations on generalization apply. Certain additional limitations on generalization apply even for functions when using constructs that provide a form of pseudo-flexibility: e.g., see the limitations on pseudo variables arising from operator overloading constraints. These restrictions do not apply if a function is marked inline, as copies of code are made and thus further concrete information is available to resolve the constraints. ByRef Arguments and Mutable Locals. "ByRef" arguments are possibly-stack-bound pointers used to pass large inline data structures and non-escaping mutable locations to procedures in .NET languages. ByRef pointers are almost totally unnecessary in F# because of the use of tuple values for multiple return values and reference cells for mutable store. However, ByRef values can arise when overriding .NET methods that have signatures involving byref values. When calling a function that accepts a byref parameter a value of type ty ref must currently be passed. The F# compiler takes the interior address of the heap-allocated cell associated with such a parameter and passes it as the pointer argument. When implementing a function that accepts a byref arguement, the argument is implicitly dereferenced wherever it is used, and a "local mutation" assignment operator id <- expr can be used to assign into the value. C# code: public class C { static public void IntegerOutParam(out int x) { x = 3; } } public class D { virtual public void IntegerOutParam(out int x) { x = 3; } } F# client code: let res1 = ref 0 in C.IntegerOutParam(res) // res1.contents now equals 3 let x = {new D() with IntegerOutParam(res : int byref) = res <- 4} in let res2 = ref 0 in x.IntegerOutParam(res2); // res2.contents now equals 4 Strict restrictions are imposed to ensure that ByRef arguments do not escape the scope of the implementing method except by being dereferenced. This means they cannot be used inside inner closures within the implementing method - they should be dereferenced first, stored in an local value (which can be used by inner closures), and copied back at the exit of the method. In this context a "method" consists of all constructs within the implementing expression except those enclosed by a function, lambda expression or one of the implementation functions of an object expression. F# generic values and types may not be instantiated with byref types. This limitation is not checked as of version 1.1.14. Mutable locals: Let-bound variables may be marked as mutable. These variables are under the same restrictions as byref arguments, and are similarly implicitly dereferenced. The AddressOf Operators: Prefix uses of the & operator take the address of a mutable local variable or byref-valued argument. If e has type T then &e has type byref<T>. If e has type T then &e has type nativeptr<T>. (Note: these operators may not currently be used to acquire an interior address of a field of an object or of an element in an array.) Use of these operators may result in unverifiable .NET IL code being generated, and a warning will typically be given. It's use is recommend only to pass addresses where byref or nativeptr parameters are expected, or to pass a byref parameter on to a subsequent function. NOTE: uses of the type constructors byref and ilsigptr and values in the Microsoft.FSharp.NativeInterop module may result in the generation of invalid or unverifiable .NET IL. In particular, these types may NOT be used within constructed types such as tuples or function types, so their use is highly constrained. They may be used as the argument type specifications of DllImport annotated functions and class member signatures. NOTE: when calling an existing .NET signature that uses a .NET pointer type create a value of type ilsigptr rather than a value of type nativeptr. Variable types may be constrained, requiring any instantiation of such a type to meet the constraint. A richer set of constraints is supported for pseudo-variable types, which are only generalized at pseudo-functions (ones marked inline), i.e. ones implemented by code-expansion techniques. type := | ... | type when constraints -- explicitly scoped constraints, for specifications of types of values | typar :> type -- constrained type | #type -- anonymous constrained type The syntactic forms for constraints on variable types are as follows: constraint := | typar = type -- equational constraint | typar :> type -- coercion constraint | typar : null -- constraint that a reference type supports null | typar : (member-spec) -- member "trait" constraint The following constraint forms are for compatibility with the full set of constraints permitted on generic .NET constructs and are less frequently used in F# programming: constraint := | ... | typar : (new : unit -> 'a) -- .NET-compatible default constructor constraint | typar : struct -- .NET-compatible non-Nullable struct constraint | typar : not struct -- .NET-compatible reference type (syntax under revision) | default typar : type -- Default to the given type if not generalized constraints := constraint and ... and constraint Constrained types are of the form typar :> type, and also arise from the constructs #type, expr :> type and pattern :> type. They also arise from the implicitly flexible interpretation of member signatures. An anonymous constrained type #type is equivalent to the use of an anonymous type variable _ :> type. Type checking ensures that each use of a value or type whose specification involves constrained type parameters will induce a constraint on the actual parameters associated with the use of that item. Member constraints arise when using operators +, - etc., and from other values built in terms of these values or other values with signatures annotated with member constraints. For example, the operator + is defined in the F# library with the following signature: val inline (+) : ^a -> ^b -> ^c when ^a : (static member (+) : ^a * ^b -> ^c) This indicates that the nominal types of ^a, ^b and ^c must be known at compile time (the meaning of the ^ annotation, see below), and that ^a must support a static member called + (whose encoded .NET name is op_Addition) with the given signature. This indicates that the may be used on two values where the first supports a static member operator + (whose encoded .NET name is op_Addition, in C# written static operator +(...) in C#). In some cases statically resolving the set of operators supported by a constrained type may require the use of overload resolution. Uses of overloaded operators are ultimately resolved statically. In particular, uses do not give rise to generalized code unless definitions are marked as inline . For example, the function let f x = x + x gives rise to a function f that can only be used to add one type of value, e.g. int or float -- the exact type will be determined either by later operations in the file, or by a type constraint. In these cases it can be a good idea to add a type annotation to the code to indicate the type of value being manipulated by the operator, e.g. let f (x:int) : int = x + x
In some cases the set of operators supported by the constrained type may require the use of overload resolution. Under this scheme new type definitions need only support the relevant static members. Here is an example showing the definition of overloaded operators for a type. These members can either be defined in an augmentation (as below) in the same file as the type definition or at the original definition site of the type. type BigInt with static member ( + )(n1,n2) = add n1 n2 static member ( * )(n1,n2) = mul n1 n2 static member ( - )(n1,n2) = sub n1 n2 static member ( / )(n1,n2) = div n1 n2 static member ( ~- )(n1) = neg n1 static member ( ~+ )(n1:BigInt) = n1 end Member constraints can only be placed on pseudo head type variables, written ^a, which lead to an additional requirement that the "head type" (i.e. type constructor name) of a type must be known at compile-time. Explicit uses of inline annotations are required to make sufficient static-resolution information available at compile time. Member-constrained operators such as + may also be used on built-in integer and floating-point types such as int (an abbreviation for System.Int32). These are considered by F# to implicitly define operators such as op_Addition, even though the actual .NET metadata for types does not contain the definition of these operators. This is one of the reasons why static compile-time resolution is required for all uses of inlined operators. Values such as (+) need implementations that specify how the operator is mapped to a call that invokes a member constraint. For example, the default mapping for the operator (+=) has signature: val inline (+=) : ^a -> 'b -> unit when ^a : (static member (+=) : ^a * 'b -> unit) and is defined as follows: let inline ( += ) (x:^a) y : unit = (^a: (static member ( += ): ^a * 'b -> unit) (x,y)) The expression form on the right indicates, in fairly verbose syntax, that the effect of calling x += y is to invokve the static member named += on the type ^a. Sound implementations of operators such as (+) need more work, because of the lack of actual implementations of these operators for the primitive types, as mentioned above. There are numerous examples in the F# library of the implementation of these operators. Constraints are solved, or partially solved as follows:
Constraint Solving and Checking for Subtype Constraints Constraints are solved, or partially solved as follows:
Examples of Constraints In a signature a value declaration may be annoated with constraints. The most primitive way to do this is to use a when annotation on a value declaration. The same declaration can be written using the following more convenient syntactic forms: val throw: 'e -> unit when 'e :> System.Exception val throw: (_ :> System.Exception) -> unit val throw: ('e :> System.Exception) -> unit val throw: #System.Exception -> unit These notations are all equivalent, and mean that the function that accepts any subtype of Exception. For example: ... throw (new ArgumentException("Failure")) ... Note that if the signature were just val throw2: Exception -> unit then the caller would need to give an explicit upcast conversion when using this function, e.g., ... throw2 (new ArgumentException("Failure") :> Exception) ... Writing inflexible types is necessary in many situations, especially when writing constructed types such as functions and collections, For example, List<Exception> indicates a collection holding exception values. List<#Exception> is a form of type rarely used: its interpretation can be judged from the expanded form, e.g., val f: List<#Exception> -> unit is identical to val f: List<'a> -> unit when 'e :> System.Exception Constraints are propagated to inferred types. For example, the C# signature for the .NET construct System.IO.BinaryWriter is: System.IO.BinaryWriter(Stream x) As specified below, a call to this function interprets the signature in a way that permits any subtype of Stream to be passed to the first argument. Thus the following F# code: open System.IO let to_binary_writer s = new BinaryWriter(s) will infer the type val to_binary_writer: #Stream -> BinaryWriter That is, the constraint has propagated to the inferred type of the value. You could also add this as a type constraint annotation: let to_binary_writer (s :> Stream) = new BinaryWriter(s) A number of default overloaded operators are defined in the default library mllib.dll. All pseudo type variables default to attempting to operate over the int type should there be no other type information in the file to further constrain the use of the operator. The following are some of the operators defined in the standard library with their minimum signatures: // standard arithmetic operators val (+) : ^a -> ^b -> ^c when ^a : (static member (+) : ^a * ^b -> ^c) val (-) : ^a -> ^b -> ^c when ^a : (static member (-) : ^a * ^b -> ^c) val ( * ): ^a -> ^b -> ^c when ^a : (static member ( * ) : ^a * ^b -> ^c) val (/) : ^a -> ^b -> ^c when ^a : (static member (/) : ^a * ^b -> ^c) val (%) : ^a -> ^b -> ^c when ^a : (static member (%) : ^a * ^b -> ^c) // bitwise operators val (&&&): ^a -> ^a -> ^a when ^a : (static member (&&&) : ^a * ^a -> ^a) val (|||) : ^a -> ^a -> ^a when ^a : (static member (|||) : ^a * ^a -> ^a) val (^^^): ^a -> ^a -> ^a when ^a : (static member (^^^) : ^a * ^a -> ^a) val (~~~) : ^a -> ^a when ^a : (static member (~~~) : ^a -> ^a) // shifting operators val (<<<): ^a -> int -> ^a when ^a : (static member (<<<) : ^a * int -> ^a) val (>>>): ^a -> int -> ^a when ^a : (static member (>>>) : ^a * int -> ^a) // OCaml compatible modulus, shifting and bitwise operators val (land): ^a -> ^a -> ^a when ^a : (static member (&&&) : ^a * ^a -> ^a) val (lor) : ^a -> ^a -> ^a when ^a : (static member (|||) : ^a * ^a -> ^a) val (lxor): ^a -> ^a -> ^a when ^a : (static member (^^^) : ^a * ^a -> ^a) val (lsl): ^a -> int -> ^a when ^a : (static member (<<<) : ^a * int -> ^a) val (lsr): ^a -> int -> ^a when ^a : (static member (op_ShiftRightLogical) : ^a * int -> ^a) val (asr): ^a -> int -> ^a when ^a : (static member (>>>) : ^a * int -> ^a) val (mod): ^a -> ^b -> ^a when ^a : (static member (%) : ^a * ^b -> ^a) // scalar multiplication, $ is on the scalar side. The matrix and vector types // in the F# library support these. val ( $* ) : 'a -> ^b -> ^b when ^b : (static member ( $* ) : 'a * ^b -> ^b) val ( *$ ) : ^a -> 'b -> ^a when ^a : (static member ( *$ ) : ^a * 'b -> ^a) // point-wise operations on aggregates. The matrix and vector types in the F# // library support these. val ( .* ) : ^a -> 'b -> 'c when ^a : (static member ( .* ) : ^a * 'b -> 'c) val ( .^ ) : ^a -> 'b -> 'c when ^a : (static member ( .^ ) : ^a * 'b -> 'c) val ( ./ ) : ^a -> 'b -> 'c when ^a : (static member ( ./ ) : ^a * 'b -> 'c) val ( .% ) : ^a -> 'b -> 'c when ^a : (static member ( .% ) : ^a * 'b -> 'c) val ( .+ ) : ^a -> 'b -> 'c when ^a : (static member ( .+ ) : ^a * 'b -> 'c) // In-place mutation operators. The matrix and vector types in the F# // library support these. val (+=) : ^a -> 'b -> unit when ^a : (static member (+=) : ^a * 'b -> unit) val (-=) : ^a -> 'b -> unit when ^a : (static member (-=) : ^a * 'b -> unit) val ( *= ): ^a -> 'b -> unit when ^a : (static member ( *= ) : ^a * 'b -> unit) val (/=) : ^a -> 'b -> unit when ^a : (static member (/=) : ^a * 'b -> unit) Implicit Flexibility of Types at Member Applications. Flexibility is implicitly added to the signatures of all members whenever they are used in a member application expression. This is because members either derive directly from .NET object model metadata (e.g., from external .NET assemblies written in other languages), where there is no tradition of declaring coercion flexibility explicitly through the use constraints, or else members derive from F# classes being used to implement or extend existing .NET abstractions. The flexibility added is as follows:
Thus the interpretation of the signatures of members and values is inherently different, though only in the sense that additional flexibility may need to be explicitly recorded when writing the signatures of values. Overload resolution for member applications proceeds as follows. The inputs to the process are a member set, representing a set of overloads, a syntactic argument expression, an expected partial return type for the application, and an overall set of constraints on inference type variables that represents prior knowledge accumulated concerning syntactic elements in the argument expressions. Firstly, the member arguments are determined by decomposing the argument expression according to whether it is a syntactic tuple. Additional parentheses can be used to distinguish the application of a single argument made up of a tuple x.M((a,b)) from the application of multiple arguments x.M(a,b). Secondly, member signatures are interpreted as specified in section member signatures. Overload resolution is then performed according to the following rules:
In these three rules the coercion constraint between expected return type and formal method return type is only utilized when the name of the member being invoked is op_Explicit or op_Implicit. This is because these are the only methods in the .NET object model which may be overloaded on return type alone. In all other cases overload resolution is performed based on arguments alone. The following additional rules are also applied at member applications (but never at value applications):
Structural Comparison and Hashing. F# values can be structurally compared and hashed using "polymorphic" operations such as compare. Indeed, every time you're using operators such as <, >, <=, >=, =, <>, compare, min and max in F# code you may be invoking structural comparison. You may also be using structural comparison and structural hashing when you use the default configurations of F# data structures such as Set, Map, HashSet and HashTable (see also Hashtbl module), or when you instantiate .NET data structures using the values produced by Microsoft.FSharp.Collections.HashIdentity.Structural. This is because F#-defined types implicitly implement the interfaces System.IComparable and Microsoft.FSharp.Core.IStructuralHash, and the implementations of the polymorphic operations utilize these interface implementations. The relevant interfaces are defined as follows: namespace System type IComparable = interface abstract CompareTo : obj -> int end namespace Microsoft.FSharp.Core type IStructuralHash = interface abstract GetStructuralHashCode : &nNodesRemaining -> int end The implicit implementations of these interfaces contribute to a cooperative implementation of a term ordering for non-recursive terms and a hash function compatible with that term ordering. Recursive calls to compare subterms should use any of the following values, all of which access the "generic" compare functionality, while also making appropriate null checks in the cases where F# values may be represented by null values: Microsoft.FSharp.Core.Operators.compare : 'a -> 'a -> int Microsoft.FSharp.Core.LanguagePrimitives.StructuralComparison : 'a -> 'a -> int The unoptimized forms of these functions convert their parameters to object form using box operations, then examine the objects for the presence of the IComparable interface. In addition strings are always compared using System.String.CompareOrdinal, and arrays are compared by structural comparison of their lengths and components. ( Note: in practice type-optimized forms are used in nearly all situations. Limitation: multi-dimensional arrays cannot be structurally compared in this release.). If values do not support any of these comparison techniques the results are undefined and a runtime error may occur. (The .NET standards for object comparison define a way to fully exclude the possibility of runtime errors during comparison - this accords with the semantics of structural comparison in OCaml). IStructuralHash is like IComparable, and is intended to implement a hash code where structurally equal items hash to the same value. The external interfaces to invoke structural hashing are as follows: Microsoft.FSharp.Core.LanguagePrimitives.StructuralHash : 'a -> int Microsoft.FSharp.Core.Operators.hash : 'a -> int The non-optimized implementations of these functions convert their parameter to object form using box operations and then examine the object for the presence of the IStructuralHash interface. If that is not present then a call to Object.GetHashCode is used instead. (Note: in practice type-optimized forms are used in nearly all situations.) The partial implementation function GetStructuralHashCode accepts a byref argument nNodesRemaining which should (in principle) be decremented by the number of meaningful nodes hashed in the term. Recursive calls to hashing should (in principle) pass this precise address, using Microsoft.FSharp.Core.LanguagePrimitives.StructuralHashParam : 'a -> nNodesRemaining:int byref -> int The argument nNodesRemaining is correctly checked and reduced by compiler derived hashing functions (see below). Current Limitation. Because of limitations in the current release byref params may only be copied-out and copied-back at method calls, and the copy-back operations may inhibit essential tailcall optimizations. Hence, the above function is not yet provided for use from user-defined structural hashing operators, and recursive hashing calls on polymorphic values (values of variable type) must be implemented using user recursive calls to the hashing functions defined above. Record and union type definitions implicitly derive support for both System.IComparable and Microsoft.FSharp.Core.IStructuralHash. Types defined to be interfaces, delegates, structs and classes do not, and these types must often be explicitly implemented for classes. For record and union types the derived functions guarantee to implement a term ordering amongst terms that consist purely of record data, union data, and well-behaved .NET primitive types such as System.Int32 that support System.IComparable and which implement value semantics for GetHashCode. The default implementations of these two interfaces for record and union types may be overriden by declaring an alternative implementation of one or both interfaces in a type augmentation attached to the definition of the type. F# types do not by default specify overrides for Object.ToString or Object.GetHashCode. The latter is used by serialization and other .NET system functionality to implement object-identity based operations on term graphs, and hence cannot safely be overriden by a structurally hashing operator. Object types structurally hash and compare using a combination of comparisons of the locally defined data and calls to the base implementations of the given interfaces. Exception values built via exception constructors derive support for these interfaces in the same way as the process described above. Floating point NaN values require special attention in comparison. When uses of the operators <, >, <=, >=, = and <>. are applied to two floating point values the IEEE rules for NaNs apply, i.e. if either argument is a NaN then the result is false (true for <>). This only applies for the use of the operators on two floating point values -- it does not apply to the use of these operators on compund data structures involving floating point values, where the semantics of comparisons involving NaN is unspecified. Events are the .NET notion of a "wire" or "listening point", that is, a configurable objects holding a set of callbacks, which can be 'triggered', often by some external action such as a mouse click or timer tick. In F#, events are first class values, i.e., are objects that mediate the addition and removal of listeners from a backing list of listeners. The F# library supports a module Microsoft.FSharp.Control.IEvent that contains some operations for mapping, folding, creating and composing events. The IEvent<_> type is at the heart of this composable event model. The definition of the type is as follows: type IEvent<'a> = interface /// Connect a listener function to the event. The listener will /// be invoked when the event is fired. abstract Add: ('a -> unit) -> unit end Events from .NET languages are revealed as object properties of type Microsoft.FSharp.Control.IDelegateEvent<_,_>, which is a subtype of the type IEvent<_>. The type arguments to the IDelegateEvent are determined by the F# compiler. The definition of IDelegateEvent is as follows: type IDelegateEvent<'del,'args> = interface inherit IEvent<'args> /// Connect a handler delegate object to the event. A handler can /// be later removed using RemoveHandler. The listener will /// be invoked when the event is fired. abstract AddHandler: 'del -> unit /// Remove a listener delegate from an event listener store abstract RemoveHandler: 'del -> unit end Event declarations are not built-in to the F# language, and event is not a keyword. However, the use of the type Microsoft.FSharp.Control.IDelegateEvent<_> is a recognised idiom, and the compiled form of properties with this type include the extra .NET metadata and methods that mark the enclosing type as having a .NET event in the style of the standard .NET metadata for such an event. A sample use of this class is shown below. The sample takes an existing virtual method (Paint) and overrides it to publish callbacks to this method as firings of an event through a listener set. The arguments transacted by the event are typesafe through the use of the parameterized types System.EventHandler<_> (built into the .NET Framework), Idioms.IEvent<_> and Idioms.EventListeners<_>. The latter defines a backing store to hold the set of listeners associated with a particular event. open Idioms type MyCanvas = class inherit Form val redrawListeners: EventListeners<PaintEventArgs> member x.Redraw = x.redrawListeners.Event override x.OnPaint(args) = x.redrawListeners.Fire(args) new() = { inherit Form(); redrawListeners= new EventListeners<PaintEventArgs>() } end let form = new MyCanvas() do form.Redraw.Add(fun args -> Printf.printf "OnRedraw\n") do form.Activate() do Application.Run(form) .NET custom metadata attributes can be added at several positions in the above grammar. These have been shown separately below for clarity. These are added to the corresponding compiled forms of the subsequent construct. These compiled forms are only defined for publicly accessible constructs such as publicly available top-level methods. Attributes placed on internal constructs may or may not appear in the compiled binary. .NET attributes can only be applied to certain target language constructs according to the AttributeUsage attribute found on the attribute class itself. A warning will be given if an attempt is made to attach an attribute to an incorrect language construct. Attributes placed immediately prior to top-level do bindings in the main file of an assembly are attached to one of
Attributes are attached to the main entrypoint if it is legitimate for them to be attached to a method according to the AttributeUsage attribute found on the attribute class itself, and likewise for the assembly (the main method takes precedence if it is legitimate for the attribute to be attached to either). For example, the .NET attribute STAThread (used to specify the GUI event processing model for the main startup thread of an application) should be placed immediately prior to a top-level do binding. attribute := object-construction attributes := [< attribute ; ... ; attribute >] val-defn := | ... | attributes val-defn -- attributes on methods and static field values member-defn := | ... | attributes member-defn -- attributes on members module-member-defn := | attributes let {rec} module-member-defn -- alternative location for attributes field-defn := | ... | attributes field-defn -- attributes on field definitions constr-defn := | ... | attributes constr-defn -- attributes on constructor definitions type-defn := | ... | attributes type-defn -- attributes on type definitions exception-defn := | ... | attributes exception-defn -- attributes on exception definitions pat := | ... | (attributes pat) -- attributes on arguments (patterns in argument position) Attributes on arguments are only supported for arguments of member functions in class and interface definitions. Attributes may also be attached to corresponding items in F# signature files (.fsi and .mli files) are incorporated into any F#-specific interface metadata associated with the generated assembly and the .NET IL metadata for the generated assembly. Attributes attached to values in F# implementations (.fs and .ml files) are only saved into the .NET IL metadata, and are not necessarily included in metadata used for F# type-checking. Thus if signature files are used then attributes that are relevant to F# type checking must be placed in signatures (e.g., Obsolete attributes, which generate warnings at compile time when constructs are used). Attributes from signature files need not be duplicated in implementation files. Term quotation (also called expression quotation) is a limited form of meta-programming that permits type-checked expressions to be captured at runtime as structured terms, typically of type Microsoft.FSharp.Quotations.Typed.expr. These structured terms can then be interpreted, analyzed, compiled to alternative languages or simply discarded at runtime. Terms may also contain holes "_", which allow them to be used as functions that generate terms at runtime by "splicing in" other terms (a form of 'anti-quotation'), or as templates by matching the term against other terms. Note: As of July 2006 some simple introductory examples to term quotation can be found on the web at Tomas Petricek's home page. The following illustrate some simple instances of typed term quotation. Note these are typed quoted terms, of type Microsoft.FSharp.Quotations.Typed.expr. open Microsoft.FSharp.Quotations.Typed;; <@ 1 + 1 @>; val it : int expr <@ (fun x -> x + 1) @>; val it : (int -> int) expr Term quotation is triggered by the use of any of the lifted term quotation operators such as <@ @>, <@| |@>, « » and «| |» (the latter are 'French quotes', valid only in UTF-8 encoded Unicode files - be careful to save your file with the right encoding!!). Any operator <@{op-char}* {op-char}*@> is also a quotation operator. Each of these capture a typed abstract syntax tree form of the enclosed expression and invoke the given parenthetical operator on the result. Any quotation operators involving <@@{op-char}* {op-char}*@@> (e.g., <@@ @@>, <@@| |@@>) are raw quotation operators where the quoted term is passed to the implementation of the operator as type Microsoft.FSharp.Quotations.Raw.template<ty1,ty2>. The types ty1 and ty2 represent information about the quotation holes in the quoted term. Raw quotation operators are typically used within implemenations of quotation processing libraries. The following illustrate some simple instances of raw term quotation: Note these are untyped quoted terms, of type Microsoft.FSharp.Quotations.Raw.expr. open Microsoft.FSharp.Quotations.Raw;; <@@ 1 + 1 @@>; val it : expr <@@ (fun x -> x + 1) @@>; val it : expr All other quotation operators are strongly typed quotation operators, and propagate type information from the surrounding context to the type of the quoted term. In these cases the quoted term will be passed to the implementation of the operator with type Microsoft.FSharp.Quotations.Typed.template<ty1,ty2,ty3,ty4>. where the types ty1, ty2, ty3 and ty4 represent information about the quotation holes in the term and the overall type of the quoted term generated by the template once all holes are filled. Both strongly typed quotation templates and quoted terms are wrappers around raw (actually runtime-type-annotated) quoted terms found in Microsoft.FSharp.Quotations.Raw, and most operations traversing terms currently need to be written in terms of raw terms. The normal definitions of most commonly used quotation operators are in Microsoft.FSharp.Quotations.Typed and Microsoft.FSharp.Quotations.Raw. These operators can be redefined if desired, though this is not normally necessary. In normal usage the operators <@ @> and « » transform the template into a function that accepts one typed term tree argument for each hole and returns a value of type expr<ty4>. Similarly, the operators <@| |@> and «| |» transform the template into a function that matches against an input term, on success returning a tuple containing the terms that matched any holes in the term. In normal usage the operators <@@ @@> and <@@| |@@> are are bound to corresponding operations for raw quoted terms. Note: See the "FLinq" sample in the distribution for an example of the uses of quotation. A string used where type inference determines that a value of type Microsoft.FSharp.Text.Format4 (or one of its abbreviations such as Microsoft.FSharp.Text.Printf.buffer_format, Microsoft.FSharp.Text.Printf.channel_format is expected is interpreted as a printf-style format string. The format string is statically analyzed to determine the number and type of parameters expected. Such a format string is typically used with one of the functions printf, fprintf, sprintf or bprintf in the Microsoft.FSharp.Text.Printf module. The F# command line tools include fsc.exe, fsyacc.exe, fslex.exe and fsi.exe. They are described in a separate section of the manual. The F# distribution comes with two standard libraries fslib.dll and mllib.dll. They are described in a separate section of the manual. |