1 people like it.

Sankey Diagram extension to Plotly.NET

Extension of Plotly.NET to draw Sankey diagrams by leveraging the underlying capability offered by Plotly.js

  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: 
module PlotlyExts
open FSharp.Plotly
open Trace

type Node = 
    {
        Label           : string
        Groups          : string[] option
        XRank           : int option
        YRank           : int option
        Color           : obj option
        LineColor       : obj option
        LineWidth       : float option
    }
    with
    static member Create(label,?groups,?xRank,?yRank,?color,?lineColor,?lineWidth) = 
        {
            Label           = label
            Groups          = groups
            XRank           = xRank
            YRank           = yRank
            Color           = color
            LineColor       = lineColor
            LineWidth       = lineWidth
        }

type Link = 
    {
        Source          : Node
        Target          : Node
        Value           : float option
        Label           : string option
        Color           : obj option
        LineColor       : obj option
        LineWidth       : float option

    }
    with
    static member Create(src,tgt,?value,?label,?color,?lineColor,?lineWidth) = 
        {
            Source          = src
            Target          = tgt
            Value           = value
            Label           = label
            Color           = color
            LineColor       = lineColor
            LineWidth   = lineWidth
        }


module Trace =
    let initSankey (applyStyle:Trace->Trace) = 
        FSharp.Plotly.Trace("sankey") |> applyStyle

