-- | Dot types. module Sound.SC3.UGen.Dot.Type where -- | Dot output formats. data Dot_Format = DOT | SVG | SVG_GZ deriving (Eq) -- | Dot options record. data Dot_Options = Dot_Options {use_tables :: Bool -- ^ Select @record@ or @html/table@ rendering. ,use_attr_id :: Bool -- ^ Write @ID@ attributes ,use_splines :: Bool -- ^ Select edge rendering ,output_format :: Dot_Format -- ^ Select viewer format. ,fix_edge_location :: Bool -- ^ Select output port edge location. ,numeric_precision :: Int -- ^ Printing precision for constants. ,indicate_precision :: Bool -- ^ Print to precision even if not required ,inline_controls :: Bool -- ^ Draw controls within UGen input port slots. ,display_control_names :: Bool -- ^ Elide control names if 'False'. ,output_directory :: FilePath -- ^ Directory to write files to. ,output_file_name :: String -- ^ File name (without suffix). ,dot_viewer :: String -- ^ @dot@ file viewer (ie. "dotty") ,svg_viewer :: String -- ^ @svg@ file viewer (ie. "rsvg-view","inkview") ,font_name :: String -- ^ Name of font to use ,font_size :: Int -- ^ Font size ,graph_size :: Maybe (Double,Double) -- ^ Graph box size (inches) ,colour_edges :: Bool -- ^ Colour edges according to source? ,run_viewer :: Bool -- ^ Run viewer process? }