hsc3-plot-0.15: Haskell SuperCollider Plotting

Safe HaskellNone
LanguageHaskell98

Sound.SC3.Plot

Contents

Description

Simple-minded plotters for Sound.SC3.

Synopsis

Math

minmax :: Ord t => [t] -> (t, t) Source

linlin'' :: Fractional a => (a, a) -> (a, a) -> a -> a Source

normalise_seq :: (Fractional b, Ord b) => (b, b) -> (b, b) -> [b] -> [b] Source

linlin of z.

normalise_seq' :: (Fractional b, Ord b) => (b, b) -> [b] -> [b] Source

Variant that derives domain from minmax of z.

square :: Num a => a -> a Source

n * n.

rms :: Floating a => [a] -> a Source

Root mean square.

resample_rms :: Floating b => Int -> [b] -> [b] Source

Data

class Num n => PNum n where Source

Class of plottable numbers. This is necessary to allow Rational, the show instance of which cannot be read by gnuplot.

Methods

pshow :: n -> String Source

Attr

type Attr = (Int, Int) -> String Source

Attibutes are generated given (i,j) where i is the data set (one indexed) and j is the number of data sets.

1-dimensional

type Table t = [t] Source

List of y values, at (implicit) equal x increments.

plotTable :: PNum t => [Table t] -> IO () Source

Plot Table data.

plotTable [[0,2..12],[0..6],[0,4..12]]
plotTable [map (\x -> x * cos (x / 20)) [-400 .. 800]]

plotTable1 :: PNum t => Table t -> IO () Source

Variant to plot singular Table.

plotImpulses :: PNum t => [[t]] -> IO () Source

Variant of plotTable where each value is drawn as an impulse.

plotImpulses [[0,2..12],[0..6],[0,4..12]]
plotImpulses [map (\x -> x * cos (x / 20)) [-400 .. 800]]

plot_table_displace :: (Enum t, Fractional t, Ord t, PNum t) => [[t]] -> IO () Source

Variant that scales each plot lie within (0,1) and displaces them.

plot_table_displace [[0,2..12],[0..6],[0,4..12]]

plot_table_displace_nrm :: (Enum t, Fractional t, Ord t, PNum t) => [[t]] -> IO () Source

Variant that normalises each table separately.

plot_table_displace_nrm [[0,2..12],[0..6],[0,4..12]]

2-dimensional

type P2 t = (t, t) Source

Cartesian (x,y) pair.

type Coord t = [P2 t] Source

List of P2.

plot_p2 :: PNum t => Attr -> [Coord t] -> IO () Source

Plot set of Coord.

let {x = [-pi,-pi + 0.01 .. pi]
    ;f r t = (r t * cos t,r t * sin t)}
in plot_p2 (attr_frac_lines 0.5)
           [zip (map cos x) (map sin x)
           ,zip (map cos x) (map (sin . (* 3)) x)
           ,map (f ((/ (2 * pi)) . (+ pi))) x]

plot_p2_ln :: PNum t => [Coord t] -> IO () Source

plot_p2 of with lines.

plot_p2_pt :: PNum t => [Coord t] -> IO () Source

plot_p2 of with points.

let f a b c d (x,y) =
    (x ** 2 - y ** 2 + a * x + b * y
    ,2 * x * y + c * x + d * y)
in plot_p2_pt [take 5000 (iterate (f 0.9 (-0.6013) 2.0 0.5) (0.1,0.0))]

plot_p2_stp :: PNum t => [Coord t] -> IO () Source

plot_p2 of with steps.

plot_p2_stp [[(0,0),(1,1),(2,0.5),(4,6),(5,1),(6,0.25)]]

3-dimensional

type P3 t = (t, t, t) Source

Cartesian (x,y,z) triple.

type Path t = [P3 t] Source

List of P3.

plot_p3 :: PNum t => Attr -> [Path t] -> IO () Source

Three-dimensional variant of plot_p2.

let {t' = [-pi,-pi + 0.01 .. pi]
    ;f0 n d = sin . (+) d . (*) n
    ;f1 t = (f0 1 (pi/2) t,f0 3 0 t,f0 5 0 t)
    ;e' = [0,0.005 .. pi]
    ;f2 a b r e t = ((a * t + r * sin e) * cos t
                    ,(a * t + r * sin e) * sin t
                    ,b * t + r * (1 - cos e))}
in plot_p3 (const "with lines")
           [map f1 t'
           ,zipWith (f2 0.25 0.25 0.25) e' t']

