The F# Programming Language Informal Specification

F# is a scalable, script-like, type-safe, efficeintly 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 "(*" and "*)" as well as C#/C++-style "//" comments-to-end-of-line.

Conditional Compilation. Conditional compilation follows the same specification as C#. That is, #if <ident>/#endif markers are used to delimit conditional compilation regions. Text in an #if block is included in the compilation if the given symbol is defined in the compilation environment, typically via the command line --define. A separate conditional compilation 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 asr begin class constraint default delegate do done downcast downto else end
enum exception false finally for fun function if in inherit interface land lazy let lor lsl lsr lxor
match member mod module mutable new null of open or override rec sig static struct then to true try
type val when inline upcast while with | -> -< . : ( ) [ ] [< >] [| |] {< >} { } # `

The following keywords are currently unused by F# but are used in OCaml and/or C# and are reserved for future use by F#. Warnings are given if they are used.

async atomic break checked component const constraint 
constructor continue decimal eager event
external fixed functor include method mixin namespace object 
process property protected public pure readonly return sealed switch 
virtual void volatile

Aside: here are some of the identifiers that have not been reserved as keywords.

base continue explicit implicit operator protected this

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>*

Certain unicode characters may also be included in the operator set: the final choice of such characters is as yet unspecified, though may be specified in the change notices with each compiler release.

The following operators are also supported, and correspond to syntactic forms for expressions.

    .[]       (expression form "a.[b]")
    .()       (expression form "a.(b)")
    .()<-     (expression form "a.(b) <- c")
    .[]<-     (expression form "a.[b] <- c")

They default to string lookup, array lookup, and array assignment. The last is unassigned by default. They can, for example, be redefined to act on bytearrays rather than unicode strings:

    let (.[])   s n   = Bytearray.get s n
    let (.[]<-) s n m = Bytearray.set s n m
    let (.())   s n   = Compatibility.CompatArray.get s n
    let (.()<-) s n   = Compatibility.CompatArray.set s n

For compatibility with OCaml the following identifiers are parsed as operators, corresponding to logical bitwise manipulations:

    land lor lsl lsr lxor mod

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.0.0 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
    string-char = 
      | ...
      | unicodegraph-short 
      | unicodegraph-long 

Precedence.

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.

    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         %left
    ^OP                         %right 
    ::                          %right 
    :?> :?                      %nonassoc
    -OP +OP -.                  %left
    *OP /OP %OP                 %left
    **OP                        %right 
    ??                          %left  
    "expr - expr"               %nonassoc 
    "f x" "lazy x" "assert x"   %left
    "| rule"                    %right  -- pattern match rules
    !OP ?OP ~OP                 %prefix
    .                           %left

Where not specified the precedence is in the order of grammatical rules given in each section of this specification.

Note: the precedence specification largely follows the rules of the OCaml language. One significant exception is that the expression "!x.y" parses as "!(x.y)" rather than "(!x).y". 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.

Numeric Literals.

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

      int8       := <xint>y         -- e.g. 34y
      uint8      := <xint>uy        -- e.g. 34uy
      int16      := <xint>s         -- e.g. 34s
      uint16     := <xint>us        -- e.g. 34us
      int32      := <xint>l         -- e.g. 34l
      uint32     := <xint>ul        -- e.g. 34ul
      nativeint  := <xint>n         -- e.g. 34n
      unativeint := <xint>un        -- e.g. 34un
      int64      := <xint>L         -- e.g. 34L
      uint64     := <xint>UL        -- e.g. 34UL
      ieee32     := <float>{F|f}   -- e.g. 3.0F or 3.0f
      ieee64     := <float>        -- e.g. 3.0

      bigint     := <int>I         -- e.g. 34742626263193832612536171I
      bignum     := <int>N         -- e.g. 34742626263193832612536171N

      // Note: bigint and bignum constants specified using hexidecimals
      // 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 := <string>B
      bytechar := <bytechar>B

      float := 
        -? digit+ . digit*  
        -? digit+ (. digit* )? (e|E) (+|-)? digit+ 

