2 people like it.

13 - Trig Functions Display

  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: 
314: 
315: 
316: 
317: 
318: 
319: 
320: 
321: 
322: 
323: 
324: 
325: 
326: 
327: 
328: 
329: 
330: 
331: 
332: 
333: 
334: 
335: 
336: 
337: 
338: 
339: 
340: 
341: 
342: 
343: 
344: 
345: 
346: 
347: 
348: 
349: 
350: 
351: 
352: 
353: 
354: 
355: 
356: 
357: 
358: 
359: 
360: 
361: 
362: 
363: 
364: 
365: 
366: 
367: 
368: 
369: 
370: 
371: 
372: 
373: 
374: 
375: 
376: 
377: 
378: 
379: 
380: 
//
// Welcome to Try F#. Type your F# script in this window. To run code use:
//
// * Ctrl-Enter or the Run button to send selected text to F# Interactive.
//   If no text is selected the entire script will be sent.
//
// * Ctrl-Shift-Enter to send the current line to F# Interactive.
//
// Part 1. - Complex Basics
// Part 2. - Graphics Basics
// Part 3. - Drawing Complex Sets

// Import Try F# compatibility (enable for Visual Studio)
//#load "Offline.fsx"

////////////////////////////////////////
// Part 1. - Complex Basics

// Define complex type with some operators
type Complex =
    { Re : float;
      Im : float }
    static member (+) (z1, z2) = { Re = z1.Re + z2.Re; Im = z1.Im + z2.Im }
    static member (+) (r1, z2) = { Re = r1 + z2.Re;    Im = z2.Im }
    static member (+) (z1, r2) = { Re = z1.Re + r2;    Im = z1.Im }
    static member (-) (z1, z2) = { Re = z1.Re - z2.Re; Im = z1.Im - z2.Im }
    static member (-) (r1, z2) = { Re = r1 - z2.Re;    Im = - z2.Im }
    static member (-) (z1, r2) = { Re = z1.Re - r2;    Im = z1.Im}
    static member (*) (z1, z2) = { Re = ((z1.Re * z2.Re) - (z1.Im * z2.Im)); Im = ((z1.Re * z2.Im) + (z1.Im * z2.Re)) }
    static member (*) (r1, z2) = { Re = r1 * z2.Re;    Im = r1 * z2.Im }
    static member (*) (z1, r2) = { Re = z1.Re * r2;    Im = z1.Im * r2 }
    static member (/) (z1, z2) = 
        let z2_conj = {Re = z2.Re; Im = -z2.Im}
        let den = (z2 * z2_conj).Re
        let num = z1 * z2_conj
        { Re = num.Re / den; Im = num.Im / den }
    static member (/) ((r1:float), z2) = 
        let z2_conj = {Re = z2.Re; Im = -z2.Im}
        let den = (z2 * z2_conj).Re
        let num = r1 * z2_conj
        { Re = num.Re / den; Im = num.Im / den }
    static member (/) (z1, r2) = {Re = z1.Re / r2; Im = z1.Im / r2}
    static member (~-) z = { Re = -z.Re; Im = -z.Im };;

// .. and printing
let print z = printfn "%.3f%+.3fi" z.Re z.Im;;
let sprint z = sprintf "%.3f%+.3fi" z.Re z.Im;;

// .. and the conjugate
let conj z = 
    { Re = z.Re; 
      Im = -z.Im };;

// ... and the modulus (absolute value)
let abs z =
    sqrt (z.Re * z.Re + z.Im * z.Im);;

// ... and the argument (actually this is the principal value of the argument (Arg)
let arg z = 
    atan2 z.Im z.Re;;

// Polar form of complex number
type ComplexPolar = 
    { Mag : float;
      Arg : float };;

// ... with conversion to and from the polar form
let toPolar z = 
    { Mag = abs z;
      Arg = arg z };;

let fromPolar zp = 
    { Re = zp.Mag * (cos zp.Arg);
      Im = zp.Mag * (sin zp.Arg) };;

// ... and define printing of the polar form
let printp zp = 
    printfn "%.1f(cos %.3f + i sin %.3f)" zp.Mag zp.Arg zp.Arg;;

// Get list of angles used for roots
let rootAngles theta n =
    let pi = atan2 0.0 -1.0
    let kList = [0 .. (n-1)]
    let angles = List.map (fun k -> (theta + 2.0 * (float k) * pi) / (float n)) kList
    let anglesModPi = List.map (fun angle -> angle % (2.0 * pi)) angles
    let anglesSorted = List.sort anglesModPi
    anglesSorted;;

