6 people like it.

Spreadsheet

Spreadsheet script runnable inside http://tryfsharp.org includes a custom DataGrid and a parser for simple formulas e.g.: =1+1 =SUM(A1,A2) Add your own functions to the evaluate function. For a more comprehensive implementation check out http://cellz.codeplex.com

  1: 
  2: 
  3: 
  4: 
  5: 
  6: 
  7: 
  8: 
  9: 
 10: 
 11: 
 12: 
 13: 
 14: 
 15: 
 16: 
 17: 
 18: 
 19: 
 20: 
 21: 
 22: 
 23: 
 24: 
 25: 
 26: 
 27: 
 28: 
 29: 
 30: 
 31: 
 32: 
 33: 
 34: 
 35: 
 36: 
 37: 
 38: 
 39: 
 40: 
 41: 
 42: 
 43: 
 44: 
 45: 
 46: 
 47: 
 48: 
 49: 
 50: 
 51: 
 52: 
 53: 
 54: 
 55: 
 56: 
 57: 
 58: 
 59: 
 60: 
 61: 
 62: 
 63: 
 64: 
 65: 
 66: 
 67: 
 68: 
 69: 
 70: 
 71: 
 72: 
 73: 
 74: 
 75: 
 76: 
 77: 
 78: 
 79: 
 80: 
 81: 
 82: 
 83: 
 84: 
 85: 
 86: 
 87: 
 88: 
 89: 
 90: 
 91: 
 92: 
 93: 
 94: 
 95: 
 96: 
 97: 
 98: 
 99: 
