17 people like it.

Transform expressions into Excel formulae

Sometimes it is extremely useful to check some calculations with Excel. The snippet shows how F# expressions can be transformed into Excel formulae. The data is exported together with the formulae, e.g. a, b and sum function as input sets A1's value to a, B1's to b and C1's formula to "=$A$1+$B$1"

Transform expressions into Excel formulae

  1: 
  2: 
  3: 
  4: 
  5: 
  6: 
  7: 
  8: 
  9: 
 10: 
 11: 
 12: 
 13: 
 14: 
 15: 
 16: 
 17: 
 18: 
 19: 
 20: 
 21: 
 22: 
 23: 
 24: 
 25: 
 26: 
 27: 
 28: 
 29: 
 30: 
 31: 
 32: 
 33: 
 34: 
 35: 
 36: 
 37: 
 38: 
 39: 
 40: 
 41: 
 42: 
 43: 
 44: 
 45: 
 46: 
 47: 
 48: 
 49: 
 50: 
 51: 
 52: 
 53: 
 54: 
 55: 
 56: 
 57: 
 58: 
 59: 
 60: 
 61: 
 62: 
 63: 
 64: 
 65: 
 66: 
 67: 
 68: 
 69: 
 70: 
 71: 
 72: 
 73: 
 74: 
 75: 
 76: 
 77: 
 78: 
 79: 
 80: 
 81: 
 82: 
 83: 
 84: 
 85: 
 86: 
 87: 
 88: 
 89: 
 90: 
 91: 
 92: 
 93: 
 94: 
 95: 
 96: 
 97: 
 98: 
 99: 
100: 
/// Simplified SpecificCall
let inline (|Func|_|) expr =(...)

/// Generate a formula pattern for an expression
/// Column number - index of var + 1 in the env
/// '#' is a temp placeholder for a row number
let generatePattern expr env =     
    // print binary ops: (x op y)
    let rec inline printBinaryOp op x y parens = 
        let res = transform x + op + transform y in if parens then "(" + res +  ")" else res

    // print functions: name(arg1, arg2, ...)
    and inline printFunc name args =
        let argValues: string[] = List.map transform args |> List.toArray
        sprintf "%s(%s)" name (String.Join (", ", argValues))

    // transform an expression into pattern
    and transform expr = 
        match expr with
        | Func <@@ (+) @@> [x; y] -> printBinaryOp "+" x y true
        | Func <@@ (-) @@> [x; y] -> printBinaryOp "-" x y true
        | Func <@@ (*) @@> [x; y] -> printBinaryOp "*" x y true
        | Func <@@ (/) @@> [x; y] -> printBinaryOp "/" x y true
        | Func <@@ ( ** ) @@> [x; y] -> printBinaryOp "^" x y false
        | Func <@@ (~-) @@> [x] -> "-" + transform x
        | Func <@@ (~+) @@> [x] -> transform x
        | Func <@@ mduration @@> args -> printFunc "MDURATION" args
        | Func <@@ accrint @@> args -> printFunc "ACCRINT" args
        | Lambdas (_, e) -> transform e
        | Value (v, _) -> string v
        // try to replace a varname with its column index
        | Var var -> 
            match List.tryFindIndex ((=)var.Name) env with
            | Some ind -> "R#C" + string (ind + 1)
            | _ -> var.Name
        // args.[i] means reference to the (i+1)th column
        | Call(None, mi, _::[Value (i, _)]) when mi.DeclaringType.Name = "IntrinsicFunctions" 
                                              && mi.Name = "GetArray" -> 
            let ind = unbox i in "R#C" + string (ind + 1)
        // replace MakeDecimal with a value
        | Call(None, mi, Value (v, _)::_) when mi.DeclaringType.Name = "IntrinsicFunctions" 
                                            && mi.Name = "MakeDecimal" -> 
            string v
        // DateTime ctor -> Excel DATE function: DATE(year, month, day)
        | NewObject(ci, Value(y,_)::Value(m,_)::Value(d,_)::_) when ci.DeclaringType.Name="DateTime"-> 
            sprintf "DATE(%A, %A, %A)" y m d
        | _ -> failwith (sprintf "Unknown expression type: %A" expr)

    "=" + transform expr

(Patterns example)

