Module Svg

module Svg: sig .. end

A small svg module


type svg 
val new_svg_document : width:int -> height:int -> ?unit:string -> unit -> svg

accepted values for the unit parameter can be: "px", "cm", "mm", "em", "ex", "in", "pt", "pc"

val finish_svg : svg -> unit

closes the root svg tag

val add_comment : svg -> s:string -> unit -> unit

adds an xml comment in the source of the svg-document

val add_newline : svg -> unit

adds a newline in the source of the svg document

val get_svg_document : svg -> string

return the result svg document as a string

val write_svg_file : svg -> filename:string -> unit

write the result svg document to a file

val print_svg_document : svg -> unit

prints the result svg document to stdout

Shapes

type class_name 

css class-name

type css_style 

provided by the to_style function

type id_name 

id-name

type svg_attr 

additional parameters, like filter links for example

val add_line : svg ->
x1:int ->
y1:int ->
x2:int ->
y2:int ->
?stroke:string ->
?stroke_width:float ->
?stroke_opacity:float ->
?attrs:svg_attr list ->
?id:id_name ->
?css:class_name -> ?style:css_style -> unit -> unit
val add_polyline : svg ->
points:(int * int) list ->
?stroke:string ->
?stroke_width:float ->
?stroke_opacity:float ->
?fill:string ->
?fill_opacity:float ->
?attrs:svg_attr list ->
?id:id_name ->
?css:class_name -> ?style:css_style -> unit -> unit
val add_polygon : svg ->
points:(int * int) list ->
?stroke:string ->
?stroke_width:float ->
?stroke_opacity:float ->
?fill:string ->
?fill_opacity:float ->
?attrs:svg_attr list ->
?id:id_name ->
?css:class_name -> ?style:css_style -> unit -> unit
val add_rect : svg ->
x:int ->
y:int ->
width:int ->
height:int ->
?rx:float ->
?ry:float ->
?fill:string ->
?fill_opacity:float ->
?stroke:string ->
?stroke_width:float ->
?stroke_opacity:float ->
?attrs:svg_attr list ->
?id:id_name ->
?css:class_name -> ?style:css_style -> unit -> unit
val add_circle : svg ->
cx:float ->
cy:float ->
r:float ->
?fill:string ->
?fill_opacity:float ->
?stroke:string ->
?stroke_width:float ->
?stroke_opacity:float ->
?attrs:svg_attr list ->
?id:id_name ->
?css:class_name -> ?style:css_style -> unit -> unit
val add_ellipse : svg ->
cx:float ->
cy:float ->
r:float * float ->
?fill:string ->
?fill_opacity:float ->
?stroke:string ->
?stroke_width:float ->
?stroke_opacity:float ->
?attrs:svg_attr list ->
?id:id_name ->
?css:class_name -> ?style:css_style -> unit -> unit
val add_triangle : svg ->
p1:int * int ->
p2:int * int ->
p3:int * int ->
?fill:string ->
?fill_opacity:float ->
?stroke:string ->
?stroke_width:float ->
?stroke_opacity:float ->
?attrs:svg_attr list ->
?id:id_name ->
?css:class_name -> ?style:css_style -> unit -> unit
val add_text : svg ->
x:int ->
y:int ->
text:string ->
?text_anchor:string ->
?dominant_baseline:string ->
?font_family:string ->
?font_size:string ->
?font_weight:string ->
?font_style:string ->
?fill:string ->
?fill_opacity:float ->
?stroke:string ->
?stroke_width:float ->
?stroke_opacity:float ->
?attrs:svg_attr list ->
?id:id_name ->
?css:class_name -> ?style:css_style -> unit -> unit
module Float: sig .. end

Compound Shapes

val add_circle_sector : svg ->
cx:float ->
cy:float ->
r:float ->
angle1:float ->
angle2:float ->
?fill:string ->
?fill_opacity:float ->
?stroke:string ->
?stroke_width:float ->
?stroke_opacity:float ->
?id:id_name ->
?css:class_name -> ?style:css_style -> unit -> unit
val add_donut_slice : svg ->
cx:float ->
cy:float ->
r1:float ->
r2:float ->
angle1:float ->
angle2:float ->
?fill:string ->
?fill_opacity:float ->
?stroke:string ->
?stroke_width:float ->
?stroke_opacity:float ->
?id:id_name ->
?css:class_name -> ?style:css_style -> unit -> unit

Regular-Polygons, and Stars

val add_regular_polygon : svg ->
c:float * float ->
n:int ->
r:float ->
?off:float ->
?fill:string ->
?fill_opacity:float ->
?stroke:string ->
?stroke_width:float ->
?stroke_opacity:float ->
?attrs:svg_attr list ->
?id:id_name ->
?css:class_name -> ?style:css_style -> unit -> unit
val add_star : svg ->
c:float * float ->
n:int ->
rs:float * float ->
?off:float ->
?fill:string ->
?fill_opacity:float ->
?stroke:string ->
?stroke_width:float ->
?stroke_opacity:float ->
?attrs:svg_attr list ->
?id:id_name ->
?css:class_name -> ?style:css_style -> unit -> unit

Transformations

val begin_group : svg ->
?translate:float * float ->
?rotate:float * int * int -> ?scale:float * float -> unit -> unit
val end_group : svg -> unit

There are two possible ways to create links: with the begin/end functions, or with a fragment.