100: 
101: 
102: 
103: 
104: 
105: 
106: 
107: 
108: 
109: 
110: 
111: 
112: 
113: 
114: 
115: 
116: 
117: 
118: 
119: 
120: 
121: 
122: 
123: 
124: 
125: 
126: 
127: 
128: 
129: 
130: 
131: 
132: 
133: 
134: 
135: 
136: 
137: 
138: 
139: 
140: 
141: 
142: 
143: 
144: 
145: 
146: 
147: 
148: 
149: 
150: 
151: 
152: 
153: 
154: 
155: 
156: 
157: 
158: 
159: 
160: 
161: 
162: 
163: 
164: 
165: 
166: 
167: 
168: 
169: 
170: 
171: 
172: 
173: 
174: 
175: 
176: 
177: 
178: 
179: 
180: 
181: 
182: 
183: 
184: 
185: 
186: 
187: 
188: 
189: 
190: 
191: 
192: 
193: 
194: 
195: 
196: 
197: 
198: 
199: 
200: 
201: 
202: 
203: 
204: 
205: 
206: 
207: 
208: 
209: 
210: 
211: 
212: 
213: 
214: 
215: 
216: 
217: 
218: 
219: 
220: 
221: 
222: 
223: 
224: 
225: 
226: 
227: 
228: 
229: 
230: 
231: 
232: 
233: 
234: 
235: 
236: 
237: 
238: 
239: 
240: 
241: 
242: 
243: 
244: 
245: 
246: 
247: 
248: 
249: 
250: 
251: 
252: 
253: 
254: 
255: 
256: 
257: 
258: 
259: 
260: 
261: 
262: 
263: 
264: 
265: 
266: 
267: 
268: 
269: 
270: 
271: 
272: 
273: 
274: 
275: 
276: 
277: 
278: 
279: 
280: 
281: 
282: 
283: 
284: 
285: 
286: 
287: 
288: 
289: 
290: 
291: 
292: 
293: 
294: 
295: 
296: 
297: 
298: 
299: 
300: 
301: 
302: 
303: 
304: 
305: 
306: 
307: 
308: 
309: 
310: 
311: 
312: 
313: 
#if INTERACTIVE
#else
namespace TryFSharp
#endif
module Spreadsheet =

    type token =
        | WhiteSpace
        | Symbol of char
        | OpToken of string
        | RefToken of int * int
        | StrToken of string
        | NumToken of decimal 

    let (|Match|_|) pattern input =
        let m = System.Text.RegularExpressions.Regex.Match(input, pattern)
        if m.Success then Some m.Value else None

    let toRef (s:string) =
        let col = int s.[0] - int 'A'
        let row = s.Substring 1 |> int
        col, row-1

    let toToken = function
        | Match @"^\s+" s -> s, WhiteSpace
        | Match @"^\+|^\-|^\*|^\/"  s -> s, OpToken s
        | Match @"^=|^<>|^<=|^>=|^>|^<"  s -> s, OpToken s   
        | Match @"^\(|^\)|^\,|^\:" s -> s, Symbol s.[0]   
        | Match @"^[A-Z]\d+" s -> s, s |> toRef |> RefToken
        | Match @"^[A-Za-z]+" s -> s, StrToken s
        | Match @"^\d+(\.\d+)?|\.\d+" s -> s, s |> decimal |> NumToken
        | _ -> invalidOp ""

    let tokenize s =
        let rec tokenize' index (s:string) =
            if index = s.Length then [] 
            else
                let next = s.Substring index 
                let text, token = toToken next
                token :: tokenize' (index + text.Length) s
        tokenize' 0 s
        |> List.choose (function WhiteSpace -> None | t -> Some t)

    type arithmeticOp = Add | Sub | Mul | Div
    type logicalOp = Eq | Lt | Gt | Le | Ge | Ne
    type formula =
        | Neg of formula
        | ArithmeticOp of formula * arithmeticOp * formula
        | LogicalOp of formula * logicalOp * formula
        | Num of decimal
        | Ref of int * int
        | Range of int * int * int * int
        | Fun of string * formula list

    let rec (|Term|_|) = function
        | Sum(f1, (OpToken(LogicOp op))::Sum(f2,t)) -> Some(LogicalOp(f1,op,f2),t)
        | Sum(f1,t) -> Some (f1,t)
        | _ -> None
    and (|LogicOp|_|) = function
        | "=" ->  Some Eq | "<>" -> Some Ne
        | "<" ->  Some Lt | ">"  -> Some Gt
        | "<=" -> Some Le | ">=" -> Some Ge
        | _ -> None
    and (|Sum|_|) = function
        | Factor(f1, t) ->      
            let rec aux f1 = function        
                | SumOp op::Factor(f2, t) -> aux (ArithmeticOp(f1,op,f2)) t               
                | t -> Some(f1, t)      
            aux f1 t  
        | _ -> None
    and (|SumOp|_|) = function 
        | OpToken "+" -> Some Add | OpToken "-" -> Some Sub 
        | _ -> None
    and (|Factor|_|) = function  
        | OpToken "-"::Factor(f, t) -> Some(Neg f, t)
        | Atom(f1, ProductOp op::Factor(f2, t)) ->
            Some(ArithmeticOp(f1,op,f2), t)       
        | Atom(f, t) -> Some(f, t)  
        | _ -> None    
    and (|ProductOp|_|) = function
        | OpToken "*" -> Some Mul | OpToken "/" -> Some Div
        | _ -> None
    and (|Atom|_|) = function      
        | NumToken n::t -> Some(Num n, t)
        | RefToken(x1,y1)::(Symbol ':'::RefToken(x2,y2)::t) -> 
            Some(Range(min x1 x2,min y1 y2,max x1 x2,max y1 y2),t)  
        | RefToken(x,y)::t -> Some(Ref(x,y), t)
        | Symbol '('::Term(f, Symbol ')'::t) -> Some(f, t)
        | StrToken s::Tuple(ps, t) -> Some(Fun(s,ps),t)  
        | _ -> None
    and (|Tuple|_|) = function
        | Symbol '('::Params(ps, Symbol ')'::t) -> Some(ps, t)  
        | _ -> None
    and (|Params|_|) = function
        | Term(f1, t) ->
            let rec aux fs = function
                | Symbol ','::Term(f2, t) -> aux (fs@[f2]) t
                | t -> fs, t
            Some(aux [f1] t)
        | t -> Some ([],t)

    let parse s = 
        tokenize s |> function 
        | Term(f,[]) -> f 
        | _ -> failwith "Failed to parse formula"

    let evaluate valueAt formula =
        let rec eval = function
            | Neg f -> - (eval f)
            | ArithmeticOp(f1,op,f2) -> arithmetic op (eval f1) (eval f2)
            | LogicalOp(f1,op,f2) -> if logic op (eval f1) (eval f2) then 0.0M else -1.0M
            | Num d -> d
            | Ref(x,y) -> valueAt(x,y) |> decimal
            | Range _ -> invalidOp "Expected in function"
            | Fun("SUM",ps) -> ps |> evalAll |> List.sum
            | Fun("IF",[condition;f1;f2]) -> 
                if (eval condition)=0.0M then eval f1 else eval f2 
            | Fun(_,_) -> failwith "Unknown function"
        and arithmetic = function
            | Add -> (+) | Sub -> (-) | Mul -> (*) | Div -> (/)
        and logic = function         
            | Eq -> (=)  | Ne -> (<>)
            | Lt -> (<)  | Gt -> (>)
            | Le -> (<=) | Ge -> (>=)
        and evalAll ps =
            ps |> List.collect (function            
                | Range(x1,y1,x2,y2) ->
                    [for x=x1 to x2 do for y=y1 to y2 do yield valueAt(x,y) |> decimal]
                | x -> [eval x]            
            )
        eval formula

    let references formula =
        let rec traverse = function
            | Ref(x,y) -> [x,y]
            | Range(x1,y1,x2,y2) -> 
                [for x=x1 to x2 do for y=y1 to y2 do yield x,y]
            | Fun(_,ps) -> ps |> List.collect traverse
            | ArithmeticOp(f1,_,f2) | LogicalOp(f1,_,f2) -> 
                traverse f1 @ traverse f2
            | _ -> []
        traverse formula