// Find roots
let nthRootsPolar n z = 
    let zp = toPolar z
    let angles = rootAngles zp.Arg n
    let mag = System.Math.Pow(zp.Mag, (1.0 / (float n)))
    List.map (fun angle -> {Mag = mag; Arg = angle}) angles;;

// ... one way to convert a list from polar
let fromPolarList polars = 
    List.map fromPolar polars;;

// ... another way...
// send (pipe) the output from the nthRootsPolar 
// to a list conversion
let nthRoots n z = 
    nthRootsPolar n z
    |> List.map fromPolar;;


// Define some standard complex numbers
let i = {Re=0.0; Im = 1.0}
let pi = atan2 0.0 -1.0

////////////////////////////////////////
// Part 2. - Graphics Basics
open System
open System.Windows
open System.Windows.Controls
open System.Windows.Media
open System.Windows.Media.Imaging
open Microsoft.TryFSharp

type Graphic = 
    { Canvas : Canvas;
      Size : float;
      Scale : float}
 
let makeGraphic (canvas : Canvas) size =
    let initSize = 250.0
    canvas.HorizontalAlignment <- HorizontalAlignment.Center
    canvas.VerticalAlignment <- VerticalAlignment.Center
    let scale = ScaleTransform()
    scale.ScaleX <- initSize / size
    scale.ScaleY <- -initSize / size
    canvas.RenderTransform <- scale
    let border = Border()
    border.Background <- SolidColorBrush(Colors.Green)
    //border.HorizontalAlignment <- HorizontalAlignment.Center
    //border.VerticalAlignment <- VerticalAlignment.Center
    Canvas.SetLeft(border, -size)
    Canvas.SetTop(border, -size)
    border.Height <- 2.0 * size
    border.Width <- 2.0 * size
    canvas.Children.Add border |> ignore

    let innerCanvas = Canvas()
    innerCanvas.HorizontalAlignment <- HorizontalAlignment.Center
    innerCanvas.VerticalAlignment <- VerticalAlignment.Center
    border.Child <- innerCanvas

    let display = TextBlock()
    display.Text <- "Hello"
    innerCanvas.Children.Add display |> ignore
    let scale = ScaleTransform()
    scale.ScaleX <- 1.0
    scale.ScaleY <- -1.0
    display.RenderTransform <- scale
    display.FontSize <- 10.0 * 2.0 * size / initSize

    Canvas.SetLeft(display, -size)
    Canvas.SetTop(display, size)
    
    let mouseMove (x,y) = 
        display.Text <- sprintf "(%.3f, %.3f)" x y
    border.MouseMove.AddHandler (fun sender mouseArgs -> 
        let p = mouseArgs.GetPosition(innerCanvas)
        mouseMove (p.X, p.Y))
    { Canvas = innerCanvas; Size = size; Scale = 2.0 * size / initSize}

let drawLine graphic brush (x1, y1) (x2, y2) = 
    let line = Shapes.Line()
    line.X1 <- x1
    line.Y1 <- y1
    line.X2 <- x2
    line.Y2 <- y2
    line.Stroke <- brush
    line.StrokeThickness <- 1.0 * graphic.Scale
    graphic.Canvas.Children.Add line |> ignore

let drawDot graphic fill (x, y) = 
    let dot = Shapes.Ellipse()
    dot.HorizontalAlignment <- HorizontalAlignment.Center
    dot.VerticalAlignment <- VerticalAlignment.Center
    dot.Height <- 2.0 * graphic.Scale
    dot.Width <- dot.Height
    dot.Fill <- fill
    dot.StrokeThickness <- 0.0
    Canvas.SetLeft(dot, x - dot.Width / 2.0)
    Canvas.SetTop(dot, y - dot.Width / 2.0)
    graphic.Canvas.Children.Add dot |> ignore

let drawDots graphic fill positions = 
    let grp = GeometryGroup()
    grp.FillRule <- FillRule.Nonzero
    let addDot (x,y) = 
        let dot = EllipseGeometry()
        dot.Center <- Point(x,y)
        dot.RadiusX <- 0.01
        dot.RadiusY <- dot.RadiusX
        grp.Children.Add dot
    List.iter addDot positions
    let shape = Shapes.Path()
    shape.Data <- grp
    shape.Fill <- fill
    shape.StrokeThickness <- 0.0
    shape.HorizontalAlignment <- HorizontalAlignment.Center
    shape.VerticalAlignment <- VerticalAlignment.Center
    //Canvas.SetLeft(dot, x - dot.Width / 2.0)
    //Canvas.SetTop(dot, y - dot.Width / 2.0)
    graphic.Canvas.Children.Add shape |> ignore

