Module OFC


module OFC: sig .. end
OCaml interface for Open Flash Chart 2


Types


type chart 
type 'a elem 
type line 
type area 
type bar 
type hbar 
type bar_stack 
type pie 
type candle 
type arrow 

type v_elem =
| Area of area elem
| Line of line elem
| Pie of pie elem
| Bar of bar elem
| HBar of hbar elem
| BarStack of bar_stack elem
| Arrow of arrow elem
| Candle of candle elem
type labels 
type spoke_labels 
type label_item 
type spoke_label_item 

type align =
| Right
| Center
| Left

Main class for the Charts


val new_chart : unit -> chart
val print_chart : ?print_header:bool -> chart -> unit
val chart_set_title : chart -> ?style:string -> string -> unit
val chart_set_bg_colour : chart -> bg_colour:string -> unit
val chart_add_element : chart -> 'a elem -> unit
val chart_add_elements : chart -> v_elem list -> unit
val chart_set_tooltip : chart ->
?colour:string ->
?background:string ->
?title:string ->
?body:string -> ?stroke:int -> ?shadow:bool -> ?mouse:int -> unit -> unit

Axes


val chart_set_x_legend : chart -> ?style:string -> string -> unit
val chart_set_y_legend : chart -> ?style:string -> string -> unit
val chart_set_x_axis : chart ->
?min:int ->
?max:int ->
?steps:int ->
?colour:string ->
?grid_colour:string ->
?labels:labels ->
?stroke:int ->
?tick_size:int -> ?offset:int -> ?offset_b:bool -> ?_3d:int -> unit -> unit
val chart_set_y_axis : chart ->
?min:int ->
?max:int ->
?steps:int ->
?colour:string ->
?grid_colour:string ->
?labels:labels ->
?stroke:int ->
?tick_size:int -> ?offset:int -> ?offset_b:bool -> unit -> unit
val chart_set_y_axis_right : chart ->
?min:int ->
?max:int ->
?steps:int ->
?colour:string ->
?grid_colour:string ->
?labels:labels ->
?stroke:int ->
?tick_size:int -> ?offset:int -> ?offset_b:bool -> unit -> unit
val chart_set_radar_axis : chart ->
?max:int ->
?steps:int ->
?colour:string ->
?grid_colour:string ->
?labels:labels ->
?spoke_labels:spoke_labels -> ?stroke:int -> unit -> unit

Labels for the axes


val new_labels : ?colour:string ->
?size:int ->
?steps:int ->
?visible_steps:int ->
?text:string ->
?align:align -> ?rotate:int -> ?visible:bool -> string list -> labels
val new_spoke_labels : ?colour:string ->
?size:int ->
?steps:int ->
?visible_steps:int ->
?text:string ->
?align:align ->
?rotate:int -> ?visible:bool -> string list -> spoke_labels
val label_item : ?colour:string ->
?size:int ->
?steps:int ->
?visible_steps:int ->
?align:align -> ?rotate:int -> ?visible:bool -> string -> label_item
module Label: sig .. end
val x_label_item : ?colour:string ->
?grid_colour:string ->
?size:int ->
?steps:int ->
?visible_steps:int ->
?text:string ->
?align:align ->
?rotate:int -> ?visible:bool -> Label.lable_value -> label_item
val y_label_item : ?colour:string ->
?grid_colour:string ->
?size:int ->
?steps:int ->
?visible_steps:int ->
?text:string ->
?align:align ->
?rotate:int -> ?visible:bool -> Label.lable_value -> label_item
val new_label_items : label_item list -> labels
val new_spoke_label_items : label_item list -> spoke_labels

Line element


val new_line_elem : unit -> line elem
val line_elem_set_width : line elem -> int -> unit
val line_elem_set_colour : line elem -> string -> unit
val line_elem_set_dot_size : line elem -> int -> unit
val line_elem_set_halo_size : line elem -> int -> unit
val line_elem_set_legend : line elem -> string -> unit
val line_elem_set_font_size : line elem -> int -> unit
val line_elem_set_loop : line elem -> bool -> unit
val line_elem_add_ints : line elem -> int list -> unit
val line_elem_add_floats : line elem -> float list -> unit
type dot 