Negative integers are currently specified using the approriate integer negation operator, e.g. "-3". This is under revision.

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 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 <expr>s separated by commas.

Basic Elements.

    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> 

Constants.

See the lexical section above for descriptions of the valid constant formats.

    const := 
      | <int>                          -- 32-bit signed integer
      | <int8> | <int16> | <int32> | <int64>    -- 8, 16, 32 and 64-bit signed integers
      | <uint8> | <uint16> | <int32> | <uint64> -- 8, 16, 32 and 64-bit unsigned integers
      | <ieee32>                       -- 32-bit 'Single' floating point number of type 'float32'
      | <ieee64>                       -- 64-bit 'Single' floating point number of type 'float32'
      | <bigint>                       -- Arbitrary sized integer number of type 'bigint' (aka 'big_int')
      | <bignum>                       -- Arbitrary 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'

Expressions.

The expression forms and related elements are as follows:

    expr :=  
      |  <expr> ; <expr>               -- sequence expressions
      |  begin <expr> end              -- block expressions
      |  ( <expr> )                    -- block expressions
      |  ( <expr> : <type> )           -- type annotations
      |  let [inline] <val-defns> in <expr> -- locally bind values
      |  let rec <rec-val-defns> in <expr>  -- locally bind mutually referential values
      |  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> -- conditionals
      |  if <expr> then <expr>         -- conditional statements
      |  while <expr> do <expr> done   -- while loops
      |  for <ident> = <expr> to <expr> do <expr> done   -- for loops
      |  lazy <expr>                   -- delayed computations
      |  assert <expr>                 -- checked computations
      |  <expr> := <expr>              -- assignments to reference cells
      |  <expr> <- <expr>              -- property and field assignments
      |  <expr>.(<expr>)               -- operator '.()', defaults to array lookup
      |  <expr>.(<expr>) <- <expr>     -- operator '.()<-', defaults to array assignment
      |  <expr>.[<expr>]               -- operator '.[]', defaults to string lookup
      |  <expr> , ... , <expr>         -- tuple expressions
      |  { <field-exprs> }             -- record expressions 
      |  { <expr> with <field-exprs> } -- copy-and-update record expressions
      |  <expr> <infix> <expr>         -- infix expressions
      |  <prefix> <expr>               -- prefix expressions
      |  <expr> <expr>                 -- application/invocation 
      |  <expr> '.' <expr>             -- member access
      |  <ident>                       -- a value
      |  ()                            -- the 'unit' value
      |  [ <expr> ; ... ; <expr> ]     -- list expressions
      |  [| <expr> ; ... ; <expr> |]   -- array expressions
      |  false | true                  -- boolean constants
      |  <const>                       -- a constant value
      |  new <object-construction>     -- object expression
      |  { new <object-construction> with <val-defns> <interface-defns>}
                                       -- object expression with overrides and interfaces
      |  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

    val-defn := 
      | <pat> ... <pat> {<type>}= <expr>   -- bind a value according to the patterns 

    rec-val-defn :=
      | <val-defn>                -- bind a value according to the 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-defns>          -- specify an implemented interface

    exprs := <expr> ',' ... ',' <expr> 
    val-defns := <val-defn> and ... and <val-defn> 
    rec-val-defns := <rec-val-defn> and ... and <rec-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 have the corresponding type and evaluate to the corresponding simple constant value.

  • 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.

  • (e1) is a parentheses expression and evaluates e1 and has the same type as e1

  • begin e1 end is a block expression and evaluates e1 and has the same type as e1

  • let binds in e1 is a binding expression and establishes bindings within the local lexical scope of e1 and has the same type as e1. Bindings are generalized to be generic (polymorphic) if they are values (i.e. lambda expressions, references to other F# values and/or constructed data). Certain other limitations on generalization apply: e.g. see the limitations on pseudo variables arising from operator overloading constraints. Fewer restrictions apply if a value is marked inline, though this is only because copies of code may be made as necessary in order to implement the given semantics. Mutually referential bindings are established using let rec. Bindings on the right of a let rec are typically functions, though see the advanced features for a description of additional constructs that are accepted with warnings.

  • fun x1 -> e1 is a lambda expression and is of function type and evaluates to function values. Lambda expressions are frequently used as building blocks to build more sophisticated objects. Lambda expressions may involve tupled and iterated arguments, e.g. fun x1 (x2,x3) -> e1 and pattern arguments (fun (MyData(x1,x2)) -> x1+x2+x3).

  • 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 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 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.

  • A conditional expression, while loop expression or for loop expression executes according to the traditional semantics. Both branches of conditional expressions must have equivalent (and not simply compatible) types. While loops and for loops type to unit and a warning will be reported if the body of a while or for expression is not of type unit.

  • 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.

  • [e1;...;en] is a list expression and is of list type ty list (also Microsoft.FSharp.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.

  • [| 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.

  • { <field-exprs> } is a record construction expression. The expressions are evaluated in an unspecified order 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.

  • { <expr> with <field-exprs> } is a copy-and-update record expression. The expressions are evaluated in an unspecified order 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.

  • f e1 .. en is an application expression.

    • If f is a value then it must be of function type and the domain of that type must be identical to the type of e1. Any known domain and range type information from the type of f is used in the type checking of e1. The same type checking process is applied iteratively to e2 to en. At runtime the constituent expressions are evaluated in an unspecified order. The body of the function value resulting from the f is then executed with the first formal parameter assigned the value of the first actual argument, and additional arguments are applied iteratively to further resulting function values.

    • If f is a method group or indexer property then the expression is a member application. Overload resolution is performed according to the partially determined static types of the argument expressions. See the interoperability section for a discussion on how overloading for members is resolved. Given the results of static overload resolution, at runtime a member application proceeds in a similar fashion to a function application, except that a virtual member of interface member is dispatched to the implementation of the dispatch slot according to the dispatch slot and interface implementation mappings of the value on which the member is being invoked. Implementation mappings are described in the mappings section.

  • 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.

  • 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 e1 is a lazy expression, where e1 is evaluated on demand in response to a Lazy.force operation on the lazy value.

  • 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.

  • 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 the various libraries provided with the language. Most operators will typically be overloaded.

  • { 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.

  • 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.

  • null is a null expression. See the interoperability section for a discussion on how nullness is treated.

  • (e1 : 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.

  • 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.

  • upcast(e1) is a static coercion expression. The target type is inferred from the local context. See the upcasts and downcasts section for more information.

  • e1 :? ty is a dynamic type test expression. See the upcasts and downcasts section for more information.

  • 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 this expression form is not recommended and may be deprecated.

  • An assert expression evaluates the given expression, which must be of type bool and raises an Microsoft.FSharp.AssertFailure exception if the expression is false.

Patterns.

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 := 
      | <const>                           -- constant pattern
      | <longident>                       -- variable binding, nullary constructor or named literal
      | <pat> as <ident>                  -- name the matched expression
      | <pat> | <pat>                     -- 'or' patterns
      | <pat> :: <pat>                    -- 'cons' patterns
      | [<pat> ; ... ; <pat>]             -- list patterns
      | (<pat>,...,<pat>)                 -- tuple patterns
      | {<field-pat> ; ... ; <field-pat>} -- record patterns
      | :? <type>                         -- dynamic type test patterns
      | :? <type> as  <ident>             -- dynamic type test patterns, with named result
      | <longident> <pat>                 -- Unary constructor
      | <longident> (<pats>)              -- N-ary constructor
      | _                                 -- wildcard pattern
      | null                              -- null-test pattern

    field-pat := <longident> = <pat>

    pats :=  <pat> , ... , <pat> 
    field-pats := <field-pat> ; ... ; <field-pat> 
    rules := {'|'} <rule> '|' ... '|' <rule>  -- multiple rules
  • Named literals may be used as constants within patterns. No construct currently exists to define literals in F#, however they may be defined in and accessed from other .NET languages.

  • :? <type> as <ident> is a dynamic type test pattern. This pattern matches any value whose runtime type is the given type or a subtype of the given type. If present the identifier after as is bound to the value coereced to the given type.

  • <p1> | <p2> is an or pattern. It matches a value if either the left or right of the pattern matches the value. Each side of the pattern must bind identicial variables.

  • {<field-pat> ; ... ; <field-pat>} is an record pattern. The pattern must give patterns for a subset of the fields of a F# record type, or a subset of the immediate (not inherited) fields of an F# object type.

Types.

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> <id>. ... .<id>        -- constructed type, e.g 'int list'
      |  ( <types> ) <id>. ... .<id>   -- constructed type, e.g '(int,string) map'
      |  <id>. ... .<id>'<';<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-defns>. <type>         -- first-class generic type, for value and record field types

    typar :=
      |  _                             -- unnamed variable type
      |  '<id>                         -- named variable type
      |  $<id>                         -- named pseudo-variable type

The semantics associated with these forms is as follows:

  • <ty1> -> <ty2> is a function type, where ty1 is the range of the function values assocaited with the type, and ty2 is the domain. Function values inhabiting this type may have side effects and may raise exceptions.

  • <ty1> * ... * <tyN> is a tuple type.

  • ( <ty> ) is identical to the type ty.

  • <typar> is a variable type. The inferred declaration site is at the point where the variable is generalized, if any, e.g. at a let binding. If the variable is never generalized then it represents a solved inference variable across the scope of type inference (i.e. across the file). If it is equated with another type by type inference then the variable acts as an abbreviation for that type.

  • <id>. ... .'<'id><<type>'>' is a constructed type with one or more type arguments. The long path must resolve to a type constructor accepting the correct number of generic type arguments.

  • <id>. ... .<id> is a named type, a simplified constructed type with no type arguments.

  • <type> <id>. ... .<id> is a constructed type with one type argument.

  • ( <types> ) <id>. ... .<id> is a constructed type with multiple type arguments.

  • <ty>[] is a .NET-compatible array type. See the advanced section for more details.

  • <ty>[,] is a .NET-compatible two dimensional non-jagged array type. See the advanced section for more details.

  • <ty> lazy is an abbreviation for Microsoft.FSharp.Lazy<ty>.

  • '<typar-defns>. <type> is a first-class polymorphic type. These types can be used only at value and record field declarations.

The following terms are used elsewhere in this language specification:

  • A type is a class type if it is a constructed type whose type constructor is, in the current scope, visible to be of kind class. Likewise for interface, delegate, struct, record, union and abstract types.

  • A type is extensible if it is a class or interface type and, in the case of class types, it's type constructor is not marked sealed. Currently only types from from .NET metadata are so marked.

  • A type is sealed if it is not extensible.

Type Definitions.

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 := 
      |  <typar-defns> <id>                      -- existing type (see type augmentations)
      |  <typar-defns> <id> <simple-type-defn>   -- simple type definition
      |  <typar-defns> <id> <class-defn>         -- class type definition

    simple-type-defn :=
      |  <type>      -- type abbreviation declaration
      |  {|} <constr-defn> | ... | <constr-defn> -- discriminated type declaration
      |  '{' <recd-defn> '}'                     -- record type declaration
      | delegate of <type>                -- delegate type 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>   

    type-defns := <type-defn> and ... and <type-defn> 

All type definitions except type abbreviations define fresh, named types.

Exception Definitions.

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.

Modules and Implementation Files (.ml or .fs).

Modules are named collections of definitions. Items in modules are accessed via long identifiers. An implementation file contains 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.

    module-member-defn := 
      | let {rec} <val-defns>            -- top level value definitions
      | type <type-defns>                -- type definitions
      | exception <exception-defns>      -- exception definitions
      | module <longident> = <longident> -- alias a module
      | open <longident>                 -- provide implicit access to the given module path
      | do <expr>                        -- execute the given expression

    module-member-defns := <module-member-defn> ... <module-member-defn>

    implementation-file :=
      | module <longident> <module-member-defns> -- named module
      | <module-member-defns>                -- anonymous module (name implicit from filename)

Module Signatures and Interface 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:

  • Type abbreviations may not be hidden by signatures. A future version of F# will permit this, though f the abbreviation will still have to be noted in the signature using an as-yet-unspecified syntax. This is for the benefit of users of other .NET languages, which do not have type abbreviations. A full abstraction warning will also be generated.

  • Any type whose representation is revealed to be an record or discriminated union by a signature must reveal all of its fields/constructors. Constructors must be declared in the same order in the signature and implementation, fields may be in any order. Types whose representations are classes may reveal some, all or none of their fields in a signature.

  • Any type which is revealed to be an interface, or a type which is a class or struct with one or more new for inherit constructors (see class definitions), may not hide its inheritance declarations, abstract dispatch slot declarations or abstract interface declarations.

    val-spec :=
      | val <ident>: <type>    -- value specifciations

    type-spec := 
      |  <typar-defns> <id>                -- abstract type specification
      |  <typar-defns> <id> = <simple-type-defn> -- simple type specification
      |  <typar-defns> <id> = <class-spec>       -- class type specification
      |  <type-spec> with <class-spec> end -- augmented 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-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> ; ... ; <type-spec> 
    exception-specs := <exception-spec> ; ... ; <exception-spec> 
    member-specs :=  <member-spec> ... <member-spec>

    module-spec := 
      | val <val-spec>                   -- value specifciations
      | type <type-specs>                -- type specifciations
      | exception <exception-specs>      -- exception specifciations
      | module <id> : sig <module-specs> end      -- submodule specifciation

    module-specs := <module-spec> ... <module-spec>

    interface-file :=
      | module <longident> <module-specs> -- named module
      | <module-specs>                -- anonymous module (name implicit from filename)

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.

Constrained Types and Overloaded Operators.

Variable types may be constrained to indicate functionality that must be supported by the type. 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>     -- constrained type, for value and record field types
      |  <typar> :> <constraints>      -- constrained variable type

The currently permitted syntactic forms for constraints on variable types are as follows:

    constraint :=  
      |  <typar> = <type>                        -- equational constraint
      |  <type> :> <type>                        -- coercion constraint
      |  $<id> '.' <id> : (  <types> )->  <type> -- static method pseudo trait constraint

It is likely that the forms of constraints supported will be increased in future releases, and restrictions associated with some constraints may be lifted.

Coercion constraints are of the form typar :> type, and also arise from the constructs expr :> type and pattern :> type. For example:

  • The F# library uses coercion constraints to allow an F# function to accept arguments that are subtypes of a particular type. For example the following declaration says that throw can be any value that are subtypes of the .NET type System.Exception.

       val throw: 'e -> unit when 'e :> System.Exception
    

    The same declaration can be written using the following more convenient syntactic forms:

       val throw: (_ :> System.Exception) -> unit
    
  • Coercion constraints also arise when calling a C# function that accepts an argument of a base type such as IEnumerable. For example, if a C# function has signature:

          
        class C { static void SomeMethod(IComparable x) }
    

    Then calling this with the F# code:

        C.SomeMethod(x)
    

    will induce a constraint that x is coercable to IComparable, i.e. ty :> IComparable when ty is the static type of x.

  • C# 2.0 and other .NET 2.0 code may use coercion constraints to specifying that a type parameter should support functionality such as IComparable. However, this pattern is not so common in F# code, where dictionaries of functionality are typically passed around by using tuples or records of function values.

Overloaded operator constraints arise when using overloaded operators +, - etc. For example, the operator + may be used on any two .NET values supporting the overloaded operator op_Addition (written static operator +(...) in C#). (They may also be used on built-in integer and floating point types, which are considered by F# to implicitly define operators such as op_Addition). Overloaded operators are generally only defined within the F# library. Overloaded operator constraints can only be placed on pseudo type variables.

Overloading is supported for the following operators 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.

    val (+)    : $a -> $b -> $a  when $a.op_Addition      : ($a, $b) -> $a
    val (-)    : $a -> $b -> $a  when $a.op_Subtraction   : ($a, $b) -> $a
    val ( * )  : $a -> $b -> $a  when $a.op_Multiply      : ($a, $b) -> $a
    val (/)    : $a -> $b -> $a  when $a.op_Division      : ($a, $b) -> $a
    val (mod)  : $a -> $b -> $a  when $a.op_Modulus       : ($a, $b) -> $a
    val (~-)   : $a -> $a        when $a.op_UnaryNegation : ($a) -> $a
    val (~+)   : $a -> $a        when $a.op_UnaryPlus     : ($a) -> $a
    val (land) : $a -> $a -> $a  when $a.op_BitwiseAnd    : ($a,$a) -> $a
    val (lor)  : $a -> $a -> $a  when $a.op_BitwiseOr     : ($a,$a) -> $a
    val (lxor) : $a -> $a -> $a  when $a.op_ExclusiveOr   : ($a,$a) -> $a
    val lnot   : $a -> $a        when $a.op_LogicalNot    : ($a) -> $a
    val (lsl)  : $a -> int -> $a when $a.op_LeftShift     : ($a,int) -> $a
    val (lsr)  : $a -> int -> $a when $a.op_RightShift    : ($a,int) -> $a
    val (asr)  : $a -> int -> $a when $a.op_RightShift    : ($a,int) -> $a

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

As with types, constraints will be inferred from the definition of a method. For example

    open System.IO
    let to_binary_writer s = new BinaryWriter(s)

will infer the type

    val to_binary_writer: (_ :> Stream) -> BinaryWriter

That is, because the constructor for System.IO.BinaryWriter accepts any subtype of System.IO.Stream, F# has also inferred that the derived function should accept any subtype of System.IO.Stream as its argument. You could also write this explicitly using:

    let to_binary_writer (s :> Stream) = new BinaryWriter(s)

Here the pattern (s :> Stream) means 's should match a value whose type can be coerced to Stream'.

Constraint Solving and Checking for Subtype Constraints

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. Constraints are solved, or partially solved as follows:

  • All constraints of the form 'a :> obj hold immediately.

  • The constraint 'a :> string are solved immediately to deduce 'a = string, since string is a sealed type.

  • Constraints involving types with identical type constructors such as Set<'a> :> Set<'b> are solved immediately, e.g. to deduce 'a = 'b. F# generic types do not support co-variance or contra-variance.

  • Constraints involving types with related type constructors are solved immediately, possible producing additional equational constaints on type parameters. For example, the constraint MySubClass<'a> :> MyBaseClass<'b> may produce a new constraint to be solved, e.g. if MySubClass<T> is derived from MyBaseClass<T> then the solution 'a = 'b will be derived, again because types do not support co-variance.

  • Constraints of the form ty :> 'b will be solved immediately to deduce ty = 'b in the absence of any existing solution for 'b. These constraints typically only arise when calling generic code from other .NET languages where a method accepts a parameter of a 'naked' variable type, e.g. a C# 2.0 function with a signature such as T Choose<T>(T x, T y).

  • Subtype constraints on .NET-comaptible single dimensional array types ty[] :> ty are solved to residual constraints to account for the fact that these types subtype System.Array, System.Collections.Generic.IList<T>, System.Collections.Generic.IEnumerable and System.Collections.Generic.IEnumerable. .NET-comaptible multi-dimensional array types ty[] :> ty implicitly subtype System.Array.

  • Types from F# and other .NET languages may, in theory, support multiple instantiations of the same interface type, e.g. C : I<int>, I<string>. This makes it more difficult to solve a constraint such as C :> I<'a>. This is rarely, if ever, used in practice. The behaviour of F# in the presence of such constraints is under-specified; the current implementation solves such constraints eagerly by choosing the first interface type that occurs in the tree of supported interface types, from most derived to least derived, iterating left-to-right in the order of the declarations in the .NET metedata.

Class Definitions.

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-defn :=
      | class <member-defns> end
      | struct <member-defns> end
      | interface <member-defns> end
      | delegate <member-defns> end
      | enum <member-defns> end

    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 (must define get and/or set)
      |  <ident> '.' <ident> with <val-defns>   -- instance property definition (must define get and/or set)

    member-defns :=  <member-defn> ... <member-defn>

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 effectively a subset of expression forms (with the additional inclusion of the form <constr-expr> then do <stmt>):

    constr-expr :=
      | <stmt> ';' <constr-expr>      -- sequence expression (action before)
      | <constr-expr> then do <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> '}' 

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 raises problems such as accessing 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. 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 effectively a subset of expression forms (with the additional inclusion of the form <constr-expr> then do <stmt>):

An interface member indicates that objects of the given type support the given interface. Interface implementations may be given in augmentations, with some caveats.

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.

An static method or property member is associated with an instance of 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
        member x.InstanceProperty = x.instanceField^".InstanceProperty"
        member x.MutableInstanceProperty
          with get()         = x.mutableInstanceField
          with set(v:string) = x.mutableInstanceField <- v
      end

Property members of all kinds may be indexer properties. Sample indexer properties are as follows:

    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.mutableInstanceArray.(idx1)
       with set (idx1) (v:string) = x.mutableInstanceArray.(idx1) <- v
    static member StaticIndexer
       with get(idx) = staticArray.(idx)

Proposed Feature (not fully implemented, as of v1.1.0.0): A new for inherit constructor is one that cannot be used to directly construct objects - it may only be used by subclasses to partially initialize an object. A new for val cosntructor is one that can only be used to create objects - it may not be used by subclasses to partially initialize objects. A regular constructor is both new for inherit and new for val. A type is 'abstract' (in the .NET sense) if no new for val constructors exist in the implementation. Any type with new for val constructors must have all abstract members and interfaces implemented. Both the new for inherit and new for val aspects of a constructor may be hidden by a signature, i.e. a regular constructor can be made new for inherit. (Aside: this is an F#-only feature - other .NET languages may be able to use the compiled forms of new for val and new for inherit constructors in unexpected ways. See full abstraction warnings.) Classes with a new for val constructor must exhibit a complete dispatch and interface implementation map. Implementation mappings are described in the mappings section. Note that values that implement mappings may be callable via the dispatch slots and interfaces even if they are not directly callable via other means.

Type Augmentations.

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-defn>
  • Type augmentations may only be given in the same file as the type definition. Type constructors may be declared multiple times within that file, but all except the first must only give an augmentation. The first definition may also give a single augmentation.

  • Type augmentations may define instance members and static members. As an experimental feature type augmentations may also define interface implementations and virtual member override implementations. Augmentations that define interface implementations and override defaults may result in undefined behaviour if the intervening code creates instances of the object at runtime and makes calls via the virtual dispatch slots implemented by these functions (ill-defined recursion cycles can in principle occur). In a future release an analysis similar to that for reactive recursion will be used to ensure initalization soundness is checked systematically for mutually recursive top-level declarations.

Structural Comparison and Hashing.

F# values can be structurally compared and hashed using "polymorphic" operations such as Pervasives.compare. This is because F#-defined types implicitly implement the interfaces System.IComparable and Microsoft.FSharp.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
    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.MLLib.Pervasives.compare : 'a -> 'a -> int
    Microsoft.FSharp.Primitves.Operators.op_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 any of the following:

    Microsoft.FSharp.Primitives.Operators.op_StructuralHash : 'a -> int
    Microsoft.FSharp.MLLib.Pervasives.hash : 'a -> int
    Microsoft.FSharp.MLLib.Hashtbl.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.Primitives.Operators.op_StructuralHashParam : 'a -> 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, union and class type definitions implicitly derive support for both System.IComparable and Microsoft.FSharp.IStructuralHash. Types defined to be interfaces or delegates do not. 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 behaviour of these interfaces may be user-specified 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. Current Limitation: in the current release the derived structural comparison and hashing implementations for classes work only on the values defined immediately in the class, regardless of the contents of values inherited from super-classes.

Exception values built via the exception type constructors derive support for these interfaces in the same way as the process described above.

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 StaticMethodsWithRefParams
        {
            static public void IntegerOutParam(out int x) { x = 3; }
        }
        public class VirtualMethodsWithRefParams
        {
            virtual public void IntegerOutParam(out int x) { x = 3; }
        }

    F# client code:
       let res1 = ref 0 in Methods.StaticMethodsWithRefParams.IntegerOutParam(res)
       // res1.contents now equals 3

       let x = {new Methods.VirtualMethodsWithRefParams() with IntegerOutParam(res : int byref) = res <- 4} in
       let res2 = ref 0 in 
       x.IntegerOutParam(res2);
       // res2.contents now equals 4

ByRef arguments may 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 implementing functions of an object expression.

F# generic values and types may not be instantiated with byref types. In any case, there is no way in F# to generate values of type byrefexcept at in very restricted ways.

Current Limitation: In the future a construct will be added to support local mutable variables that are implicitly dereferenced, which can be used within inner bindings (i.e. are heap-allocated if necessary) and which can be passed as byref parameters using an "address of" operator. Values of type "ref" will still be able to be passed to "byref" arguments. In this release, let-bound variables within the scope of a lambda expression may be marked as mutable. These variables are under the same restrictions as byref arguments, and are similarly implicitly dereferenced. There is no officially supported language construct to take the address of a mutable local variable to use it as a byref argument, though releases may include an & operator for this purpose. Use of this operator may or may not result in verifiable .NET IL code.

Events.

Events are the .NET notion of a "wire" or "listening point", that is, a configurable mutable location holding a set of callbacks. Callbacks are .NET delegate values, which are explicitly named function types. In F#, events are defined as properties that return objects that mediate the addition and removal of listeners from a backing listener set. Event declarations are not built-in to the F# language, except in the sense that properties that are a subtype of the F# library type Microsoft.FSharp.Idioms.IDelegateEvent<_> or Microsoft.FSharp.Idioms.IEvent<_> result in extra .NET metadata and methods that implement an event of that name. Events declared using Idioms.IEvent are the easiest to use from F#, as Add actions on events simply take function values. The type IEvent and some related types are defined as follows:

    type SimpleEventArgs<'a> = 
      class 
        inherit System.EventArgs 
        member Data: 'a 
        new: 'a -> SimpleEventArgs<'a>
      end

    type SimpleEventHandler<'a> =  System.EventHandler >

    type IEvent<'a> = 
       interface 
          abstract AddHandler: SimpleEventHandler<'a> -> unit
          abstract RemoveHandler: SimpleEventHandler<'a> -> unit 

          // We add this one, which from F# code this is very simple to use:
          abstract Add: ('a -> unit) -> unit
       end

    type event<'a> = IEvent<'a>

    type EventListeners<'a> 
      with
        member Fire: 'a -> unit
        member Event: IEvent<'a>
        new: unit -> EventListeners<'a>
      end

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.

    type MyCanvas = 
      class 
        inherit Form
        val redrawListeners: EventListeners
        member x.Redraw = x.redrawListeners.Event
        override x.OnPaint(args) = x.redrawListeners.Fire(args)

        new() = { inherit Form(); redrawListeners= new EventListeners() }
      end

    let form = new MyCanvas()
    do form.Redraw.Add(fun args -> Printf.printf "OnRedraw\n")
    do form.Activate()
    do Application.Run(form)

Custom Attributes.

.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

  • The main entry point of the program

  • The compiled assembly

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.

    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 declarations

    type-defn :=
      | ...
      | <attributes> type-defn         -- attributes on type definitions

    attribute := <object-construction>
    attributes := [< <attribute> ; ...  ; <attribute> >]

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.

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.