open Spreadsheet
open System.ComponentModel

type Cell (sheet:Sheet) as cell =
    inherit ObservableObject()
    let mutable value = ""
    let mutable data = ""       
    let mutable formula : formula option = None
    let updated = Event<_>()
    let mutable subscriptions : System.IDisposable list = []   
    let cellAt(x,y) = 
        let (row : Row) = Array.get sheet.Rows y
        let (cell : Cell) = Array.get row.Cells x
        cell
    let valueAt address = (cellAt address).Value
    let eval formula =         
        try (evaluate valueAt formula).ToString()       
        with _ -> "N/A"
    let parseFormula (text:string) =
        if text.StartsWith "="
        then                
            try true, parse (text.Substring 1) |> Some
            with _ -> true, None
        else false, None
    let update newValue generation =
        if newValue <> value then
            value <- newValue
            updated.Trigger generation
            cell.Notify "Value"
    let unsubscribe () =
        subscriptions |> List.iter (fun d -> d.Dispose())
        subscriptions <- []
    let subscribe formula addresses =
        let remember x = subscriptions <- x :: subscriptions
        for address in addresses do
            let cell' : Cell = cellAt address
            cell'.Updated
            |> Observable.subscribe (fun generation ->   
                if generation < sheet.MaxGeneration then
                    let newValue = eval formula
                    update newValue (generation+1)
            ) |> remember
    member cell.Data 
        with get () = data 
        and set (text:string) =
            data <- text        
            cell.Notify "Data"          
            let isFormula, newFormula = parseFormula text               
            formula <- newFormula
            unsubscribe()
            formula |> Option.iter (fun f -> references f |> subscribe f)
            let newValue =
                match isFormula, formula with           
                | _, Some f -> eval f
                | true, _ -> "N/A"
                | _, None -> text
            update newValue 0
    member cell.Value = value
    member cell.Updated = updated.Publish     
and Row (index,colCount,sheet) =
    let cells = Array.init colCount (fun i -> Cell(sheet))
    member row.Cells = cells
    member row.Index = index
and Sheet (colCount,rowCount) as sheet =
    let cols = Array.init colCount (fun i -> string (int 'A' + i |> char)) 
    let rows = Array.init rowCount (fun index -> Row(index+1,colCount,sheet))
    member sheet.Columns = cols
    member sheet.Rows = rows
    member sheet.MaxGeneration = 1000
and ObservableObject() =
    let propertyChanged = 
        Event<PropertyChangedEventHandler,PropertyChangedEventArgs>()
    member this.Notify name =
        propertyChanged.Trigger(this,PropertyChangedEventArgs name)
    interface INotifyPropertyChanged with
        [<CLIEvent>]
        member this.PropertyChanged = propertyChanged.Publish
        