type value =
| Int of int
| Float of float
| Value of dot
| Null

type dot_kind =
| Dot
| Solid_dot
| Hollow_dot
| Anchor
| Star
| Bow

type dot_value =
| I of int
| F of float
| II of int * int
| FF of float * float
| IF of int * float
| FI of float * int
val dot : ?colour:string ->
?kind:dot_kind ->
?tip:string ->
?dot_size:int ->
?halo_size:int ->
?sides:int ->
?label:string ->
?label_colour:string ->
?font_size:int -> ?on_click:string -> dot_value -> value
val line_elem_add_values : line elem -> value list -> unit
val line_elem_set_dot_style : line elem ->
?kind:dot_kind ->
?hollow:bool ->
?colour:string ->
?alpha:float ->
?background_colour:string ->
?background_alpha:float ->
?dot_size:int ->
?size:int ->
?sides:int -> ?width:int -> ?tip:string -> ?halo_size:int -> unit -> unit

type line_style =
| Dash
| Solid
val line_elem_set_line_style : line elem ->
?style:line_style -> ?on:int -> ?off:int -> unit -> unit

type on_show_kind =
| Mid_slide
| Grow_up
| Pop
| Pop_up
| Drop
| Shrink_in
| Explode
| Fade_in
val line_elem_set_on_show : line elem ->
kind:on_show_kind -> ?cascade:float -> ?delay:float -> unit -> unit

Area element


val new_area_elem : unit -> area elem
val area_elem_set_fill : area elem -> string -> unit
val area_elem_set_fill_alpha : area elem -> float -> unit
val area_elem_set_width : area elem -> int -> unit
val area_elem_set_colour : area elem -> string -> unit
val area_elem_set_dot_size : area elem -> int -> unit
val area_elem_set_legend : area elem -> string -> unit
val area_elem_set_font_size : area elem -> int -> unit
val area_elem_set_loop : area elem -> bool -> unit
val area_elem_add_ints : area elem -> int list -> unit
val area_elem_add_floats : area elem -> float list -> unit
val area_elem_add_values : area elem -> value list -> unit
val area_elem_set_dot_style : area elem ->
?kind:dot_kind ->
?hollow:bool ->
?colour:string ->
?alpha:float ->
?background_colour:string ->
?background_alpha:float ->
?dot_size:int ->
?size:int ->
?sides:int -> ?width:int -> ?tip:string -> ?halo_size:int -> unit -> unit
val area_elem_set_line_style : area elem ->
?style:line_style -> ?on:int -> ?off:int -> unit -> unit
val area_elem_set_on_show : area elem ->
kind:on_show_kind -> ?cascade:float -> ?delay:float -> unit -> unit

Bar element


val new_bar_elem : unit -> bar elem
val new_bar_sketch_elem : unit -> bar elem
val new_bar_3d_elem : unit -> bar elem
val new_bar_filled_elem : unit -> bar elem
val new_bar_cylinder_elem : unit -> bar elem
val new_bar_cylinder_outline_elem : unit -> bar elem
val new_bar_round_glass_elem : unit -> bar elem
val new_bar_round_elem : unit -> bar elem
val new_bar_dome_elem : unit -> bar elem
val new_bar_glass_elem : unit -> bar elem
val new_bar_plastic_elem : unit -> bar elem
val new_bar_plastic_flat_elem : unit -> bar elem
val new_bar_round3d_elem : unit -> bar elem
val bar_elem_set_alpha : bar elem -> alpha:float -> unit
val bar_elem_set_tip : bar elem -> tip:string -> unit
val bar_elem_set_width : bar elem -> int -> unit
val bar_elem_set_colour : bar elem -> string -> unit
val bar_elem_set_dot_size : bar elem -> int -> unit
val bar_elem_set_legend : bar elem -> string -> unit
val bar_elem_set_font_size : bar elem -> int -> unit
val bar_elem_add_ints : bar elem -> int list -> unit
val bar_elem_add_floats : bar elem -> float list -> unit
val bar_elem_add_values : bar elem -> value list -> unit
val bar_elem_set_on_show : bar elem ->
kind:on_show_kind -> ?cascade:float -> ?delay:float -> unit -> unit
val new_hbar_elem : unit -> hbar elem
val hbar_elem_set_tip : hbar elem -> tip:string -> unit
val hbar_elem_set_width : hbar elem -> int -> unit
val hbar_elem_set_colour : hbar elem -> string -> unit
val hbar_elem_set_dot_size : hbar elem -> int -> unit
val hbar_elem_set_legend : hbar elem -> string -> unit
val hbar_elem_set_font_size : hbar elem -> int -> unit
val hbar_elem_set_on_show : hbar elem ->
kind:on_show_kind -> ?cascade:float -> ?delay:float -> unit -> unit
val hbar_elem_add_ints : hbar elem -> int list -> unit
val hbar_elem_add_floats : hbar elem -> float list -> unit
module HBar_values: sig .. end
val hbar_elem_add_values : hbar elem -> HBar_values.hbar_value list -> unit