let drawText graphic (x, y) text = 
    let tb = TextBlock()
    //tb.HorizontalAlignment <- HorizontalAlignment.Center
    //tb.VerticalAlignment <- VerticalAlignment.Center
    tb.Text <- text
    let scale = ScaleTransform()
    scale.ScaleX <- 1.0
    scale.ScaleY <- -1.0
    tb.RenderTransform <- scale
    tb.FontSize <- 10.0 * graphic.Scale
    Canvas.SetLeft(tb, x)
    Canvas.SetTop(tb, y)
    graphic.Canvas.Children.Add tb |> ignore

let drawAxes graphic tickUnit =
    let darkGray = SolidColorBrush(Colors.DarkGray)
    drawLine graphic darkGray (-graphic.Size, 0.0) (graphic.Size, 0.0)
    drawLine graphic darkGray (0.0, -graphic.Size) (0.0, graphic.Size)
    let ticks = [0.0 .. tickUnit .. graphic.Size] @ [-tickUnit .. -tickUnit .. -graphic.Size]
    let tickSize = tickUnit / 10.0
    List.iter (fun x -> drawLine graphic darkGray (x, -tickSize) (x, tickSize)) ticks
    List.iter (fun y -> drawLine graphic darkGray (-tickSize, y) (tickSize, y)) ticks
    
let drawBitmap graphic colorFunc =
    let getCoordinates =
        let step = graphic.Size * 2.0 / 100.0
        [ for x in -graphic.Size .. step .. graphic.Size do
            for y in -graphic.Size .. step .. graphic.Size do
                yield (x, y) ]
    List.iter (fun p -> drawDot graphic (colorFunc p) p) getCoordinates

let drawTestDot graphic fill =
    drawDot graphic fill (-graphic.Size, graphic.Size)

//
//let drawBitmap graphic colorFunc =
//    let setPixel (bm:WriteableBitmap) row col (alpha : byte) (r : byte) (g : byte) (b : byte) = 
//        let idx = row * bm.PixelWidth + col
//        let r1 = byte ((uint16 r) * (uint16 alpha) / (uint16 255))
//        let g1 = byte ((uint16 g) * (uint16 alpha) / (uint16 255))
//        let b1 = byte ((uint16 b) * (uint16 alpha) / (uint16 255))
//        Array.set bm.Pixels idx (((((int alpha) <<< 24) ||| ( int r1 <<< 16)) ||| (int g1 <<< 8)) ||| int b1)
//    let draw (bm:WriteableBitmap) x =
//        for i = 0 to 499 do
//            for j = 0 to 499 do
//                setPixel bm i j 255uy (byte i) (byte j) (200uy + x)
//        bm.Invalidate()
//    let bm = new WriteableBitmap(500, 500, 96.0, 96.0, PixelFormats.Bgr32, null )
//    let image = new Image()
//    image.Source <- bm
//    graphic.Canvas.Children.Add image


////////////////////////////////////////
// Part 3. - Mouse display for Complex Functions