module Test =
    [<ReflectedDefinition>]
    let sum (a: decimal) b = a + b
  
    [<ReflectedDefinition>]
    let mdurationMonth m c y f basis = (mduration (DateTime(2012, 1, 7)) m c y f basis) * 12M

    let run export = 
        let data: obj list list =(Some data)

        // the vars with such names will be replaced with R{rownum}C{var index + 1}
        let dataColumns = ["a"; "b"; "s"; "m"; "c"; "y"; "f"; "basis"]
        let funcs = ["sum"; "mdurationMonth"]

        // try to find the reflected definitions (usual expressions can be used instead)
        let reflectedDefinitions = 
            let methods = 
                Assembly.GetExecutingAssembly().GetTypes() 
                |> Array.collect (fun t -> t.GetMethods())

            Array.foldBack (fun mi state -> 
                match Expr.TryGetReflectedDefinition mi with
                | Some expr -> (mi.Name, expr) :: state
                | None -> state) methods []
            |> Map.ofList

        // transform quotation into a pattern & split by the rownum replacement '#'
        let unquote = 
            Option.bind (fun expr -> 
                try 
                    Some ((generatePattern expr dataColumns).Split [|'#'|])
                with _ -> None)

        // reflected definitions -> formulae
        let formulae = funcs
                        |> List.map (reflectedDefinitions.TryFind >> unquote)
                        |> List.filter Option.isSome
                        |> List.map Option.get
        
        data |> List.iteri (export formulae)

/// Export data with given pattern
let export exportValue exportFunc (patterns: string[] list) row (items: _ list) =(...)

// Standard output
Test.run (export 
            (fun row i item -> printfn "Cells.[%d, %d]<-%A" row (i+1) item)
            (fun cell formula -> printfn "Range(%A, %A).Formula <- \"%s\"" cell cell formula))

Simple export to Excel

 1: 
 2: 
 3: 
 4: 
 5: 
 6: 
 7: 
 8: 
 9: 
10: 
11: 
12: 
let app = new ApplicationClass()
let workbook = app.Workbooks.Add(XlWBATemplate.xlWBATWorksheet)
let worksheet = workbook.Worksheets.[1] :?> Worksheet

// fill the cells
Test.run (export 
            (fun row i item -> worksheet.Cells.[row, i+1] <- item)
            (fun cell formula -> worksheet.Range(cell, cell).Formula <- formula))

app.ReferenceStyle <- XlReferenceStyle.xlA1

(Close workbook and release objects)
Multiple items
type Func<'TResult> =
  delegate of unit -> 'TResult

Full name: System.Func<_>

--------------------
type Func<'T,'TResult> =
  delegate of 'T -> 'TResult

Full name: System.Func<_,_>

--------------------
type Func<'T1,'T2,'TResult> =
  delegate of 'T1 * 'T2 -> 'TResult

Full name: System.Func<_,_,_>

--------------------
type Func<'T1,'T2,'T3,'TResult> =
  delegate of 'T1 * 'T2 * 'T3 -> 'TResult

Full name: System.Func<_,_,_,_>

--------------------
type Func<'T1,'T2,'T3,'T4,'TResult> =
  delegate of 'T1 * 'T2 * 'T3 * 'T4 -> 'TResult

Full name: System.Func<_,_,_,_,_>

--------------------
type Func<'T1,'T2,'T3,'T4,'T5,'TResult> =
  delegate of 'T1 * 'T2 * 'T3 * 'T4 * 'T5 -> 'TResult

Full name: System.Func<_,_,_,_,_,_>

--------------------
type Func<'T1,'T2,'T3,'T4,'T5,'T6,'TResult> =
  delegate of 'T1 * 'T2 * 'T3 * 'T4 * 'T5 * 'T6 -> 'TResult

Full name: System.Func<_,_,_,_,_,_,_>

--------------------
type Func<'T1,'T2,'T3,'T4,'T5,'T6,'T7,'TResult> =
  delegate of 'T1 * 'T2 * 'T3 * 'T4 * 'T5 * 'T6 * 'T7 -> 'TResult

Full name: System.Func<_,_,_,_,_,_,_,_>

--------------------
type Func<'T1,'T2,'T3,'T4,'T5,'T6,'T7,'T8,'TResult> =
  delegate of 'T1 * 'T2 * 'T3 * 'T4 * 'T5 * 'T6 * 'T7 * 'T8 -> 'TResult

Full name: System.Func<_,_,_,_,_,_,_,_,_>

