Copyright | (c) Justus Sagemüller 2013-2019 |
---|---|
License | GPL v3 |
Maintainer | (@) jsag $ hvl.no |
Stability | experimental |
Portability | requires GHC>6 extensions |
Safe Haskell | None |
Language | Haskell2010 |
- plotPrerender :: ViewportConfig -> [DynamicPlottable] -> IO PlainGraphicsR2
- plotWindow :: [DynamicPlottable] -> IO GraphWindowSpec
- plotWindow' :: ViewportConfig -> [DynamicPlottable] -> IO GraphWindowSpec
- class Plottable p where
- fnPlot :: (forall m. Object (RWDiffable ℝ) m => AgentVal (-->) m ℝ -> AgentVal (-->) m ℝ) -> DynamicPlottable
- paramPlot :: (forall m. (WithField ℝ PseudoAffine m, SimpleSpace (Needle m)) => AgentVal (-->) m ℝ -> (AgentVal (-->) m ℝ, AgentVal (-->) m ℝ)) -> DynamicPlottable
- continFnPlot :: (Double -> Double) -> DynamicPlottable
- tracePlot :: [(Double, Double)] -> DynamicPlottable
- lineSegPlot :: [(Double, Double)] -> DynamicPlottable
- linregressionPlot :: forall x m y. (SimpleSpace m, Scalar m ~ ℝ, y ~ ℝ, x ~ ℝ) => (x -> m +> y) -> [(x, Shade' y)] -> (Shade' m -> DynamicPlottable -> DynamicPlottable -> DynamicPlottable) -> DynamicPlottable
- colourPaintPlot :: ((Double, Double) -> Maybe (Colour Double)) -> DynamicPlottable
- type PlainGraphicsR2 = Diagram B
- shapePlot :: PlainGraphicsR2 -> DynamicPlottable
- diagramPlot :: PlainGraphicsR2 -> DynamicPlottable
- plotMultiple :: Plottable x => [x] -> DynamicPlottable
- plotLatest :: Plottable x => [x] -> DynamicPlottable
- tint :: Colour ℝ -> DynamicPlottable -> DynamicPlottable
- autoTint :: DynamicPlottable -> DynamicPlottable
- legendName :: String -> DynamicPlottable -> DynamicPlottable
- plotLegendPrerender :: LegendDisplayConfig -> [DynamicPlottable] -> IO (Maybe PlainGraphicsR2)
- plotDelay :: NominalDiffTime -> DynamicPlottable -> DynamicPlottable
- freezeAnim :: DynamicPlottable -> DynamicPlottable
- startFrozen :: DynamicPlottable -> DynamicPlottable
- xInterval :: (Double, Double) -> DynamicPlottable
- yInterval :: (Double, Double) -> DynamicPlottable
- forceXRange :: (Double, Double) -> DynamicPlottable
- forceYRange :: (Double, Double) -> DynamicPlottable
- unitAspect :: DynamicPlottable
- newtype MousePressed = MousePressed {
- mouseIsPressedAt :: Maybe (ℝ, ℝ)
- newtype MousePress = MousePress {
- lastMousePressedLocation :: (ℝ, ℝ)
- newtype MouseClicks = MouseClicks {
- getClickPositions :: [(ℝ, ℝ)]
- clickThrough :: Plottable p => [p] -> DynamicPlottable
- withDraggablePoints :: forall p list. (Plottable p, Traversable list) => list (ℝ, ℝ) -> (list (ℝ, ℝ) -> p) -> DynamicPlottable
- mouseInteractive :: Plottable p => (MouseEvent (ℝ, ℝ) -> s -> s) -> s -> (s -> p) -> DynamicPlottable
- data MouseEvent x
- clickLocation :: forall x. Lens' (MouseEvent x) x
- releaseLocation :: forall x. Lens' (MouseEvent x) x
- newtype ViewXCenter = ViewXCenter {}
- newtype ViewYCenter = ViewYCenter {}
- newtype ViewWidth = ViewWidth {}
- newtype ViewHeight = ViewHeight {}
- newtype ViewXResolution = ViewXResolution {}
- newtype ViewYResolution = ViewYResolution {}
- dynamicAxes :: DynamicPlottable
- noDynamicAxes :: DynamicPlottable
- xAxisLabel :: String -> DynamicPlottable
- yAxisLabel :: String -> DynamicPlottable
- type DynamicPlottable = DynamicPlottable' RVar
- tweakPrerendered :: (PlainGraphicsR2 -> PlainGraphicsR2) -> DynamicPlottable -> DynamicPlottable
- data ViewportConfig
- xResV :: Lens' ViewportConfig Int
- yResV :: Lens' ViewportConfig Int
- setSolidBackground :: Colour Double -> ViewportConfig -> ViewportConfig
- prerenderScaling :: Lens' ViewportConfig PrerenderScaling
- data PrerenderScaling
- data LegendDisplayConfig
- legendPrerenderSize :: Iso' LegendDisplayConfig (SizeSpec V2 Double)
- graphicsPostprocessing :: Lens' ViewportConfig (PlainGraphicsR2 -> PlainGraphicsR2)
Display
Static
plotPrerender :: ViewportConfig -> [DynamicPlottable] -> IO PlainGraphicsR2 Source #
Render a single view of a collection of plottable objects. This can be
used the same way as plotWindow
, but does not open any GTK but gives
the result as-is.
If the objects contain animations, only the initial frame will be rendered.
Interactive
plotWindow :: [DynamicPlottable] -> IO GraphWindowSpec Source #
Plot some plot objects to a new interactive GTK window. Useful for a quick preview of some unknown data or real-valued functions; things like selection of reasonable view range and colourisation are automatically chosen.
Example:
The individual objects you want to plot can be evaluated in multiple threads, so
a single hard calculatation won't freeze the responsitivity of the whole window.
Invoke e.g. from ghci +RTS -N4
to benefit from this.
ATTENTION: the window may sometimes freeze, especially when displaying
complicated functions with fnPlot
from ghci. This is apparently
a kind of deadlock problem with one of the C libraries that are invoked,
At the moment, we can recommend no better solution than to abort and restart ghci
(or what else you use – iHaskell kernel, process, ...) if this occurs.
plotWindow' :: ViewportConfig -> [DynamicPlottable] -> IO GraphWindowSpec Source #
Like plotWindow
, but with explicit specification how the window is supposed
to show up. (plotWindow
uses the default configuration, i.e. def
.)
Plottable objects
Class
class Plottable p where Source #
Class for types that can be plotted in some canonical, “obvious”
way. If you want to display something and don't know about any specific caveats,
try just using plot
!
plot :: p -> DynamicPlottable Source #
Plottable DynamicPlottable Source # | |
Plottable p => Plottable [p] Source # | |
Plottable p => Plottable (Maybe p) Source # | |
Plottable p => Plottable (Option p) Source # | |
Plottable (Shade ℝ²) Source # | |
Plottable (ConvexSet ℝ²) Source # | |
Plottable (Shade' ℝ²) Source # | |
Plottable (Cutplane (ℝ, ℝ)) Source # | |
Plottable (Cutplane ℝ²) Source # | |
Plottable p => Plottable (MousePressed -> p) Source # | |
Plottable p => Plottable (MousePress -> p) Source # | |
Plottable p => Plottable (MouseClicks -> p) Source # | |
Plottable p => Plottable (ViewHeight -> p) Source # | |
Plottable p => Plottable (ViewWidth -> p) Source # | |
Plottable p => Plottable (ViewYCenter -> p) Source # | |
Plottable p => Plottable (ViewXCenter -> p) Source # | |
Plottable (PointsWeb (ℝ, ℝ) (Colour ℝ)) Source # | |
Plottable (PointsWeb (ℝ, ℝ) (Shade (Colour ℝ))) Source # | |
Plottable (PointsWeb ℝ² (Colour ℝ)) Source # | |
Plottable (PointsWeb ℝ² (Shade (Colour ℝ))) Source # | |
Plottable (PointsWeb ℝ (Shade' ℝ)) Source # | |
Plottable (Shaded ℝ ℝ) Source # | |
Simple function plots
fnPlot :: (forall m. Object (RWDiffable ℝ) m => AgentVal (-->) m ℝ -> AgentVal (-->) m ℝ) -> DynamicPlottable Source #
Plot a continuous function in the usual way, taking arguments from the
x-Coordinate and results to the y one.
The signature looks more complicated than it is; think about it as requiring
a polymorphic Floating
function. Any simple expression like
will work.fnPlot
(\x -> sin x / cos (sqrt x))
Under the hood this uses the category of region-wise differentiable functions,
RWDiffable
, to prove that no details are omitted (like small high-frequency
bumps). Note that this can become difficult for contrived cases like cos(1/sin x)
– while such functions will never come out with aliasing artifacts, they also
may not come out quickly at all. (But for well-behaved functions, using the
differentiable category actually tends to be more effective, because the algorithm
immediately sees when it can describe an almost-linear region with only a few line
segments.)
This function is equivalent to using plot
on an RWDiffable
arrow.
paramPlot :: (forall m. (WithField ℝ PseudoAffine m, SimpleSpace (Needle m)) => AgentVal (-->) m ℝ -> (AgentVal (-->) m ℝ, AgentVal (-->) m ℝ)) -> DynamicPlottable Source #
Plot a continuous, “parametric function”, i.e. mapping the real line to a path in ℝ².
continFnPlot :: (Double -> Double) -> DynamicPlottable Source #
Plot an (assumed continuous) function in the usual way.
Since this uses functions of actual Double
values, you have more liberty
of defining functions with range-pattern-matching etc., which is at the moment
not possible in the :-->
category.
However, because Double
can't really prove properties of a mathematical
function, aliasing and similar problems are not taken into account. So it only works
accurately when the function is locally linear on pixel scales (what most
other plot programs just assume silently). In case of singularities, the
naïve thing is done (extend as far as possible; vertical line at sign change),
which again is common enough though not really right.
We'd like to recommend using fnPlot
whenever possible, which automatically adjusts
the resolution so the plot is guaranteed accurate (but it's not usable yet for
a lot of real applications).
tracePlot :: [(Double, Double)] -> DynamicPlottable Source #
Plot a sequence of points (x,y)
. The appearance of the plot will be automatically
chosen to match resolution and point density: at low densities, each point will simply
get displayed on its own. When the density goes so high you couldn't distinguish
individual points anyway, we switch to a “trace view”, approximating
the probability density function around a “local mean path”, which is
rather more insightful (and much less obstructive/clunky) than a simple cloud of
independent points.
In principle, this should be able to handle vast amounts of data (so you can, say, directly plot an audio file); at the moment the implementation isn't efficient enough and will get slow for more than some 100000 data points.
lineSegPlot :: [(Double, Double)] -> DynamicPlottable Source #
Simply connect the points by straight line segments, in the given order.
Beware that this will always slow down the performance when the list is large;
there is no &201d; as in tracePlot
.
linregressionPlot :: forall x m y. (SimpleSpace m, Scalar m ~ ℝ, y ~ ℝ, x ~ ℝ) => (x -> m +> y) -> [(x, Shade' y)] -> (Shade' m -> DynamicPlottable -> DynamicPlottable -> DynamicPlottable) -> DynamicPlottable Source #
colourPaintPlot :: ((Double, Double) -> Maybe (Colour Double)) -> DynamicPlottable Source #
Plot a function that assigns every point in view a colour value.
> plotWindow [colourPaintPlot $ (x,y) -> case (x^2+y^2, atan2 y x) of (r,φ) -> guard (sin (7*φ-2*r) > r) >> Just (Dia.blend (tanh r) Dia.red Dia.green), unitAspect ]
We try to evaluate that function no more often than necessary, but since it's a plain function with no differentiability information there's only so much that can be done; this requires a tradeoff between rasterisation fineness and performance. It works well for simple, smooth functions, but may not be adequate for functions with strong edges/transients, nor for expensive to compute functions.
type PlainGraphicsR2 = Diagram B Source #
Use plot
to directly include any Diagram
.
(All DynamicPlottable
is internally rendered to that type.)
The exact type may change in the future: we'll probably stay with diagrams
,
but when document output is introduced the backend might become variable
or something else but Cairo
.
shapePlot :: PlainGraphicsR2 -> DynamicPlottable Source #
Use a generic diagram within a plot.
Like with the various specialised function plotters, this will get automatically
tinted to be distinguishable from other plot objects in the same window.
Use diagramPlot
instead, if you want to view the diagram as-is.
diagramPlot :: PlainGraphicsR2 -> DynamicPlottable Source #
Plot a generic Diagram
.
Multiple objects in one plot
plotMultiple :: Plottable x => [x] -> DynamicPlottable Source #
Combine multiple objects in a single plot. Each will get an individual tint
(if applicable). This is also the default behaviour of plotWindow
.
To plot a family objects all with the same (but automatically-chosen) tint,
simply use plot
on the list, or combine them monoidally with <>
.
Computation in progress
plotLatest :: Plottable x => [x] -> DynamicPlottable Source #
Lazily consume the list, always plotting the latest value available as they
arrive.
Useful for displaying results of expensive computations that iteratively improve
some result, but also for making simple animations (see plotDelay
).
Plot-object attributes
Colour
tint :: Colour ℝ -> DynamicPlottable -> DynamicPlottable Source #
Colour this plot object in a fixed shade.
autoTint :: DynamicPlottable -> DynamicPlottable Source #
Allow the object to be automatically assigned a colour that's otherwise unused in the plot. (This is the default for most plot objects.)
Legend captions
legendName :: String -> DynamicPlottable -> DynamicPlottable Source #
Set the caption for this plot object that should appear in the plot legend.
plotLegendPrerender :: LegendDisplayConfig -> [DynamicPlottable] -> IO (Maybe PlainGraphicsR2) Source #
Render the legend (if any) belonging to a collection of plottable objects.
Animation
plotDelay :: NominalDiffTime -> DynamicPlottable -> DynamicPlottable Source #
Limit the refresh / frame rate for this plot object. Useful to slowly
study some sequence of plots with plotLatest
, or to just reduce processor load.
Note: the argument will probably change to NominalDiffTime from the thyme library soon.
freezeAnim :: DynamicPlottable -> DynamicPlottable Source #
Disable an animation, i.e. take an animated plot and show only the first frame.
startFrozen :: DynamicPlottable -> DynamicPlottable Source #
Wait with starting the animation until the user has clicked on it.
Viewport
View selection
xInterval :: (Double, Double) -> DynamicPlottable Source #
When you “plot” xInterval
/ yInterval
, it is ensured that the (initial) view encompasses
(at least) the specified range.
Note there is nothing special about these “flag” objects: any Plottable
can request a
certain view, e.g. for a discrete point cloud it's obvious and a function defines at least
a y
-range for a given x
-range. Only use explicit range when necessary.
forceXRange :: (Double, Double) -> DynamicPlottable Source #
Like xInterval
, this only affects what range is plotted. However, it doesn't merely
request that a certain interval should be visible, but actually enforces particular
values for the left and right boundary. Nothing outside the range will be plotted
(unless there is another, contradicting forceXRange
).
forceYRange :: (Double, Double) -> DynamicPlottable Source #
unitAspect :: DynamicPlottable Source #
Require that both coordinate axes are zoomed the same way, such that e.g. the unit circle will appear as an actual circle.
Interactive content
MouseClicks
, ViewXCenter
, ViewYResolution
etc. can be used as arguments to some object
you plot
, if you want to plot stuff that depends on user interaction
or just on the screen's visible range, for instance to calculate a tangent
at the middle of the screen:
plotWindow [fnPlot sin, plot $ \(ViewXCenter xc) x -> sin xc + (x-xc) * cos xc]
newtype MousePressed Source #
MousePressed | |
|
Plottable p => Plottable (MousePressed -> p) Source # | |
newtype MousePress Source #
MousePress | |
|
Plottable p => Plottable (MousePress -> p) Source # | |
newtype MouseClicks Source #
MouseClicks | |
|
Plottable p => Plottable (MouseClicks -> p) Source # | |
clickThrough :: Plottable p => [p] -> DynamicPlottable Source #
Move through a sequence of plottable objects, switching to the next
whenever a click is received anywhere on the screen. Similar to plotLatest
,
but does not proceed automatically.
withDraggablePoints :: forall p list. (Plottable p, Traversable list) => list (ℝ, ℝ) -> (list (ℝ, ℝ) -> p) -> DynamicPlottable Source #
Plot something dependent on points that the user can interactively move around. The nearest point (Euclidean distance) is always picked to be dragged.
mouseInteractive :: Plottable p => (MouseEvent (ℝ, ℝ) -> s -> s) -> s -> (s -> p) -> DynamicPlottable Source #
data MouseEvent x Source #
Eq x => Eq (MouseEvent x) Source # | |
clickLocation :: forall x. Lens' (MouseEvent x) x Source #
releaseLocation :: forall x. Lens' (MouseEvent x) x Source #
Displayed range
newtype ViewXCenter Source #
Plottable p => Plottable (ViewXCenter -> p) Source # | |
newtype ViewYCenter Source #
Plottable p => Plottable (ViewYCenter -> p) Source # | |
newtype ViewHeight Source #
Plottable p => Plottable (ViewHeight -> p) Source # | |
Resolution
newtype ViewXResolution Source #
newtype ViewYResolution Source #
Auxiliary plot objects
dynamicAxes :: DynamicPlottable Source #
Coordinate axes with labels. For many plottable objects, these will be added
automatically, by default (unless inhibited with noDynamicAxes
).
xAxisLabel :: String -> DynamicPlottable Source #
yAxisLabel :: String -> DynamicPlottable Source #
Types
The plot type
type DynamicPlottable = DynamicPlottable' RVar Source #
tweakPrerendered :: (PlainGraphicsR2 -> PlainGraphicsR2) -> DynamicPlottable -> DynamicPlottable Source #
Viewport choice
Resolution
Background
Output scaling
data PrerenderScaling Source #
ValuespaceScaling | The diagram has the original coordinates of the data that's plotted in it. E.g. if you've plotted an oscillation with amplitude 1e-4, the height of the plot will be indicated as only 0.0002. Mostly useful when you want to juxtapose multiple plots with correct scale matching. |
NormalisedScaling | The diagram is scaled to have a range of |
OutputCoordsScaling | Scaled to pixel coordinates, i.e. the x range is
|