open System
open System.Collections
open System.Windows
open System.Windows.Controls
open System.Windows.Data
open System.Windows.Input
open System.Windows.Media

type DataGrid(headings:seq<_>, items:IEnumerable, cellFactory:int*int->FrameworkElement) as grid =
    inherit Grid()    
    do  grid.ShowGridLines <- true   
    let createHeader heading horizontalAlignment =
        let header = TextBlock(Text=heading)
        header.HorizontalAlignment <- horizontalAlignment
        header.VerticalAlignment <- VerticalAlignment.Center
        let container = Grid(Background=SolidColorBrush Colors.Gray)        
        container.Children.Add header |> ignore
        container
    do  ColumnDefinition(Width=GridLength(24.0)) |> grid.ColumnDefinitions.Add 
    do  headings |> Seq.iteri (fun i heading ->
        let width = GridLength(64.0)
        ColumnDefinition(Width=width) |> grid.ColumnDefinitions.Add       
        let header = createHeader heading HorizontalAlignment.Center
        grid.Children.Add header |> ignore
        Grid.SetColumn(header,i+1)
    )   
    do  let height = GridLength(24.0)
        RowDefinition(Height=height) |> grid.RowDefinitions.Add
        let mutable y = 1
        for item in items do
        RowDefinition(Height=height) |> grid.RowDefinitions.Add
        let header = createHeader (y.ToString()) HorizontalAlignment.Right       
        grid.Children.Add header |> ignore
        Grid.SetRow(header,y)
        for x=1 to Seq.length headings do
            let cell = cellFactory (x-1,y-1)
            cell.DataContext <- item
            grid.Children.Add cell |> ignore
            Grid.SetColumn(cell,x)
            Grid.SetRow(cell,y)
        y <- y + 1

type View() =
    inherit UserControl()  
    let sheet = Sheet(26,50)
    let remember = ignore
    let cellFactory (x,y) =
        let binding = Binding(sprintf "Cells.[%d].Data" x)   
        binding.Mode <- BindingMode.TwoWay
        let edit = TextBox()
        edit.SetBinding(TextBox.TextProperty,binding) |> ignore        
        edit.Visibility <- Visibility.Collapsed
        let view = Button(Background=SolidColorBrush Colors.White)
        view.BorderBrush <- null
        view.Style <- null
        let binding = Binding(sprintf "Cells.[%d].Value" x)
        let block = TextBlock()
        block.SetBinding(TextBlock.TextProperty, binding) |> ignore
        view.Content <- block
        view.HorizontalContentAlignment <- HorizontalAlignment.Left
        view.VerticalContentAlignment <- VerticalAlignment.Center
        let setEditMode _ =
            edit.Visibility <- Visibility.Visible
            view.Visibility <- Visibility.Collapsed                   
            edit.Focus() |> ignore
        let setViewMode _ =
            edit.Visibility <- Visibility.Collapsed
            view.Visibility <- Visibility.Visible        
        view.Click |> Observable.subscribe setEditMode |> remember
        edit.LostFocus |> Observable.subscribe setViewMode |> remember        
        let enterKeyDown = edit.KeyDown |> Observable.filter (fun e -> e.Key = Key.Enter)
        enterKeyDown |> Observable.subscribe setViewMode |> remember
        let container = Grid()
        container.Children.Add view |> ignore
        container.Children.Add edit |> ignore
        container :> FrameworkElement
    let viewer = ScrollViewer(HorizontalScrollBarVisibility=ScrollBarVisibility.Auto)
    do  viewer.Content <- DataGrid(sheet.Columns,sheet.Rows,cellFactory)
    do  base.Content <- viewer

#if INTERACTIVE
open Microsoft.TryFSharp
App.Dispatch (fun() -> 
    App.Console.ClearCanvas()
    View() |> App.Console.Canvas.Children.Add
    App.Console.CanvasPosition <- CanvasPosition.Right
)
#else
type App() as app =
    inherit System.Windows.Application()
    do app.Startup.Add(fun _ -> app.RootVisual <- View())
#endif
type token =
  | WhiteSpace
  | Symbol of char
  | OpToken of string
  | RefToken of int * int
  | StrToken of string
  | NumToken of decimal