val begin_link : svg -> href:string -> ?title:string -> unit -> unit
val end_link : svg -> unit
val add_link : svg -> href:string -> ?title:string -> frag:svg -> unit -> unit

Paths

type path 
val empty_path : path
val new_path : unit -> path
val move_to : path -> x:float -> y:float -> path
val line_to : path -> x:float -> y:float -> path
val h_line : path -> x:float -> path
val v_line : path -> y:float -> path
val quad_curve : path -> x1:float -> y1:float -> x:float -> y:float -> path
val cubic_curve : path ->
x1:float ->
y1:float -> x2:float -> y2:float -> x:float -> y:float -> path
val arc_to : path ->
x:float ->
y:float ->
r:float * float ->
?rotation:float -> ?large_arc:bool -> ?clockwise:bool -> unit -> path
val close_path : path -> path
val add_path : svg ->
path:path ->
?fill:string ->
?fill_opacity:float ->
?stroke:string ->
?stroke_width:float ->
?stroke_opacity:float ->
?attrs:svg_attr list ->
?id:id_name ->
?css:class_name -> ?style:css_style -> unit -> unit
type cmd = 
| M of float * float (*

move-to

*)
| L of float * float (*

line-to

*)
| H of float (*

h-line

*)
| V of float (*

v-line

*)
| Q of (float * float) * (float * float) (*

quad-curve

*)
| C of (float * float) * (float * float) * (float * float) (*

cubic-curve

*)
| A of (float * float) * float * bool * bool * (float * float) (*

arc-to

*)
| Z (*

close-path

*)

path-commands

val to_path : cmd list -> path

convert commands to a path

module Relative: sig .. end
val scale_path : float -> cmd list -> cmd list

scale the coordinates of path commands

val translate_path : float * float -> cmd list -> cmd list

translate the coordinates of path commands (only for non-relative coords)

val of_relative : cmd list -> cmd list

Fragments

val new_fragment : unit -> svg

initialises a new svg fragment (useful for example to simulate layers)

val add_fragment : svg -> frag:svg -> unit

add_fragment svg frag adds the fragment frag to the svg document svg

val fragment_from_file : filename:string -> svg

loads an svg fragment from a file

CSS / Styles

type css_attr 
val fill : css_attr
val fill_opacity : css_attr
val stroke : css_attr
val stroke_width : css_attr
val stroke_opacity : css_attr
val text_anchor : css_attr
val font_family : css_attr
val font_size : css_attr
val font_weight : css_attr
val font_style : css_attr
val letter_spacing : css_attr
val word_spacing : css_attr
val to_style : styles:(css_attr * string) list -> css_style

format css-properties that you can provide to the style parameter of the shapes functions

module Attrs: sig .. end

CSS style-sheet

type style_sheet 

css style-sheet

val new_style_sheet : unit -> style_sheet

initialises a new empty style-sheet

val style_sheet_add : style_sheet ->
class_name:string ->
properties:(css_attr * string) list -> class_name * style_sheet

adds css-properties to a css style-sheet, and returns the associated class_name, that can be provided to the ~css:class_name parameter of the shapes functions

val add_style_sheet : svg -> style_sheet -> unit

add the css style-sheet to a svg document

ID's

val style_sheet_add_id : style_sheet ->
id_name:string ->
properties:(css_attr * string) list -> id_name * style_sheet

same than style_sheet_add, but using an id instead of a class_name

the returned id_name can be provided to the ~id parameter of the shapes functions

val mk_id : string -> id_name

makes an id with no associated style

Gradients

type def 

defines additional elements, that can be used in conjunction with other shapes elements

val linear_gradient : p1:int * int ->
p2:int * int ->
stops:(float * string) list ->
?translate:int * int -> unit -> def * string

a stop should be a tuple with a float between 0.0 and 1.0, and a color

returns a def that should be added to the svg document with add_def,

and a string that should be provided to the fill parameter of shape functions

val radial_gradient : c:int * int ->
r:int ->
stops:(float * string) list ->
?translate:int * int -> unit -> def * string
val add_def : svg -> def -> unit

add a def to the svg document

val add_defs : svg -> def list -> unit

add some defs to the svg document

Example

Here is a small example:

let () =
  let svg = Svg.new_svg_document ~width:300 ~height:190 () in

  Svg.add_circle svg
      ~cx:120.0
      ~cy:80.0
      ~r:60.0
      ~fill:"#00f" ();

  Svg.finish_svg svg;
  Svg.print_svg_document svg;
;;

It will create a small svg-document, with a blue circle in the middle of it.

Filters

val gaussian_blur : std_dev:float -> def * svg_attr

gaussian-blur, returns a def that should be added to the svg document with add_def,

and an svg_attr that should be added to the shape functions with the attrs parameter

val gaussian_blur2 : std_dev:float * float -> def * svg_attr

same than gaussian_blur but with 2 different values for the x and y axes

Markers

val make_marker : marker_size:int * int ->
ref_pos:int * int -> frag:svg -> def * svg_attr * svg_attr

returns a def, and a svg_attr that can be provided to the attrs parameter of the stroke shape functions (line, polyline, and path)

returns 2 svg_attr (start, end), if there is one that is not needed, it can be ignored with the wildcard "_"

Patterns

val make_pattern : width:int -> height:int -> frag:svg -> def * string

creates a pattern with the given size, filled with a fragment

returns a string that can be used for the ~fill parameters of shapes

Clipping

val clip_path : frag:svg -> def * svg_attr

returns a clip-path that can be provided to the attr parameter of shapes