--------------------
type Func<'T1,'T2,'T3,'T4,'T5,'T6,'T7,'T8,'T9,'TResult> =
  delegate of 'T1 * 'T2 * 'T3 * 'T4 * 'T5 * 'T6 * 'T7 * 'T8 * 'T9 -> 'TResult

Full name: System.Func<_,_,_,_,_,_,_,_,_,_>

--------------------
type Func<'T1,'T2,'T3,'T4,'T5,'T6,'T7,'T8,'T9,'T10,'TResult> =
  delegate of 'T1 * 'T2 * 'T3 * 'T4 * 'T5 * 'T6 * 'T7 * 'T8 * 'T9 * 'T10 -> 'TResult

Full name: System.Func<_,_,_,_,_,_,_,_,_,_,_>

--------------------
type Func<'T1,'T2,'T3,'T4,'T5,'T6,'T7,'T8,'T9,'T10,'T11,'TResult> =
  delegate of 'T1 * 'T2 * 'T3 * 'T4 * 'T5 * 'T6 * 'T7 * 'T8 * 'T9 * 'T10 * 'T11 -> 'TResult

Full name: System.Func<_,_,_,_,_,_,_,_,_,_,_,_>

--------------------
type Func<'T1,'T2,'T3,'T4,'T5,'T6,'T7,'T8,'T9,'T10,'T11,'T12,'TResult> =
  delegate of 'T1 * 'T2 * 'T3 * 'T4 * 'T5 * 'T6 * 'T7 * 'T8 * 'T9 * 'T10 * 'T11 * 'T12 -> 'TResult

Full name: System.Func<_,_,_,_,_,_,_,_,_,_,_,_,_>

--------------------
type Func<'T1,'T2,'T3,'T4,'T5,'T6,'T7,'T8,'T9,'T10,'T11,'T12,'T13,'TResult> =
  delegate of 'T1 * 'T2 * 'T3 * 'T4 * 'T5 * 'T6 * 'T7 * 'T8 * 'T9 * 'T10 * 'T11 * 'T12 * 'T13 -> 'TResult

Full name: System.Func<_,_,_,_,_,_,_,_,_,_,_,_,_,_>

--------------------
type Func<'T1,'T2,'T3,'T4,'T5,'T6,'T7,'T8,'T9,'T10,'T11,'T12,'T13,'T14,'TResult> =
  delegate of 'T1 * 'T2 * 'T3 * 'T4 * 'T5 * 'T6 * 'T7 * 'T8 * 'T9 * 'T10 * 'T11 * 'T12 * 'T13 * 'T14 -> 'TResult

Full name: System.Func<_,_,_,_,_,_,_,_,_,_,_,_,_,_,_>

--------------------
type Func<'T1,'T2,'T3,'T4,'T5,'T6,'T7,'T8,'T9,'T10,'T11,'T12,'T13,'T14,'T15,'TResult> =
  delegate of 'T1 * 'T2 * 'T3 * 'T4 * 'T5 * 'T6 * 'T7 * 'T8 * 'T9 * 'T10 * 'T11 * 'T12 * 'T13 * 'T14 * 'T15 -> 'TResult

Full name: System.Func<_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_>

--------------------
type Func<'T1,'T2,'T3,'T4,'T5,'T6,'T7,'T8,'T9,'T10,'T11,'T12,'T13,'T14,'T15,'T16,'TResult> =
  delegate of 'T1 * 'T2 * 'T3 * 'T4 * 'T5 * 'T6 * 'T7 * 'T8 * 'T9 * 'T10 * 'T11 * 'T12 * 'T13 * 'T14 * 'T15 * 'T16 -> 'TResult

Full name: System.Func<_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_>
val expr : Expr
match expr with
    | Lambdas(_,(Call(_,minfo1,_))) -> function
        | Call(obj, minfo2, args) when minfo1.MetadataToken = minfo2.MetadataToken ->
            Some args
        | _ -> None
    | _ -> failwith "invalid template parameter"
val generatePattern : expr:Expr -> env:string list -> string

Full name: Script.generatePattern


 Generate a formula pattern for an expression
 Column number - index of var + 1 in the env
 '#' is a temp placeholder for a row number
val env : string list
val printBinaryOp : (string -> Expr -> Expr -> bool -> string)
val op : string
val x : Expr
val y : Expr
val parens : bool
val res : string
val transform : (Expr -> string)
val printFunc : (string -> Expr list -> string)
val name : string
val args : Expr list
val argValues : string []
Multiple items
val string : value:'T -> string

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

--------------------
type string = String

Full name: Microsoft.FSharp.Core.string
Multiple items
module List

from Microsoft.FSharp.Collections

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

Full name: Microsoft.FSharp.Collections.List<_>
val map : mapping:('T -> 'U) -> list:'T list -> 'U list

Full name: Microsoft.FSharp.Collections.List.map
val toArray : list:'T list -> 'T []

Full name: Microsoft.FSharp.Collections.List.toArray
val sprintf : format:Printf.StringFormat<'T> -> 'T

Full name: Microsoft.FSharp.Core.ExtraTopLevelOperators.sprintf
Multiple items
active recognizer String: Expr -> string option

Full name: Microsoft.FSharp.Quotations.DerivedPatterns.( |String|_| )

--------------------
type String =
  new : value:char -> string + 7 overloads
  member Chars : int -> char
  member Clone : unit -> obj
  member CompareTo : value:obj -> int + 1 overload
  member Contains : value:string -> bool
  member CopyTo : sourceIndex:int * destination:char[] * destinationIndex:int * count:int -> unit
  member EndsWith : value:string -> bool + 2 overloads
  member Equals : obj:obj -> bool + 2 overloads
  member GetEnumerator : unit -> CharEnumerator
  member GetHashCode : unit -> int
  ...

Full name: System.String

--------------------
String(value: nativeptr<char>) : unit
String(value: nativeptr<sbyte>) : unit
String(value: char []) : unit
String(c: char, count: int) : unit
String(value: nativeptr<char>, startIndex: int, length: int) : unit
String(value: nativeptr<sbyte>, startIndex: int, length: int) : unit
String(value: char [], startIndex: int, length: int) : unit
String(value: nativeptr<sbyte>, startIndex: int, length: int, enc: Text.Encoding) : unit
String.Join(separator: string, values: Collections.Generic.IEnumerable<string>) : string
String.Join<'T>(separator: string, values: Collections.Generic.IEnumerable<'T>) : string
String.Join(separator: string, [<ParamArray>] values: obj []) : string
String.Join(separator: string, [<ParamArray>] value: string []) : string
String.Join(separator: string, value: string [], startIndex: int, count: int) : string
Multiple items
active recognizer Func: Expr -> Expr -> Expr list option

Full name: Script.( |Func|_| )


 Simplified SpecificCall


--------------------
type Func<'TResult> =
  delegate of unit -> 'TResult

Full name: System.Func<_>

--------------------
type Func<'T,'TResult> =
  delegate of 'T -> 'TResult

Full name: System.Func<_,_>

--------------------
type Func<'T1,'T2,'TResult> =
  delegate of 'T1 * 'T2 -> 'TResult

Full name: System.Func<_,_,_>

--------------------
type Func<'T1,'T2,'T3,'TResult> =
  delegate of 'T1 * 'T2 * 'T3 -> 'TResult

Full name: System.Func<_,_,_,_>

--------------------
type Func<'T1,'T2,'T3,'T4,'TResult> =
  delegate of 'T1 * 'T2 * 'T3 * 'T4 -> 'TResult

Full name: System.Func<_,_,_,_,_>

--------------------
type Func<'T1,'T2,'T3,'T4,'T5,'TResult> =
  delegate of 'T1 * 'T2 * 'T3 * 'T4 * 'T5 -> 'TResult

Full name: System.Func<_,_,_,_,_,_>

--------------------
type Func<'T1,'T2,'T3,'T4,'T5,'T6,'TResult> =
  delegate of 'T1 * 'T2 * 'T3 * 'T4 * 'T5 * 'T6 -> 'TResult

Full name: System.Func<_,_,_,_,_,_,_>

--------------------
type Func<'T1,'T2,'T3,'T4,'T5,'T6,'T7,'TResult> =
  delegate of 'T1 * 'T2 * 'T3 * 'T4 * 'T5 * 'T6 * 'T7 -> 'TResult

Full name: System.Func<_,_,_,_,_,_,_,_>

--------------------
type Func<'T1,'T2,'T3,'T4,'T5,'T6,'T7,'T8,'TResult> =
  delegate of 'T1 * 'T2 * 'T3 * 'T4 * 'T5 * 'T6 * 'T7 * 'T8 -> 'TResult