type TraceStyle with
    static member Sankey
        (
            nodes:Node seq, 
            links:Link seq, 
            ?nodePadding:float,
            ?nodeThicknes:float,
            ?nodeColor:obj,
            ?nodeLineColor:obj,
            ?nodeLineWidth:float,
            ?linkColor:obj, 
            ?linkLineColor: obj,
            ?linkLineWidth:float
        ) =
        (fun (trace:('T :> Trace)) ->
            let nonUniqueLabels = nodes |> Seq.countBy (fun x->x.Label) |> Seq.filter (fun (_,c) -> c > 1)
            if  nonUniqueLabels |> Seq.length > 0 then failwithf "duplicated label names %A" (nonUniqueLabels |> Seq.map fst)
            let lblMap = nodes |> Seq.mapi(fun i x->x.Label,i) |> Map.ofSeq // give each node an index

            let link = 
                let linkClrs =  
                    links 
                    |> Seq.map (fun x->x.Color)
                    |> Seq.map (function Some x -> x | None -> linkColor |> Option.defaultValue null)
                    |> fun xs -> if xs |> Seq.exists (fun x-> x <> null) then  xs |> Seq.toArray |> Some else None

                let linkLineClrs =  
                    links 
                    |> Seq.map (fun x->x.LineColor)
                    |> Seq.map (function Some x -> x | None -> linkLineColor |> Option.defaultValue null)
                    |> fun xs -> if xs |> Seq.exists (fun x-> x <> null) then  xs |> Seq.toArray |> Some else None

                let linkLineWidths =  
                    links 
                    |> Seq.map (fun x->x.LineWidth)
                    |> Seq.map (function Some x -> x | None -> linkLineWidth |> Option.defaultValue 0.5)
                    |> fun xs -> if xs |> Seq.exists (fun x-> x <> 0.5) then  xs |> Seq.toArray |> Some else None

                let values = 
                    links 
                    |> Seq.map (fun x->x.Value)
                    |> fun xs -> if xs |> Seq.exists Option.isSome then 
                                    xs |> Seq.map(function Some x -> box x | None -> null) |> Seq.toArray |> Some
                                 else 
                                    None

                let line = 
                    match (linkLineClrs,linkLineWidths) with 
                    | None,None -> None 
                    | cs,ws -> 
                        let ln = new DynamicObj()
                        DynObj.setValueOpt ln "color" cs
                        DynObj.setValueOpt ln "width" ws
                        Some ln

                let l = new DynamicObj()
                DynObj.setValue     l "source" (links |> Seq.map (fun x->lblMap.[x.Source.Label]))
                DynObj.setValue     l "target" (links |> Seq.map (fun x->lblMap.[x.Target.Label]))
                DynObj.setValueOpt  l "color"  linkClrs
                DynObj.setValueOpt  l "value"  values
                DynObj.setValueOpt  l "line"   line

                l

            let node = 
                let groups = 
                    nodes 
                    |> Seq.collect(fun x->x.Groups |> Option.defaultValue [||] |> Array.map (fun g-> g,lblMap.[x.Label]))
                    |> Seq.groupBy fst
                    |> Seq.map (fun (g,gs) -> gs |> Seq.map snd)
                    |> fun xs -> if Seq.isEmpty xs then Some (xs |> Seq.map Seq.toArray |> Seq.toArray) else None

                let xRanks =
                    nodes
                    |> Seq.map (fun x -> x.XRank |> Option.map box |> Option.defaultValue null)
                    |> fun xs -> if xs |> Seq.exists (fun x-> x <> null) then  xs |> Seq.toArray |> Some else None

                let yRanks =
                    nodes
                    |> Seq.map (fun x -> x.YRank |> Option.map box |> Option.defaultValue null)
                    |> fun xs -> if xs |> Seq.exists (fun x-> x <> null) then  xs |> Seq.toArray |> Some else None

                let nodeClrs =  
                    nodes 
                    |> Seq.map (fun x->x.Color)
                    |> Seq.map (function Some x -> x | None -> nodeColor |> Option.defaultValue null)
                    |> fun xs -> if xs |> Seq.exists (fun x-> x <> null) then  xs |> Seq.toArray |> Some else None

                let nodeLineClrs =  
                    nodes 
                    |> Seq.map (fun x->x.LineColor)
                    |> Seq.map (function Some x -> x | None -> nodeLineColor |> Option.defaultValue null)
                    |> fun xs -> if xs |> Seq.exists (fun x-> x <> null) then  xs |> Seq.toArray |> Some else None

                let nodeLineWidths =  
                    nodes 
                    |> Seq.map (fun x->x.LineWidth)
                    |> Seq.map (function Some x -> x | None -> nodeLineWidth |> Option.defaultValue 0.5)
                    |> fun xs -> if xs |> Seq.exists (fun x-> x <> 0.5) then  xs |> Seq.toArray |> Some else None

                let line = 
                    match (nodeLineClrs,nodeLineWidths) with 
                    | None,None -> None 
                    | cs,ws -> 
                        let ln = new DynamicObj()
                        DynObj.setValueOpt ln "color" cs
                        DynObj.setValueOpt ln "width" ws
                        Some ln

                let n = new DynamicObj()
                DynObj.setValue    n "label" (nodes |> Seq.map (fun  x->x.Label)) 
                DynObj.setValueOpt n "groups" groups
                DynObj.setValueOpt n "pad" nodePadding
                DynObj.setValueOpt n "thickness" nodeThicknes
                DynObj.setValueOpt n "x" xRanks
                DynObj.setValueOpt n "y" yRanks
                DynObj.setValueOpt n "color" nodeClrs
                DynObj.setValueOpt n "line" line
                DynObj.setValueOpt n "color" nodeClrs
                n
            
            DynObj.setValue trace "node" node
            DynObj.setValue trace "link" link

            trace
        )

type Chart with
    static member Sankey
        (
            nodes:Node seq, 
            links:Link seq, 
            ?nodePadding:float,
            ?nodeThicknes:float,
            ?nodeColor:obj,
            ?nodeLineColor:obj,
            ?nodeLineWidth:float,
            ?linkColor:obj, 
            ?linkLineColor: obj,
            ?linkLineWidth:float
        ) =
        Trace.initSankey(TraceStyle.Sankey
            (
                nodes, 
                links, 
                ?nodePadding=nodePadding,
                ?nodeThicknes=nodeThicknes,
                ?nodeColor=nodeColor,
                ?nodeLineColor=nodeLineColor,
                ?nodeLineWidth=nodeLineWidth,
                ?linkColor=linkColor,
                ?linkLineColor=linkLineColor,
                ?linkLineWidth=linkLineWidth
            ))
        |> GenericChart.ofTraceObject
   

(*
#load "PlotlyExts.fs"
open FSharp.Plotly
open PlotlyExts
let testSankey() =
    let n1 = Node.Create("a",color="Black")
    let n2 = Node.Create("b",color="Red")
    let n3 = Node.Create("c",color="Purple")
    let n4 = Node.Create("d",color="Green")
    let n5 = Node.Create("e",color="Orange")
    let link1 = Link.Create(n1,n2,value=1.0)
    let link2 = Link.Create(n2,n3,value=2.0)
    let link3 = Link.Create(n1,n5,value=1.3)
    let link4 = Link.Create(n4,n5,value=1.5)
    let link5 = Link.Create(n3,n5,value=0.5)
    Chart.Sankey([n1;n2;n3;n4;n5],[link1;link2;link3;link4;link5])
    |> Chart.withTitle "Sankey Sample"
    |> Chart.Show

testSankey()
*)



      
module PlotlyExts
Multiple items
namespace FSharp

--------------------
namespace Microsoft.FSharp
namespace FSharp.Plotly
Multiple items
module Trace

from FSharp.Plotly

--------------------
type Trace =
  inherit DynamicObj
  new : traceTypeName:string -> Trace
  member type : string
  member type : string with set

Full name: FSharp.Plotly.Trace

--------------------
new : traceTypeName:string -> Trace
type Node =
  {Label: string;
   Groups: string [] option;
   XRank: int option;
   YRank: int option;
   Color: obj option;
   LineColor: obj option;
   LineWidth: float option;}
  static member Create : label:string * ?groups:string [] * ?xRank:int * ?yRank:int * ?color:obj * ?lineColor:obj * ?lineWidth:float -> Node

Full name: PlotlyExts.Node
Node.Label: string
Multiple items
val string : value:'T -> string

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

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

Full name: Microsoft.FSharp.Core.string
Node.Groups: string [] option
type 'T option = Option<'T>

Full name: Microsoft.FSharp.Core.option<_>
Node.XRank: int option
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<_>
Node.YRank: int option
Node.Color: obj option
type obj = System.Object

Full name: Microsoft.FSharp.Core.obj
Node.LineColor: obj option
Node.LineWidth: float option
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<_>
static member Node.Create : label:string * ?groups:string [] * ?xRank:int * ?yRank:int * ?color:obj * ?lineColor:obj * ?lineWidth:float -> Node

Full name: PlotlyExts.Node.Create
val label : string
val groups : string [] option
val xRank : int option
val yRank : int option
val color : obj option
val lineColor : obj option
val lineWidth : float option
type Link =
  {Source: Node;
   Target: Node;
   Value: float option;
   Label: string option;
   Color: obj option;
   LineColor: obj option;
   LineWidth: float option;}
  static member Create : src:Node * tgt:Node * ?value:float * ?label:string * ?color:obj * ?lineColor:obj * ?lineWidth:float -> Link

Full name: PlotlyExts.Link
Link.Source: Node
Link.Target: Node
Link.Value: float option
Link.Label: string option
Link.Color: obj option
Link.LineColor: obj option
Link.LineWidth: float option
static member Link.Create : src:Node * tgt:Node * ?value:float * ?label:string * ?color:obj * ?lineColor:obj * ?lineWidth:float -> Link

Full name: PlotlyExts.Link.Create
val src : Node
val tgt : Node
val value : float option
val label : string option
val initSankey : applyStyle:(Trace -> Trace) -> Trace

Full name: PlotlyExts.Trace.initSankey
val applyStyle : (Trace -> Trace)
Multiple items
type TraceStyle =
  new : unit -> TraceStyle
  static member Bar : ?X:seq<#IConvertible> * ?Y:seq<#IConvertible> * ?Marker:Marker * ?R:'g * ?T:'h * ?Error_y:Error * ?Error_x:Error * ?Orientation:Orientation -> ('T -> 'T) (requires 'T :> Trace)
  static member BoxPlot : ?Y:'h * ?X:'i * ?X0:'j * ?Y0:'k * ?Whiskerwidth:'l * ?Boxpoints:Boxpoints * ?Boxmean:BoxMean * ?Jitter:'m * ?Pointpos:'n * ?Orientation:Orientation * ?Fillcolor:'o * ?xAxis:'p * ?yAxis:'q * ?Ysrc:'r * ?Xsrc:'s -> ('T -> 'T) (requires 'T :> Trace)
  static member ChoroplethMap : ?Locations:seq<string> * ?Z:seq<#IConvertible> * ?Text:seq<#IConvertible> * ?Locationmode:LocationFormat * ?Autocolorscale:bool * ?Colorscale:Colorscale * ?Colorbar:'h * ?Marker:Marker * ?Zmin:'i * ?Zmax:'j -> ('T -> 'T) (requires 'T :> Trace)
  static member Contour : ?Z:seq<#seq<'h>> * ?X:seq<#IConvertible> * ?Y:seq<#IConvertible> * ?X0:'k * ?dX:'l * ?Y0:'m * ?dY:'n * ?xType:'o * ?yType:'p * ?xAxis:'q * ?yAxis:'r * ?Zsrc:'s * ?Xsrc:'t * ?Ysrc:'a1 * ?Xgap:'a2 * ?Ygap:'a3 * ?Transpose:'a4 * ?zAuto:'a5 * ?zMin:'a6 * ?zMax:'a7 * ?Colorscale:Colorscale * ?Autocolorscale:'a8 * ?Reversescale:'a9 * ?Showscale:'a10 * ?zSmooth:SmoothAlg * ?Colorbar:'a11 -> ('T -> 'T) (requires 'h :> IConvertible and 'T :> Trace)
  static member Heatmap : ?Z:seq<#seq<'j>> * ?X:seq<#IConvertible> * ?Y:seq<#IConvertible> * ?X0:'m * ?dX:'n * ?Y0:'o * ?dY:'p * ?xType:'q * ?yType:'r * ?xAxis:'s * ?yAxis:'t * ?Zsrc:'a1 * ?Xsrc:'a2 * ?Ysrc:'a3 * ?Xgap:'a4 * ?Ygap:'a5 * ?Transpose:'a6 * ?zAuto:'a7 * ?zMin:'a8 * ?zMax:'a9 * ?Colorscale:Colorscale * ?Autocolorscale:'a10 * ?Reversescale:'a11 * ?Showscale:'a12 * ?zSmooth:SmoothAlg * ?Colorbar:'a13 -> ('T -> 'T) (requires 'j :> IConvertible and 'T :> Trace)
  static member Histogram : ?X:seq<#IConvertible> * ?Y:seq<#IConvertible> * ?Text:seq<string> * ?xAxis:'g * ?yAxis:'h * ?Xsrc:'i * ?Ysrc:'j * ?Orientation:Orientation * ?HistFunc:HistNorm * ?HistNorm:HistNorm * ?Cumulative:Cumulative * ?Autobinx:bool * ?nBinsx:int * ?xBins:Bins * ?Autobiny:bool * ?nBinsy:int * ?yBins:Bins * ?Marker:Marker * ?xError:Error * ?yError:Error -> ('T -> 'T) (requires 'T :> Trace)
  static member Histogram2d : ?X:seq<#IConvertible> * ?Y:seq<#IConvertible> * ?Z:seq<#seq<'s>> * ?X0:'t * ?dX:'a1 * ?Y0:'a2 * ?dY:'a3 * ?xType:'a4 * ?yType:'a5 * ?xAxis:'a6 * ?yAxis:'a7 * ?Zsrc:'a8 * ?Xsrc:'a9 * ?Ysrc:'a10 * ?Marker:Marker * ?Orientation:Orientation * ?HistFunc:HistNorm * ?HistNorm:HistNorm * ?Autobinx:bool * ?nBinsx:int * ?xBins:Bins * ?Autobiny:bool * ?nBinsy:int * ?yBins:Bins * ?Xgap:'a11 * ?Ygap:'a12 * ?Transpose:'a13 * ?zAuto:'a14 * ?zMin:'a15 * ?zMax:'a16 * ?Colorscale:Colorscale * ?Autocolorscale:'a17 * ?Reversescale:'a18 * ?Showscale:'a19 * ?zSmooth:SmoothAlg * ?Colorbar:'a20 -> ('T -> 'T) (requires 's :> IConvertible and 'T :> Trace)
  static member Histogram2dContour : ?X:seq<#IConvertible> * ?Y:seq<#IConvertible> * ?Z:seq<#seq<'t>> * ?X0:'a1 * ?dX:'a2 * ?Y0:'a3 * ?dY:'a4 * ?xType:'a5 * ?yType:'a6 * ?xAxis:'a7 * ?yAxis:'a8 * ?Zsrc:'a9 * ?Xsrc:'a10 * ?Ysrc:'a11 * ?Marker:Marker * ?Orientation:Orientation * ?HistFunc:HistNorm * ?HistNorm:HistNorm * ?Autobinx:bool * ?nBinsx:int * ?xBins:Bins * ?Autobiny:bool * ?nBinsy:int * ?yBins:Bins * ?nContours:int * ?Contours:Contour * ?Line:Line * ?Xgap:'a12 * ?Ygap:'a13 * ?Transpose:'a14 * ?zAuto:'a15 * ?zMin:'a16 * ?zMax:'a17 * ?Colorscale:Colorscale * ?Autocolorscale:'a18 * ?Reversescale:'a19 * ?Showscale:'a20 * ?zSmooth:SmoothAlg * ?Colorbar:'a21 -> ('T -> 'T) (requires 't :> IConvertible and 'T :> Trace)
  static member Line : ?Width:'f * ?Color:'g * ?Shape:Shape * ?Dash:DrawingStyle * ?Smoothing:'h * ?Colorscale:Colorscale -> ('T -> 'T) (requires 'T :> Trace)
  ...

Full name: FSharp.Plotly.TraceModule.TraceStyle

--------------------
new : unit -> TraceStyle
static member TraceStyle.Sankey : nodes:seq<Node> * links:seq<Link> * ?nodePadding:float * ?nodeThicknes:float * ?nodeColor:obj * ?nodeLineColor:obj * ?nodeLineWidth:float * ?linkColor:obj * ?linkLineColor:obj * ?linkLineWidth:float -> ('T -> 'T) (requires 'T :> Trace)

Full name: PlotlyExts.Sankey
val nodes : seq<Node>
Multiple items
val seq : sequence:seq<'T> -> seq<'T>

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

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

Full name: Microsoft.FSharp.Collections.seq<_>
val links : seq<Link>
val nodePadding : float option
val nodeThicknes : float option
val nodeColor : obj option
val nodeLineColor : obj option
val nodeLineWidth : float option
val linkColor : obj option
val linkLineColor : obj option
val linkLineWidth : float option
val trace : #Trace
Multiple items
module Trace

from PlotlyExts

--------------------
module Trace

from FSharp.Plotly

--------------------
type Trace =
  inherit DynamicObj
  new : traceTypeName:string -> Trace
  member type : string
  member type : string with set

Full name: FSharp.Plotly.Trace

--------------------
new : traceTypeName:string -> Trace
val nonUniqueLabels : seq<string * int>
Multiple items
module Seq

from FSharp.Plotly

--------------------
module Seq

from Microsoft.FSharp.Collections
val countBy : projection:('T -> 'Key) -> source:seq<'T> -> seq<'Key * int> (requires equality)

Full name: Microsoft.FSharp.Collections.Seq.countBy
val x : Node
val filter : predicate:('T -> bool) -> source:seq<'T> -> seq<'T>

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

Full name: Microsoft.FSharp.Collections.Seq.length
val failwithf : format:Printf.StringFormat<'T,'Result> -> 'T

Full name: Microsoft.FSharp.Core.ExtraTopLevelOperators.failwithf
val map : mapping:('T -> 'U) -> source:seq<'T> -> seq<'U>

Full name: Microsoft.FSharp.Collections.Seq.map
val fst : tuple:('T1 * 'T2) -> 'T1

Full name: Microsoft.FSharp.Core.Operators.fst
val lblMap : Map<string,int>
val mapi : mapping:(int -> 'T -> 'U) -> source:seq<'T> -> seq<'U>

Full name: Microsoft.FSharp.Collections.Seq.mapi
val i : int
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 ofSeq : elements:seq<'Key * 'T> -> Map<'Key,'T> (requires comparison)

Full name: Microsoft.FSharp.Collections.Map.ofSeq
val link : DynamicObj
val linkClrs : obj [] option
val x : Link
union case Option.Some: Value: 'T -> Option<'T>
val x : obj
union case Option.None: Option<'T>
module Option

from Microsoft.FSharp.Core
val xs : seq<obj>
val exists : predicate:('T -> bool) -> source:seq<'T> -> bool

Full name: Microsoft.FSharp.Collections.Seq.exists
val toArray : source:seq<'T> -> 'T []

Full name: Microsoft.FSharp.Collections.Seq.toArray
val linkLineClrs : obj [] option
val linkLineWidths : float [] option
val x : float
val xs : seq<float>
val values : obj [] option
val xs : seq<float option>
val isSome : option:'T option -> bool

Full name: Microsoft.FSharp.Core.Option.isSome
val box : value:'T -> obj

Full name: Microsoft.FSharp.Core.Operators.box
val line : DynamicObj option
val cs : obj [] option
val ws : float [] option
val ln : DynamicObj
Multiple items
type DynamicObj =
  inherit DynamicObject
  new : unit -> DynamicObj
  private new : dict:Dictionary<string,obj> -> DynamicObj
  override GetDynamicMemberNames : unit -> IEnumerable<string>
  member GetProperties : includeInstanceProperties:bool -> seq<KeyValuePair<string,obj>>
  member Remove : name:string -> bool
  member SetValue : name:string * value:'a -> unit
  override TryGetMember : binder:GetMemberBinder * result:byref<obj> -> bool
  member TryGetTypedValue : name:string -> 'a option
  member TryGetValue : name:string -> obj option
  ...

Full name: FSharp.Plotly.DynamicObj

--------------------
new : unit -> DynamicObj
module DynObj

from FSharp.Plotly
val setValueOpt : dyn:DynamicObj -> propName:string -> _arg1:'a21 option -> unit

Full name: FSharp.Plotly.DynObj.setValueOpt
val l : DynamicObj
val setValue : dyn:DynamicObj -> propName:string -> o:'i -> unit

Full name: FSharp.Plotly.DynObj.setValue
val node : DynamicObj
val groups : int [] [] option
val collect : mapping:('T -> #seq<'U>) -> source:seq<'T> -> seq<'U>

Full name: Microsoft.FSharp.Collections.Seq.collect
module Array

from Microsoft.FSharp.Collections
val map : mapping:('T -> 'U) -> array:'T [] -> 'U []

Full name: Microsoft.FSharp.Collections.Array.map
val g : obj
val groupBy : projection:('T -> 'Key) -> source:seq<'T> -> seq<'Key * seq<'T>> (requires equality)

Full name: Microsoft.FSharp.Collections.Seq.groupBy
val gs : seq<obj * int>
val snd : tuple:('T1 * 'T2) -> 'T2

Full name: Microsoft.FSharp.Core.Operators.snd
val xs : seq<seq<int>>
val isEmpty : source:seq<'T> -> bool

Full name: Microsoft.FSharp.Collections.Seq.isEmpty
val xRanks : obj [] option
val map : mapping:('T -> 'U) -> option:'T option -> 'U option

Full name: Microsoft.FSharp.Core.Option.map
val yRanks : obj [] option
val nodeClrs : obj [] option
val nodeLineClrs : obj [] option
val nodeLineWidths : float [] option
val n : DynamicObj
type Chart =
  static member Area : xy:seq<#IConvertible * #IConvertible> * ?Name:string * ?ShowMarkers:bool * ?Showlegend:bool * ?MarkerSymbol:Symbol * ?Color:'a2 * ?Opacity:float * ?Labels:seq<#IConvertible> * ?TextPosition:TextPosition * ?TextFont:Font * ?Dash:DrawingStyle * ?Width:'a4 -> GenericChart
  static member Area : x:seq<#IConvertible> * y:seq<#IConvertible> * ?Name:string * ?ShowMarkers:bool * ?Showlegend:bool * ?MarkerSymbol:Symbol * ?Color:'a2 * ?Opacity:float * ?Labels:seq<#IConvertible> * ?TextPosition:TextPosition * ?TextFont:Font * ?Dash:DrawingStyle * ?Width:'a4 -> GenericChart
  static member Bar : keysvalues:seq<#IConvertible * #IConvertible> * ?Name:string * ?Showlegend:bool * ?Color:'a2 * ?Opacity:float * ?Labels:seq<#IConvertible> * ?TextPosition:TextPosition * ?TextFont:Font * ?Marker:Marker -> GenericChart
  static member Bar : keys:seq<#IConvertible> * values:seq<#IConvertible> * ?Name:string * ?Showlegend:bool * ?Color:'a2 * ?Opacity:float * ?Labels:seq<#IConvertible> * ?TextPosition:TextPosition * ?TextFont:Font * ?Marker:Marker -> GenericChart
  static member BoxPlot : xy:seq<'a0 * 'a1> * ?Name:string * ?Showlegend:bool * ?Color:'a2 * ?Fillcolor:'a3 * ?Opacity:float * ?Whiskerwidth:'a4 * ?Boxpoints:Boxpoints * ?Boxmean:BoxMean * ?Jitter:'a5 * ?Pointpos:'a6 * ?Orientation:Orientation -> GenericChart
  static member BoxPlot : ?x:'a0 * ?y:'a1 * ?Name:string * ?Showlegend:bool * ?Color:'a2 * ?Fillcolor:'a3 * ?Opacity:float * ?Whiskerwidth:'a4 * ?Boxpoints:Boxpoints * ?Boxmean:BoxMean * ?Jitter:'a5 * ?Pointpos:'a6 * ?Orientation:Orientation -> GenericChart
  static member Bubble : xysizes:seq<#IConvertible * #IConvertible * #IConvertible> * ?Name:string * ?Showlegend:bool * ?MarkerSymbol:Symbol * ?Color:'a3 * ?Opacity:float * ?Labels:seq<#IConvertible> * ?TextPosition:TextPosition * ?TextFont:Font -> GenericChart
  static member Bubble : x:seq<#IConvertible> * y:seq<#IConvertible> * sizes:seq<#IConvertible> * ?Name:string * ?Showlegend:bool * ?MarkerSymbol:Symbol * ?Color:'a3 * ?Opacity:float * ?Labels:seq<#IConvertible> * ?TextPosition:TextPosition * ?TextFont:Font -> GenericChart
  static member ChoroplethMap : locations:seq<string> * z:seq<#IConvertible> * ?Text:seq<#IConvertible> * ?Locationmode:LocationFormat * ?Autocolorscale:bool * ?Colorscale:Colorscale * ?Colorbar:'a2 * ?Marker:Marker * ?Zmin:'a3 * ?Zmax:'a4 -> GenericChart
  static member Column : keysvalues:seq<#IConvertible * #IConvertible> * ?Name:string * ?Showlegend:bool * ?Color:'a2 * ?Opacity:float * ?Labels:seq<#IConvertible> * ?TextPosition:TextPosition * ?TextFont:Font * ?Marker:Marker -> GenericChart
  ...

Full name: FSharp.Plotly.Chart
static member Chart.Sankey : nodes:seq<Node> * links:seq<Link> * ?nodePadding:float * ?nodeThicknes:float * ?nodeColor:obj * ?nodeLineColor:obj * ?nodeLineWidth:float * ?linkColor:obj * ?linkLineColor:obj * ?linkLineWidth:float -> GenericChart.GenericChart

Full name: PlotlyExts.Sankey
static member TraceStyle.Sankey : nodes:seq<Node> * links:seq<Link> * ?nodePadding:float * ?nodeThicknes:float * ?nodeColor:obj * ?nodeLineColor:obj * ?nodeLineWidth:float * ?linkColor:obj * ?linkLineColor:obj * ?linkLineWidth:float -> ('T -> 'T) (requires 'T :> Trace)
module GenericChart

from FSharp.Plotly
val ofTraceObject : trace:Trace -> GenericChart.GenericChart

Full name: FSharp.Plotly.GenericChart.ofTraceObject
Next Version Raw view Test code New version

More information

Link:http://fssnip.net/7WI
Posted:2 years ago
Author:Faisal Waris, Tobias Burger
Tags: charting , sankey , fsplotly