Full name: Script.Spreadsheet.token
union case token.WhiteSpace: token
union case token.Symbol: char -> token
Multiple items
val char : value:'T -> char (requires member op_Explicit)

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

--------------------
type char = System.Char

Full name: Microsoft.FSharp.Core.char
union case token.OpToken: string -> token
Multiple items
val string : value:'T -> string

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

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

Full name: Microsoft.FSharp.Core.string
union case token.RefToken: int * int -> token
Multiple items
val int : value:'T -> int (requires member op_Explicit)

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

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

Full name: Microsoft.FSharp.Core.int

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

Full name: Microsoft.FSharp.Core.int<_>
union case token.StrToken: string -> token
union case token.NumToken: decimal -> token
Multiple items
val decimal : value:'T -> decimal (requires member op_Explicit)

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

--------------------
type decimal = System.Decimal

Full name: Microsoft.FSharp.Core.decimal

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

Full name: Microsoft.FSharp.Core.decimal<_>
val pattern : string
val input : string
val m : System.Text.RegularExpressions.Match
namespace System
namespace System.Text
namespace System.Text.RegularExpressions
Multiple items
type Regex =
  new : pattern:string -> Regex + 1 overload
  member GetGroupNames : unit -> string[]
  member GetGroupNumbers : unit -> int[]
  member GroupNameFromNumber : i:int -> string
  member GroupNumberFromName : name:string -> int
  member IsMatch : input:string -> bool + 1 overload
  member Match : input:string -> Match + 2 overloads
  member Matches : input:string -> MatchCollection + 1 overload
  member Options : RegexOptions
  member Replace : input:string * replacement:string -> string + 5 overloads
  ...

Full name: System.Text.RegularExpressions.Regex

--------------------
System.Text.RegularExpressions.Regex(pattern: string) : unit
System.Text.RegularExpressions.Regex(pattern: string, options: System.Text.RegularExpressions.RegexOptions) : unit
System.Text.RegularExpressions.Regex.Match(input: string, pattern: string) : System.Text.RegularExpressions.Match
System.Text.RegularExpressions.Regex.Match(input: string, pattern: string, options: System.Text.RegularExpressions.RegexOptions) : System.Text.RegularExpressions.Match
property System.Text.RegularExpressions.Group.Success: bool
union case Option.Some: Value: 'T -> Option<'T>
property System.Text.RegularExpressions.Capture.Value: string
union case Option.None: Option<'T>
val toRef : s:string -> int * int

Full name: Script.Spreadsheet.toRef
val s : string
val col : int
val row : int
System.String.Substring(startIndex: int) : string
System.String.Substring(startIndex: int, length: int) : string
val toToken : _arg1:string -> string * token

Full name: Script.Spreadsheet.toToken
active recognizer Match: string -> string -> string option

Full name: Script.Spreadsheet.( |Match|_| )
val invalidOp : message:string -> 'T

Full name: Microsoft.FSharp.Core.Operators.invalidOp
val tokenize : s:string -> token list

Full name: Script.Spreadsheet.tokenize
val tokenize' : (int -> string -> token list)
val index : int
property System.String.Length: int
val next : string
val text : string
Multiple items
val token : token

--------------------
type token =
  | WhiteSpace
  | Symbol of char
  | OpToken of string
  | RefToken of int * int
  | StrToken of string
  | NumToken of decimal

Full name: Script.Spreadsheet.token
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 choose : chooser:('T -> 'U option) -> list:'T list -> 'U list

Full name: Microsoft.FSharp.Collections.List.choose
val t : token
type arithmeticOp =
  | Add
  | Sub
  | Mul
  | Div

Full name: Script.Spreadsheet.arithmeticOp
union case arithmeticOp.Add: arithmeticOp
union case arithmeticOp.Sub: arithmeticOp
union case arithmeticOp.Mul: arithmeticOp
union case arithmeticOp.Div: arithmeticOp
type logicalOp =
  | Eq
  | Lt
  | Gt
  | Le
  | Ge
  | Ne