Full name: System.Func<_,_,_,_,_,_,_,_,_>

--------------------
type Func<'T1,'T2,'T3,'T4,'T5,'T6,'T7,'T8,'T9,'TResult> =
  delegate of 'T1 * 'T2 * 'T3 * 'T4 * 'T5 * 'T6 * 'T7 * 'T8 * 'T9 -> 'TResult

Full name: System.Func<_,_,_,_,_,_,_,_,_,_>

--------------------
type Func<'T1,'T2,'T3,'T4,'T5,'T6,'T7,'T8,'T9,'T10,'TResult> =
  delegate of 'T1 * 'T2 * 'T3 * 'T4 * 'T5 * 'T6 * 'T7 * 'T8 * 'T9 * 'T10 -> 'TResult

Full name: System.Func<_,_,_,_,_,_,_,_,_,_,_>

--------------------
type Func<'T1,'T2,'T3,'T4,'T5,'T6,'T7,'T8,'T9,'T10,'T11,'TResult> =
  delegate of 'T1 * 'T2 * 'T3 * 'T4 * 'T5 * 'T6 * 'T7 * 'T8 * 'T9 * 'T10 * 'T11 -> 'TResult

Full name: System.Func<_,_,_,_,_,_,_,_,_,_,_,_>

--------------------
type Func<'T1,'T2,'T3,'T4,'T5,'T6,'T7,'T8,'T9,'T10,'T11,'T12,'TResult> =
  delegate of 'T1 * 'T2 * 'T3 * 'T4 * 'T5 * 'T6 * 'T7 * 'T8 * 'T9 * 'T10 * 'T11 * 'T12 -> 'TResult

Full name: System.Func<_,_,_,_,_,_,_,_,_,_,_,_,_>

--------------------
type Func<'T1,'T2,'T3,'T4,'T5,'T6,'T7,'T8,'T9,'T10,'T11,'T12,'T13,'TResult> =
  delegate of 'T1 * 'T2 * 'T3 * 'T4 * 'T5 * 'T6 * 'T7 * 'T8 * 'T9 * 'T10 * 'T11 * 'T12 * 'T13 -> 'TResult

Full name: System.Func<_,_,_,_,_,_,_,_,_,_,_,_,_,_>

--------------------
type Func<'T1,'T2,'T3,'T4,'T5,'T6,'T7,'T8,'T9,'T10,'T11,'T12,'T13,'T14,'TResult> =
  delegate of 'T1 * 'T2 * 'T3 * 'T4 * 'T5 * 'T6 * 'T7 * 'T8 * 'T9 * 'T10 * 'T11 * 'T12 * 'T13 * 'T14 -> 'TResult

Full name: System.Func<_,_,_,_,_,_,_,_,_,_,_,_,_,_,_>

--------------------
type Func<'T1,'T2,'T3,'T4,'T5,'T6,'T7,'T8,'T9,'T10,'T11,'T12,'T13,'T14,'T15,'TResult> =
  delegate of 'T1 * 'T2 * 'T3 * 'T4 * 'T5 * 'T6 * 'T7 * 'T8 * 'T9 * 'T10 * 'T11 * 'T12 * 'T13 * 'T14 * 'T15 -> 'TResult

Full name: System.Func<_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_>

--------------------
type Func<'T1,'T2,'T3,'T4,'T5,'T6,'T7,'T8,'T9,'T10,'T11,'T12,'T13,'T14,'T15,'T16,'TResult> =
  delegate of 'T1 * 'T2 * 'T3 * 'T4 * 'T5 * 'T6 * 'T7 * 'T8 * 'T9 * 'T10 * 'T11 * 'T12 * 'T13 * 'T14 * 'T15 * 'T16 -> 'TResult

Full name: System.Func<_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_>
val mduration : settlement:'a -> maturity:'b -> coupon:'c -> yld:'d -> frequency:'e -> basis:'f -> decimal

Full name: Script.mduration
val accrint : issue:'a -> first_interest:'b -> settlement:'c -> rate:'d -> par:'e -> frequency:'f -> basis:'g -> decimal

Full name: Script.accrint
active recognizer Lambdas: Expr -> (Var list list * Expr) option

Full name: Microsoft.FSharp.Quotations.DerivedPatterns.( |Lambdas|_| )
val e : Expr
active recognizer Value: Expr -> (obj * Type) option

Full name: Microsoft.FSharp.Quotations.Patterns.( |Value|_| )
val v : obj
Multiple items
active recognizer Var: Expr -> Var option

Full name: Microsoft.FSharp.Quotations.Patterns.( |Var|_| )

--------------------
type Var =
  interface IComparable
  new : name:string * typ:Type * ?isMutable:bool -> Var
  member IsMutable : bool
  member Name : string
  member Type : Type
  static member Global : name:string * typ:Type -> Var

Full name: Microsoft.FSharp.Quotations.Var

--------------------
new : name:string * typ:Type * ?isMutable:bool -> Var
val var : Var
val tryFindIndex : predicate:('T -> bool) -> list:'T list -> int option

Full name: Microsoft.FSharp.Collections.List.tryFindIndex
property Var.Name: string
union case Option.Some: Value: 'T -> Option<'T>
val ind : int
active recognizer Call: Expr -> (Expr option * MethodInfo * Expr list) option

Full name: Microsoft.FSharp.Quotations.Patterns.( |Call|_| )
union case Option.None: Option<'T>
val mi : MethodInfo
val i : obj
property MemberInfo.DeclaringType: Type
property MemberInfo.Name: string
val unbox : value:obj -> 'T

Full name: Microsoft.FSharp.Core.Operators.unbox
active recognizer NewObject: Expr -> (ConstructorInfo * Expr list) option

Full name: Microsoft.FSharp.Quotations.Patterns.( |NewObject|_| )
val ci : ConstructorInfo
val y : obj
val m : obj
val d : obj
val failwith : message:string -> 'T

Full name: Microsoft.FSharp.Core.Operators.failwith
// "=((((1+2^3)*3)-4)/5)"
generatePattern <@@ ((1. + 2.**3.) * 3. - 4.) / 5. @@> []
// "=(-x+1)"
generatePattern <@@ fun (x: decimal) -> -x + +1M @@> [ ]
// "=R#C1^4"
generatePattern <@@ fun a b -> a ** 4. @@> ["a"; "b"]
// "=(R#C1+R#C2)" - arrays can be used instead of explicit var names
generatePattern <@@ fun (args: _ array) -> args.[0] + args.[1] @@> []
// "=ACCRINT(R#C1, DATE(2010, 9, 8), R#C2, 10, 100, 2, 0)"
generatePattern <@@ fun issue settlement ->
    accrint issue (DateTime(2010,9,8)) settlement 10 100 2 0 @@> [ "issue"; "settlement"]
Multiple items
type ReflectedDefinitionAttribute =
  inherit Attribute
  new : unit -> ReflectedDefinitionAttribute

Full name: Microsoft.FSharp.Core.ReflectedDefinitionAttribute

--------------------
new : unit -> ReflectedDefinitionAttribute
val sum : a:decimal -> b:decimal -> decimal

Full name: Script.Test.sum
val a : decimal
Multiple items
val decimal : value:'T -> decimal (requires member op_Explicit)

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

--------------------
type decimal = Decimal

Full name: Microsoft.FSharp.Core.decimal

--------------------
type decimal<'Measure> = decimal

Full name: Microsoft.FSharp.Core.decimal<_>
val b : decimal
val mdurationMonth : m:'a -> c:'b -> y:'c -> f:'d -> basis:'e -> decimal

Full name: Script.Test.mdurationMonth
val m : 'a
val c : 'b
val y : 'c
val f : 'd
val basis : 'e
Multiple items
type DateTime =
  struct
    new : ticks:int64 -> DateTime + 10 overloads
    member Add : value:TimeSpan -> DateTime
    member AddDays : value:float -> DateTime
    member AddHours : value:float -> DateTime
    member AddMilliseconds : value:float -> DateTime
    member AddMinutes : value:float -> DateTime
    member AddMonths : months:int -> DateTime
    member AddSeconds : value:float -> DateTime
    member AddTicks : value:int64 -> DateTime
    member AddYears : value:int -> DateTime
    ...
  end

Full name: System.DateTime

--------------------
DateTime()
   (+0 other overloads)
DateTime(ticks: int64) : unit
   (+0 other overloads)
DateTime(ticks: int64, kind: DateTimeKind) : unit
   (+0 other overloads)
DateTime(year: int, month: int, day: int) : unit
   (+0 other overloads)
DateTime(year: int, month: int, day: int, calendar: Globalization.Calendar) : unit
   (+0 other overloads)
DateTime(year: int, month: int, day: int, hour: int, minute: int, second: int) : unit
   (+0 other overloads)
DateTime(year: int, month: int, day: int, hour: int, minute: int, second: int, kind: DateTimeKind) : unit
   (+0 other overloads)
DateTime(year: int, month: int, day: int, hour: int, minute: int, second: int, calendar: Globalization.Calendar) : unit
   (+0 other overloads)
DateTime(year: int, month: int, day: int, hour: int, minute: int, second: int, millisecond: int) : unit
   (+0 other overloads)
DateTime(year: int, month: int, day: int, hour: int, minute: int, second: int, millisecond: int, kind: DateTimeKind) : unit
   (+0 other overloads)
val run : export:(string [] list -> int -> obj list -> unit) -> unit

Full name: Script.Test.run
val export : (string [] list -> int -> obj list -> unit)
val data : obj list list
type obj = Object

Full name: Microsoft.FSharp.Core.obj
type 'T list = List<'T>

Full name: Microsoft.FSharp.Collections.list<_>
[
            [ 42; 0; DateTime(2012, 1, 7); DateTime(2030, 1, 1); 15M; 0.9M; 1; 1 ]
            [ null; null; null; DateTime(2016, 1, 7); 8M; 9M; 2; 1 ]
        ]
val dataColumns : string list
val funcs : string list
val reflectedDefinitions : Map<string,Expr>
val methods : MethodInfo []
type Assembly =
  member CodeBase : string
  member CreateInstance : typeName:string -> obj + 2 overloads
  member EntryPoint : MethodInfo
  member Equals : o:obj -> bool
  member EscapedCodeBase : string
  member Evidence : Evidence
  member FullName : string
  member GetCustomAttributes : inherit:bool -> obj[] + 1 overload
  member GetCustomAttributesData : unit -> IList<CustomAttributeData>
  member GetExportedTypes : unit -> Type[]
  ...

Full name: System.Reflection.Assembly
Assembly.GetExecutingAssembly() : Assembly
type Array =
  member Clone : unit -> obj
  member CopyTo : array:Array * index:int -> unit + 1 overload
  member GetEnumerator : unit -> IEnumerator
  member GetLength : dimension:int -> int
  member GetLongLength : dimension:int -> int64
  member GetLowerBound : dimension:int -> int
  member GetUpperBound : dimension:int -> int
  member GetValue : [<ParamArray>] indices:int[] -> obj + 7 overloads
  member Initialize : unit -> unit
  member IsFixedSize : bool
  ...

Full name: System.Array
val collect : mapping:('T -> 'U []) -> array:'T [] -> 'U []

Full name: Microsoft.FSharp.Collections.Array.collect
val t : Type
Type.GetMethods() : MethodInfo []
Type.GetMethods(bindingAttr: BindingFlags) : MethodInfo []
val foldBack : folder:('T -> 'State -> 'State) -> array:'T [] -> state:'State -> 'State

Full name: Microsoft.FSharp.Collections.Array.foldBack
val state : (string * Expr) list
Multiple items
type Expr =
  override Equals : obj:obj -> bool
  member GetFreeVars : unit -> seq<Var>
  member Substitute : substitution:(Var -> Expr option) -> Expr
  member ToString : full:bool -> string
  member CustomAttributes : Expr list
  member Type : Type
  static member AddressOf : target:Expr -> Expr
  static member AddressSet : target:Expr * value:Expr -> Expr
  static member Application : functionExpr:Expr * argument:Expr -> Expr
  static member Applications : functionExpr:Expr * arguments:Expr list list -> Expr
  ...

Full name: Microsoft.FSharp.Quotations.Expr

--------------------
type Expr<'T> =
  inherit Expr
  member Raw : Expr

Full name: Microsoft.FSharp.Quotations.Expr<_>
static member Expr.TryGetReflectedDefinition : methodBase:MethodBase -> Expr option
Multiple items
module Map

from Microsoft.FSharp.Collections

--------------------
type Map<'Key,'Value (requires comparison)> =
  interface IEnumerable
  interface IComparable
  interface IEnumerable<KeyValuePair<'Key,'Value>>
  interface ICollection<KeyValuePair<'Key,'Value>>
  interface IDictionary<'Key,'Value>
  new : elements:seq<'Key * 'Value> -> Map<'Key,'Value>
  member Add : key:'Key * value:'Value -> Map<'Key,'Value>
  member ContainsKey : key:'Key -> bool
  override Equals : obj -> bool
  member Remove : key:'Key -> Map<'Key,'Value>
  ...

Full name: Microsoft.FSharp.Collections.Map<_,_>

--------------------
new : elements:seq<'Key * 'Value> -> Map<'Key,'Value>
val ofList : elements:('Key * 'T) list -> Map<'Key,'T> (requires comparison)

Full name: Microsoft.FSharp.Collections.Map.ofList
val unquote : (Expr option -> string [] option)
module Option

from Microsoft.FSharp.Core
val bind : binder:('T -> 'U option) -> option:'T option -> 'U option

Full name: Microsoft.FSharp.Core.Option.bind
val formulae : string [] list
member Map.TryFind : key:'Key -> 'Value option
val filter : predicate:('T -> bool) -> list:'T list -> 'T list

Full name: Microsoft.FSharp.Collections.List.filter
val isSome : option:'T option -> bool

Full name: Microsoft.FSharp.Core.Option.isSome
val get : option:'T option -> 'T

Full name: Microsoft.FSharp.Core.Option.get
val iteri : action:(int -> 'T -> unit) -> list:'T list -> unit

Full name: Microsoft.FSharp.Collections.List.iteri
val export : exportValue:(int -> int -> 'a -> unit) -> exportFunc:(string -> string -> unit) -> patterns:string [] list -> row:int -> items:'a list -> unit

Full name: Script.export


 Export data with given pattern
val exportValue : (int -> int -> 'a -> unit)
val exportFunc : (string -> string -> unit)
val patterns : string [] list
val row : int
val items : 'a list
let row = row + 1
    let j = items.Length
    let formulae = patterns |> List.map (fun arr -> String.Join (string row, arr))
    List.iteri (exportValue row) items
    List.iteri (fun i formula ->
        let cell = sprintf "%c%d" (char (65 + i + j)) row
        exportFunc cell formula) formulae
module Test

from Script
val i : int
val item : obj
val printfn : format:Printf.TextWriterFormat<'T> -> 'T

Full name: Microsoft.FSharp.Core.ExtraTopLevelOperators.printfn
val cell : string
val formula : string
val app : ApplicationClass

Full name: Script.app
Multiple items
type ApplicationClass =
  new : unit -> ApplicationClass
  member ActivateMicrosoftApp : Index:XlMSApplication -> unit
  member ActiveCell : Range
  member ActiveChart : Chart
  member ActiveDialog : DialogSheet
  member ActiveEncryptionSession : int
  member ActiveMenuBar : MenuBar
  member ActivePrinter : string with get, set
  member ActiveProtectedViewWindow : ProtectedViewWindow
  member ActiveSheet : obj
  ...

Full name: Microsoft.Office.Interop.Excel.ApplicationClass

--------------------
ApplicationClass() : unit
val workbook : Workbook

Full name: Script.workbook
Workbooks.Add(?Template: obj) : Workbook
type XlWBATemplate =
  | xlWBATChart = -4109
  | xlWBATExcel4IntlMacroSheet = 4
  | xlWBATExcel4MacroSheet = 3
  | xlWBATWorksheet = -4167

Full name: Microsoft.Office.Interop.Excel.XlWBATemplate
field XlWBATemplate.xlWBATWorksheet = -4167
val worksheet : Worksheet

Full name: Script.worksheet
type Worksheet =

Full name: Microsoft.Office.Interop.Excel.Worksheet
property _Worksheet.Cells: Range
property _Worksheet.Range: obj * obj -> Range
type XlReferenceStyle =
  | xlA1 = 1
  | xlR1C1 = -4150

Full name: Microsoft.Office.Interop.Excel.XlReferenceStyle
field XlReferenceStyle.xlA1 = 1
// release COM objects
let inline release (objs: obj list) =
    List.iter (System.Runtime.InteropServices.Marshal.ReleaseComObject >> ignore) objs

let filename = "test.xls"
workbook.SaveAs(filename, XlFileFormat.xlWorkbookNormal)
workbook.Close true
app.Quit()

release [worksheet; workbook; app]
Next Version Raw view Test code New version

More information

Link:http://fssnip.net/9T
Posted:12 years ago
Author:Natallie Baikevich
Tags: quotations , excel , reflection