let makeFunctionGraphic (canvas : Canvas) size f =
    let initSize = 220.0
    let scale = 2.0 * size / initSize

    // Set the containing canvas to have the right positioning and scaling and y-axis orientation
    canvas.HorizontalAlignment <- HorizontalAlignment.Center
    canvas.VerticalAlignment <- VerticalAlignment.Center
    let scaleTf = ScaleTransform()
    scaleTf.ScaleX <- initSize / size
    scaleTf.ScaleY <- -initSize / size
    canvas.RenderTransform <- scaleTf

    // Add the stack panel which will contain our innner canvases
    let stackPanel = StackPanel()
    stackPanel.Orientation <- Orientation.Horizontal
    Canvas.SetLeft(stackPanel, -size*2.0)
    Canvas.SetTop(stackPanel, -size)
    canvas.Children.Add stackPanel |> ignore

    // An inner canvas needs a border to receive mouse events
    let addCanvas (stackPanel : StackPanel) background =
        let border = Border()
        border.Background <- background
        border.Height <- 2.0 * size
        border.Width <- 2.0 * size
        border.Margin <- Thickness(0.1, 0.0, 0.1, 0.0)
        let canvas = Canvas()
        canvas.HorizontalAlignment <- HorizontalAlignment.Center
        canvas.VerticalAlignment <- VerticalAlignment.Center
        border.Child <- canvas
        stackPanel.Children.Add border |> ignore
        (canvas, border)

    let leftCanvasBorder = addCanvas stackPanel (SolidColorBrush(Colors.LightGray))
    let rightCanvasBorder = addCanvas stackPanel (SolidColorBrush(Colors.White))

    let leftCanvas = fst leftCanvasBorder
    let rightCanvas = fst rightCanvasBorder

    let addTextBlock (canvas : Canvas) =
        let tb = TextBlock()
        let scaleTransform = ScaleTransform()
        scaleTransform.ScaleX <- 1.0
        scaleTransform.ScaleY <- -1.0
        tb.RenderTransform <- scaleTransform
        tb.FontSize <- 10.0 * scale
        Canvas.SetLeft(tb, -size)
        Canvas.SetTop(tb, size)
        canvas.Children.Add tb |> ignore
        tb

    let leftText = addTextBlock leftCanvas
    let rightText = addTextBlock rightCanvas

    let addDot (canvas:Canvas) fill =
        let dot = Shapes.Ellipse()
        dot.Height <- 5.0 * scale
        dot.Width <- dot.Height
        dot.Fill <- fill
        canvas.Children.Add dot |> ignore
        dot
    
    let leftDot = addDot leftCanvas (SolidColorBrush(Colors.Red))
    let rightDot = addDot rightCanvas (SolidColorBrush(Colors.Green))

    let mouseMove (x,y) = 
        let z = {Re=x; Im=y}
        let fz = f z
        leftText.Text <- sprint z
        rightText.Text <- sprint fz
        Canvas.SetLeft(leftDot, x - leftDot.Width / 2.0)
        Canvas.SetTop(leftDot, y - leftDot.Width / 2.0)
        Canvas.SetLeft(rightDot, fz.Re - leftDot.Width / 2.0)
        Canvas.SetTop(rightDot, fz.Im - leftDot.Width / 2.0)
    
    let leftBorder = snd leftCanvasBorder
    leftBorder.MouseMove.AddHandler 
        (fun sender mouseArgs -> 
            let p = mouseArgs.GetPosition(leftCanvas)
            mouseMove (p.X, p.Y))

    let leftGraphic = { Canvas = leftCanvas; Size = size; Scale = scale}
    let rightGraphic = { Canvas = rightCanvas; Size = size; Scale = scale}

    drawAxes leftGraphic 1.0
    drawAxes rightGraphic 1.0
    ()

let show f () =   
    App.Dispatch (fun() -> 
        App.Console.ClearCanvas ()
        makeFunctionGraphic App.Console.Canvas 10.0 f
        App.Console.CanvasPosition <- CanvasPosition.Alone)

////////////////////////////////////
// Easy to change below here

let f1 z = z
let f2 (z:Complex) = 2.0 * z
let f3 z = i * z
let f4 (z:Complex) = z * z
let f5 (z:Complex) = 1.0 / z
let exp z = 
    {Re = (Math.Exp z.Re) * (Math.Cos z.Im); 
     Im = (Math.Exp z.Re) * (Math.Sin z.Im)}
let sin z =
    1.0 / (2.0 * i) * (exp (i * z) - exp (-i*z))
let cos z =
    1.0 / 2.0  * (exp (i * z) + exp (-i*z))
let sinh z = 
    1.0 / 2.0  * (exp z - exp -z)
let cosh z = 
    1.0 / 2.0  * (exp z + exp -z)

show sin ()
Complex.Re: float
Multiple items
val float : value:'T -> float (requires member op_Explicit)

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

--------------------
type float = System.Double

Full name: Microsoft.FSharp.Core.float

--------------------
type float<'Measure> = float

Full name: Microsoft.FSharp.Core.float<_>
Complex.Im: float
val z1 : Complex
val z2 : Complex
val r1 : float
val r2 : float
val z2_conj : Complex
val den : float
val num : Complex
val z : Complex
val print : z:Complex -> unit

Full name: Script.print
val printfn : format:Printf.TextWriterFormat<'T> -> 'T

Full name: Microsoft.FSharp.Core.ExtraTopLevelOperators.printfn
val sprint : z:Complex -> string

Full name: Script.sprint
val sprintf : format:Printf.StringFormat<'T> -> 'T