Full name: Script.Spreadsheet.logicalOp
union case logicalOp.Eq: logicalOp
union case logicalOp.Lt: logicalOp
union case logicalOp.Gt: logicalOp
union case logicalOp.Le: logicalOp
union case logicalOp.Ge: logicalOp
union case logicalOp.Ne: logicalOp
type formula =
  | Neg of formula
  | ArithmeticOp of formula * arithmeticOp * formula
  | LogicalOp of formula * logicalOp * formula
  | Num of decimal
  | Ref of int * int
  | Range of int * int * int * int
  | Fun of string * formula list

Full name: Script.Spreadsheet.formula
union case formula.Neg: formula -> formula
union case formula.ArithmeticOp: formula * arithmeticOp * formula -> formula
union case formula.LogicalOp: formula * logicalOp * formula -> formula
union case formula.Num: decimal -> formula
union case formula.Ref: int * int -> formula
union case formula.Range: int * int * int * int -> formula
union case formula.Fun: string * formula list -> formula
type 'T list = List<'T>

Full name: Microsoft.FSharp.Collections.list<_>
active recognizer Sum: token list -> (formula * token list) option

Full name: Script.Spreadsheet.( |Sum|_| )
val f1 : formula
active recognizer LogicOp: string -> logicalOp option

Full name: Script.Spreadsheet.( |LogicOp|_| )
val op : logicalOp
val f2 : formula
val t : token list
active recognizer Factor: token list -> (formula * token list) option

Full name: Script.Spreadsheet.( |Factor|_| )
val aux : (formula -> token list -> (formula * token list) option)
active recognizer SumOp: token -> arithmeticOp option

Full name: Script.Spreadsheet.( |SumOp|_| )
val op : arithmeticOp
val f : formula
active recognizer Atom: token list -> (formula * token list) option

Full name: Script.Spreadsheet.( |Atom|_| )
active recognizer ProductOp: token -> arithmeticOp option

Full name: Script.Spreadsheet.( |ProductOp|_| )
val n : decimal
val x1 : int
val y1 : int
val x2 : int
val y2 : int
val min : e1:'T -> e2:'T -> 'T (requires comparison)

Full name: Microsoft.FSharp.Core.Operators.min
val max : e1:'T -> e2:'T -> 'T (requires comparison)

Full name: Microsoft.FSharp.Core.Operators.max
val x : int
val y : int
active recognizer Term: token list -> (formula * token list) option

Full name: Script.Spreadsheet.( |Term|_| )
active recognizer Tuple: token list -> (formula list * token list) option

Full name: Script.Spreadsheet.( |Tuple|_| )
val ps : formula list
active recognizer Params: token list -> (formula list * token list) option

Full name: Script.Spreadsheet.( |Params|_| )
val aux : (formula list -> token list -> formula list * token list)
val fs : formula list
val parse : s:string -> formula

Full name: Script.Spreadsheet.parse
val failwith : message:string -> 'T

Full name: Microsoft.FSharp.Core.Operators.failwith
val evaluate : valueAt:(int * int -> string) -> formula:formula -> decimal

Full name: Script.Spreadsheet.evaluate
val valueAt : (int * int -> string)
Multiple items
val formula : formula

--------------------
type formula =
  | Neg of formula
  | ArithmeticOp of formula * arithmeticOp * formula
  | LogicalOp of formula * logicalOp * formula
  | Num of decimal
  | Ref of int * int
  | Range of int * int * int * int
  | Fun of string * formula list

Full name: Script.Spreadsheet.formula
val eval : (formula -> decimal)
val arithmetic : (arithmeticOp -> decimal -> decimal -> decimal)
val logic : (logicalOp -> decimal -> decimal -> bool)
val d : decimal
val evalAll : (formula list -> decimal list)
val sum : list:'T list -> 'T (requires member ( + ) and member get_Zero)

Full name: Microsoft.FSharp.Collections.List.sum
val condition : formula
val collect : mapping:('T -> 'U list) -> list:'T list -> 'U list

Full name: Microsoft.FSharp.Collections.List.collect
val x : formula
val references : formula:formula -> (int * int) list

Full name: Script.Spreadsheet.references
val traverse : (formula -> (int * int) list)
module Spreadsheet

from Script
namespace System.ComponentModel
Multiple items
type Cell =
  inherit ObservableObject
  new : sheet:Sheet -> Cell
  member Data : string
  member Updated : IEvent<int>
  member Value : string
  member Data : string with set

Full name: Script.Cell

--------------------
new : sheet:Sheet -> Cell
val sheet : Sheet
Multiple items
type Sheet =
  new : colCount:int * rowCount:int -> Sheet
  member Columns : string []
  member MaxGeneration : int
  member Rows : Row []

Full name: Script.Sheet

--------------------
new : colCount:int * rowCount:int -> Sheet
val cell : Cell
Multiple items
type ObservableObject =
  interface INotifyPropertyChanged
  new : unit -> ObservableObject
  member Notify : name:string -> unit

Full name: Script.ObservableObject

--------------------
new : unit -> ObservableObject
val mutable value : string
val mutable data : string
Multiple items
val mutable formula : formula option

--------------------
type formula =
  | Neg of formula
  | ArithmeticOp of formula * arithmeticOp * formula
  | LogicalOp of formula * logicalOp * formula
  | Num of decimal
  | Ref of int * int
  | Range of int * int * int * int
  | Fun of string * formula list

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

Full name: Microsoft.FSharp.Core.option<_>
val updated : Event<int>
Multiple items
module Event

from Microsoft.FSharp.Control

--------------------
type Event<'T> =
  new : unit -> Event<'T>
  member Trigger : arg:'T -> unit
  member Publish : IEvent<'T>

Full name: Microsoft.FSharp.Control.Event<_>

--------------------
type Event<'Delegate,'Args (requires delegate and 'Delegate :> Delegate)> =
  new : unit -> Event<'Delegate,'Args>
  member Trigger : sender:obj * args:'Args -> unit
  member Publish : IEvent<'Delegate,'Args>

Full name: Microsoft.FSharp.Control.Event<_,_>

--------------------
new : unit -> Event<'T>

--------------------
new : unit -> Event<'Delegate,'Args>
val mutable subscriptions : System.IDisposable list
type IDisposable =
  member Dispose : unit -> unit

Full name: System.IDisposable
val cellAt : (int * int -> Cell)
val row : Row
Multiple items
type Row =
  new : index:int * colCount:int * sheet:Sheet -> Row
  member Cells : Cell []
  member Index : int

Full name: Script.Row

--------------------
new : index:int * colCount:int * sheet:Sheet -> Row
module Array

from Microsoft.FSharp.Collections
val get : array:'T [] -> index:int -> 'T

Full name: Microsoft.FSharp.Collections.Array.get
property Sheet.Rows: Row []
property Row.Cells: Cell []
val address : int * int
val eval : (formula -> string)
val parseFormula : (string -> bool * formula option)
System.String.StartsWith(value: string) : bool
System.String.StartsWith(value: string, comparisonType: System.StringComparison) : bool
System.String.StartsWith(value: string, ignoreCase: bool, culture: System.Globalization.CultureInfo) : bool
val update : (string -> int -> unit)
val newValue : string
val generation : int
member Event.Trigger : arg:'T -> unit
member ObservableObject.Notify : name:string -> unit
val unsubscribe : (unit -> unit)
val iter : action:('T -> unit) -> list:'T list -> unit

Full name: Microsoft.FSharp.Collections.List.iter
val d : System.IDisposable
System.IDisposable.Dispose() : unit
val subscribe : (formula -> seq<int * int> -> unit)
val addresses : seq<int * int>
val remember : (System.IDisposable -> unit)
val x : System.IDisposable
val cell' : Cell
property Cell.Updated: IEvent<int>
module Observable

from Microsoft.FSharp.Control
val subscribe : callback:('T -> unit) -> source:System.IObservable<'T> -> System.IDisposable

Full name: Microsoft.FSharp.Control.Observable.subscribe
property Sheet.MaxGeneration: int
Multiple items
member Cell.Data : string with set

Full name: Script.Cell.Data

--------------------
namespace Microsoft.FSharp.Data
val set : elements:seq<'T> -> Set<'T> (requires comparison)

Full name: Microsoft.FSharp.Core.ExtraTopLevelOperators.set
val isFormula : bool
val newFormula : formula option
module Option

from Microsoft.FSharp.Core
val iter : action:('T -> unit) -> option:'T option -> unit

Full name: Microsoft.FSharp.Core.Option.iter
member Cell.Value : string

Full name: Script.Cell.Value
member Cell.Updated : IEvent<int>

Full name: Script.Cell.Updated
property Event.Publish: IEvent<int>
val colCount : int
val cells : Cell []
val init : count:int -> initializer:(int -> 'T) -> 'T []

Full name: Microsoft.FSharp.Collections.Array.init
val i : int
member Row.Cells : Cell []

Full name: Script.Row.Cells
member Row.Index : int

Full name: Script.Row.Index
val rowCount : int
val cols : string []
val rows : Row []
member Sheet.Columns : string []

Full name: Script.Sheet.Columns
member Sheet.Rows : Row []

Full name: Script.Sheet.Rows
member Sheet.MaxGeneration : int

Full name: Script.Sheet.MaxGeneration
val propertyChanged : Event<PropertyChangedEventHandler,PropertyChangedEventArgs>
type PropertyChangedEventHandler =
  delegate of obj * PropertyChangedEventArgs -> unit

Full name: System.ComponentModel.PropertyChangedEventHandler
Multiple items
type PropertyChangedEventArgs =
  inherit EventArgs
  new : propertyName:string -> PropertyChangedEventArgs
  member PropertyName : string

Full name: System.ComponentModel.PropertyChangedEventArgs

--------------------
PropertyChangedEventArgs(propertyName: string) : unit
val this : ObservableObject
member ObservableObject.Notify : name:string -> unit

Full name: Script.ObservableObject.Notify
val name : string
member Event.Trigger : sender:obj * args:'Args -> unit
type INotifyPropertyChanged =
  event PropertyChanged : PropertyChangedEventHandler

Full name: System.ComponentModel.INotifyPropertyChanged
Multiple items
type CLIEventAttribute =
  inherit Attribute
  new : unit -> CLIEventAttribute

Full name: Microsoft.FSharp.Core.CLIEventAttribute

--------------------
new : unit -> CLIEventAttribute
override ObservableObject.PropertyChanged : IEvent<PropertyChangedEventHandler,PropertyChangedEventArgs>

Full name: Script.ObservableObject.PropertyChanged
property Event.Publish: IEvent<PropertyChangedEventHandler,PropertyChangedEventArgs>
namespace System.Collections
namespace System.Windows
Multiple items
namespace System.Data

--------------------
namespace Microsoft.FSharp.Data
namespace System.Media
Multiple items
type DataGrid =
  inherit obj
  new : headings:seq<'a> * items:IEnumerable * cellFactory:(int * int -> 'b) -> DataGrid

Full name: Script.DataGrid

--------------------
new : headings:seq<'a> * items:IEnumerable * cellFactory:(int * int -> 'b) -> DataGrid
val headings : seq<'a>
Multiple items
val seq : sequence:seq<'T> -> seq<'T>

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

--------------------
type seq<'T> = Generic.IEnumerable<'T>

Full name: Microsoft.FSharp.Collections.seq<_>
val items : IEnumerable
type IEnumerable =
  member GetEnumerator : unit -> IEnumerator

Full name: System.Collections.IEnumerable
val cellFactory : (int * int -> 'a)
val grid : DataGrid
val ignore : value:'T -> unit

Full name: Microsoft.FSharp.Core.Operators.ignore
module Seq

from Microsoft.FSharp.Collections
val iteri : action:(int -> 'T -> unit) -> source:seq<'T> -> unit

Full name: Microsoft.FSharp.Collections.Seq.iteri
val length : source:seq<'T> -> int

Full name: Microsoft.FSharp.Collections.Seq.length
Multiple items
type View =
  inherit obj
  new : unit -> View

Full name: Script.View

--------------------
new : unit -> View
val sprintf : format:Printf.StringFormat<'T> -> 'T

Full name: Microsoft.FSharp.Core.ExtraTopLevelOperators.sprintf
val subscribe : callback:('T -> unit) -> source:IObservable<'T> -> IDisposable

Full name: Microsoft.FSharp.Control.Observable.subscribe
val filter : predicate:('T -> bool) -> source:IObservable<'T> -> IObservable<'T>

Full name: Microsoft.FSharp.Control.Observable.filter

More information

Link:http://fssnip.net/4v
Posted:12 years ago
Author:Phillip Trelford
Tags: spreadsheet , silverlight , parser , datagrid