Bar-Stack element


val new_bar_stack_elem : unit -> bar_stack elem
val bar_stack_elem_set_colours : bar_stack elem -> colours:string list -> unit
val bar_stack_elem_add_ints : bar_stack elem -> int list list -> unit
val bar_stack_elem_add_floats : bar_stack elem -> float list list -> unit
module Bar_stack_values: sig .. end
val bs_value_int : ?colour:string -> int -> Bar_stack_values.value
val bs_value_float : ?colour:string -> float -> Bar_stack_values.value
val bar_stack_elem_add_values : bar_stack elem -> Bar_stack_values.value list list -> unit
type bar_stack_key 
val bs_key : ?colour:string -> ?text:string -> ?font_size:int -> unit -> bar_stack_key
val bar_stack_elem_set_keys : bar_stack elem -> bar_stack_key list -> unit

Pie element


val new_pie_elem : unit -> pie elem
val pie_elem_set_colours : pie elem -> colours:string list -> unit
val pie_elem_set_radius : pie elem -> radius:int -> unit
val pie_elem_set_alpha : pie elem -> alpha:float -> unit
val pie_elem_set_border : pie elem -> border:int -> unit
val pie_elem_set_start_angle : pie elem -> start_angle:int -> unit
val pie_elem_set_gradient_fill : pie elem -> gradient_fill:bool -> unit
val pie_elem_set_no_labels : pie elem -> no_labels:bool -> unit
val pie_elem_set_label_colour : pie elem -> label_colour:string -> unit
val pie_elem_set_tip : pie elem -> tip:string -> unit
val pie_elem_set_animate : pie elem -> animate:bool -> unit

type pie_animations =
| Bounce of int
| Fade
val pie_elem_set_animations : pie elem -> animations:pie_animations list -> unit
module Pie_values: sig .. end
val pie_value : ?label:string ->
?tip:string ->
?on_click:string ->
Pie_values.pie_value_param -> Pie_values.pie_value
val pie_elem_add_values : pie elem -> Pie_values.pie_value list -> unit

Candle Element


val new_candle_elem : unit -> candle elem
val candle_elem_set_on_show : candle elem ->
kind:on_show_kind -> ?cascade:float -> ?delay:float -> unit -> unit
val candle_elem_set_colour : candle elem -> colour:string -> unit
val candle_elem_set_negative_colour : candle elem -> colour:string -> unit
val candle_elem_set_alpha : candle elem -> alpha:float -> unit
val candle_elem_set_legend : candle elem -> text:string -> unit
val candle_elem_set_font_size : candle elem -> size:int -> unit
val candle_elem_set_tip : candle elem -> tip:string -> unit
type candle_value 
val candle_value_ints : high:int ->
top:int ->
bottom:int ->
low:int -> ?tip:string -> ?colour:string -> unit -> candle_value
val candle_value_floats : high:float ->
top:float ->
bottom:float ->
low:float -> ?tip:string -> ?colour:string -> unit -> candle_value
val candle_elem_add_values : candle elem -> candle_value list -> unit

Arrow Element


val new_arrow_elem : start:int * int ->
end_:int * int ->
?barb_length:int -> ?colour:string -> unit -> arrow elem