Full name: Microsoft.FSharp.Core.ExtraTopLevelOperators.sprintf
val conj : z:Complex -> Complex

Full name: Script.conj
val abs : z:Complex -> float

Full name: Script.abs
val sqrt : value:'T -> 'U (requires member Sqrt)

Full name: Microsoft.FSharp.Core.Operators.sqrt
val arg : z:Complex -> float

Full name: Script.arg
val atan2 : y:'T1 -> x:'T1 -> 'T2 (requires member Atan2)

Full name: Microsoft.FSharp.Core.Operators.atan2
type ComplexPolar =
  {Mag: float;
   Arg: float;}

Full name: Script.ComplexPolar
ComplexPolar.Mag: float
ComplexPolar.Arg: float
val toPolar : z:Complex -> ComplexPolar

Full name: Script.toPolar
val fromPolar : zp:ComplexPolar -> Complex

Full name: Script.fromPolar
val zp : ComplexPolar
val cos : value:'T -> 'T (requires member Cos)

Full name: Microsoft.FSharp.Core.Operators.cos
val sin : value:'T -> 'T (requires member Sin)

Full name: Microsoft.FSharp.Core.Operators.sin
val printp : zp:ComplexPolar -> unit

Full name: Script.printp
val rootAngles : theta:float -> n:int -> float list

Full name: Script.rootAngles
val theta : float
val n : int
val pi : float
val kList : int list
val angles : float list
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 k : int
val anglesModPi : float list
val angle : float
val anglesSorted : float list
val sort : list:'T list -> 'T list (requires comparison)

Full name: Microsoft.FSharp.Collections.List.sort
val nthRootsPolar : n:int -> z:Complex -> ComplexPolar list

Full name: Script.nthRootsPolar
val mag : float
namespace System
type Math =
  static val PI : float
  static val E : float
  static member Abs : value:sbyte -> sbyte + 6 overloads
  static member Acos : d:float -> float
  static member Asin : d:float -> float
  static member Atan : d:float -> float
  static member Atan2 : y:float * x:float -> float
  static member BigMul : a:int * b:int -> int64
  static member Ceiling : d:decimal -> decimal + 1 overload
  static member Cos : d:float -> float
  ...

Full name: System.Math
System.Math.Pow(x: float, y: float) : float
val fromPolarList : polars:ComplexPolar list -> Complex list

Full name: Script.fromPolarList
val polars : ComplexPolar list
val nthRoots : n:int -> z:Complex -> Complex list

Full name: Script.nthRoots
val i : Complex

Full name: Script.i
val pi : float

Full name: Script.pi
namespace System.Windows
namespace System.Media
namespace Microsoft
type Graphic =
  {Canvas: obj;
   Size: float;
   Scale: float;}

Full name: Script.Graphic
Graphic.Canvas: obj
Graphic.Size: float
Multiple items
val float : value:'T -> float (requires member op_Explicit)

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

--------------------
type float = Double

Full name: Microsoft.FSharp.Core.float

--------------------
type float<'Measure> = float

Full name: Microsoft.FSharp.Core.float<_>
Graphic.Scale: float
val makeGraphic : canvas:'a -> size:float -> Graphic

Full name: Script.makeGraphic
val canvas : 'a
val size : float
val initSize : float
val scale : obj
val border : obj
val ignore : value:'T -> unit