plot_p3_ln :: PNum t => [Path t] -> IO () Source

plot_p3 of with lines.

plot_p3_pt :: PNum t => [Path t] -> IO () Source

plot_p3 of with points pt 0.

Vector (Cartesian)

type Vc t = [(P2 t, P2 t)] Source

List of (P2,P2) vectors.

plotVectors :: (PNum t, Num t) => [Vc t] -> IO () Source

Plot vectors given as (p,q).

let {p = [((0,0),(2,1)),((2,2),(3,2)),((3,4),(4,1))]
    ;d = [1,2,3,2,3,2,1]
    ;x = 0 : scanl1 (+) d
    ;y = [6,4,5,3,7,2,8]
    ;f x y d = ((x,y),(x+d,y))}
in plotVectors [p,zipWith3 f x y d]

Matrix

plotMatrix :: (PNum t, Num t) => [String] -> [[t]] -> IO () Source

Plot regular matrix data.

plotMatrix ["set palette grey","unset colorbox"] [[1,3,2],[6,4,5],[8,9,7]]
let d = [[1.00000000,1.00000000,1.00000000,0.73961496]
        ,[1.00000000,1.00000000,1.00000000,0.39490538]
        ,[0.53443549,0.31331112,0.90917979,0.58216201]
        ,[0.35888692,0.7361968,0.95389629,0.94283073]
        ,[0.85763543,0.1405479,0.78166569,0.43739318]
        ,[0.18519824,0.31907815,0.18394244,0.01633875]
        ,[0.0442339,0.33393132,0.77247883,0.79683943]
        ,[0.8472137,0.42471225,0.94257581,0.70417117]]
in plotMatrix ["set palette color"] d

Envelope

plotEnvelope :: (PNum t, Ord t, Floating t, Enum t) => [Envelope t] -> IO () Source

Plot Envelope data.

import Sound.SC3
plotEnvelope [envPerc 0.2 1
             ,envSine 1 0.75
             ,envADSR 0.4 0.4 0.8 0.9 1 (EnvNum (-4)) 0]

Buffer

plot_buffer1 :: (MonadIO m, DuplexOSC m) => Int -> m () Source

plotTable1 of b_fetch.

withSC3 (plot_buffer1 0)

plot_buffer1_rms :: (MonadIO m, DuplexOSC m) => Int -> Int -> m () Source

plotTable1 of resample_rms of b_fetch.

withSC3 (plot_buffer1_rms 512 0)

plot_buffer1_resamp1 :: (MonadIO m, DuplexOSC m) => Int -> Int -> m () Source

plot_table1_resamp1 of b_fetch.

withSC3 (plot_buffer1_resamp1 512 0)

Histogram

plotHistogram :: PNum t => [Histogram t] -> IO () Source

Plot Histogram data.

plotHistogram [histogram 3 [0,0,1,2,2,2]
              ,histogram 9 [1,2,2,3,3,3,4,4,4,4]]

Vector (Data Type)

plot_table1_resamp1 :: (Enum t, RealFrac t, PNum t) => Int -> Vector t -> IO () Source

plot_table1_vector of resamp1.

d <- withSC3 (b_fetch 512 0)
plot_table1_resamp1 1024 (V.fromList d)

Synonyms

Low-level

type PlotSize = (Double, Double) Source

Plot size (width,height).

plotOptX11 :: PlotOpt Source

Default options for X11.

plotOptWXT :: PlotOpt Source

Default options for WXT.

plotOptSVG :: PlotSize -> PlotOpt Source

Default options for SVG.

plotNameEnc :: PlotOpt -> String Source

Names for SVG terminal have character restrictions.

type PlotParam = ([String], String, Attr) Source

Plot parameters, (pre,cmd,attr)

writePlotData :: (PNum t, Num t) => PlotOpt -> [[[t]]] -> IO () Source

mkPlotOpt :: (PNum t, Num t) => PlotOpt -> PlotParam -> [[[t]]] -> IO () Source

Plotter given PlotOpt and PlotParam.

mkPlotX11 :: (PNum t, Num t) => PlotParam -> [[[t]]] -> IO () Source

mkPlotSVG :: (Num t, PNum t) => PlotSize -> PlotParam -> [[[t]]] -> IO () Source

mkPlot :: (PNum t, Num t) => PlotParam -> [[[t]]] -> IO () Source

WXT and SVG.