Full name: Microsoft.FSharp.Core.Operators.ignore
val innerCanvas : obj
val display : obj
namespace System.Text
val mouseMove : ('b * 'c -> 'd)
val x : 'b
val y : 'c
val drawLine : graphic:Graphic -> brush:'a -> x1:'b * y1:'c -> x2:'d * y2:'e -> unit

Full name: Script.drawLine
val graphic : Graphic
val brush : 'a
val x1 : 'b
val y1 : 'c
val x2 : 'd
val y2 : 'e
val line : obj
val drawDot : graphic:Graphic -> fill:'a -> x:'b * y:'c -> unit

Full name: Script.drawDot
val fill : 'a
val dot : obj
val drawDots : graphic:Graphic -> fill:'a -> positions:('b * 'c) list -> unit

Full name: Script.drawDots
val positions : ('b * 'c) list
val grp : obj
val addDot : ('d * 'e -> 'f)
val x : 'd
val y : 'e
val iter : action:('T -> unit) -> list:'T list -> unit

Full name: Microsoft.FSharp.Collections.List.iter
val shape : obj
Multiple items
namespace System.Data

--------------------
namespace Microsoft.FSharp.Data
val drawText : graphic:Graphic -> x:'a * y:'b -> text:'c -> unit

Full name: Script.drawText
val x : 'a
val y : 'b
val text : 'c
val tb : obj
val drawAxes : graphic:Graphic -> tickUnit:float -> unit

Full name: Script.drawAxes
val tickUnit : float
val darkGray : obj
val ticks : float list
val tickSize : float
val x : float
val y : float
val drawBitmap : graphic:Graphic -> colorFunc:(float * float -> 'a) -> unit

Full name: Script.drawBitmap
val colorFunc : (float * float -> 'a)
val getCoordinates : (float * float) list
val step : float
val p : float * float
val drawTestDot : graphic:Graphic -> fill:'a -> unit

Full name: Script.drawTestDot
val makeFunctionGraphic : canvas:'a -> size:float -> f:(Complex -> 'b) -> unit

Full name: Script.makeFunctionGraphic
val f : (Complex -> 'b)
val scale : float
val scaleTf : obj
val stackPanel : obj
val addCanvas : ('c -> 'd -> 'e * 'f)
val stackPanel : 'c
val background : 'd
val border : 'f
val canvas : 'e
val leftCanvasBorder : obj * obj
val rightCanvasBorder : obj * obj
val leftCanvas : obj
val fst : tuple:('T1 * 'T2) -> 'T1

Full name: Microsoft.FSharp.Core.Operators.fst
val rightCanvas : obj
val addTextBlock : ('c -> 'd)
val canvas : 'c
val tb : 'd
val scaleTransform : obj
val leftText : obj
val rightText : obj
val addDot : ('c -> 'd -> 'e)
val fill : 'd
val dot : 'e
val leftDot : obj
val rightDot : obj
val mouseMove : (float * float -> 'c)
val fz : 'b
val leftBorder : obj
val snd : tuple:('T1 * 'T2) -> 'T2

Full name: Microsoft.FSharp.Core.Operators.snd
val leftGraphic : Graphic
val rightGraphic : Graphic
val show : f:'a -> unit -> 'b

Full name: Script.show
val f : 'a
type Console =
  static member BackgroundColor : ConsoleColor with get, set
  static member Beep : unit -> unit + 1 overload
  static member BufferHeight : int with get, set
  static member BufferWidth : int with get, set
  static member CapsLock : bool
  static member Clear : unit -> unit
  static member CursorLeft : int with get, set
  static member CursorSize : int with get, set
  static member CursorTop : int with get, set
  static member CursorVisible : bool with get, set
  ...

Full name: System.Console
val f1 : z:'a -> 'a

Full name: Script.f1
val z : 'a
val f2 : z:Complex -> Complex

Full name: Script.f2
type Complex =
  {Re: float;
   Im: float;}
  static member ( + ) : z1:Complex * z2:Complex -> Complex
  static member ( + ) : r1:float * z2:Complex -> Complex
  static member ( + ) : z1:Complex * r2:float -> Complex
  static member ( / ) : z1:Complex * z2:Complex -> Complex
  static member ( / ) : r1:float * z2:Complex -> Complex
  static member ( / ) : z1:Complex * r2:float -> Complex
  static member ( * ) : z1:Complex * z2:Complex -> Complex
  static member ( * ) : r1:float * z2:Complex -> Complex
  static member ( * ) : z1:Complex * r2:float -> Complex
  static member ( - ) : z1:Complex * z2:Complex -> Complex
  static member ( - ) : r1:float * z2:Complex -> Complex
  static member ( - ) : z1:Complex * r2:float -> Complex
  static member ( ~- ) : z:Complex -> Complex

Full name: Script.Complex
val f3 : z:Complex -> Complex

Full name: Script.f3
val f4 : z:Complex -> Complex

Full name: Script.f4
val f5 : z:Complex -> Complex

Full name: Script.f5
val exp : z:Complex -> Complex

Full name: Script.exp
Math.Exp(d: float) : float
Math.Cos(d: float) : float
Math.Sin(a: float) : float
val sin : z:Complex -> Complex

Full name: Script.sin
val cos : z:Complex -> Complex

Full name: Script.cos
val sinh : z:Complex -> Complex

Full name: Script.sinh
val cosh : z:Complex -> Complex

Full name: Script.cosh
Raw view Test code New version

More information

Link:http://fssnip.net/78
Posted:14 years ago
Author:
Tags: