plots-0.1.1.3: Diagrams based plotting library
Copyright(C) 2016 Christopher Chalmers
LicenseBSD-style (see the file LICENSE)
MaintainerChristopher Chalmers
Stabilityexperimental
Portabilitynon-portable
Safe HaskellSafe-Inferred
LanguageHaskell2010

Plots.Types.HeatMap

Description

A heat map is a graphical representation of data where the individual values contained in a matrix are represented as colours.

(see heatMapIndexed example for code to make this plot)

Synopsis

Heat map

data HeatMap b n Source #

A mapping from points in a 2D axis do Doubles. These Doubles are converted to colours using the axis ColourMap.

Instances

Instances details
HasHeatMap f (HeatMap b n) b Source # 
Instance details

Defined in Plots.Types.HeatMap

OrderedField n => Enveloped (HeatMap b n) Source # 
Instance details

Defined in Plots.Types.HeatMap

Methods

getEnvelope :: HeatMap b n -> Envelope (V (HeatMap b n)) (N (HeatMap b n)) #

(Typeable b, TypeableFloat n, Renderable (Path V2 n) b) => Plotable (HeatMap b n) b Source # 
Instance details

Defined in Plots.Types.HeatMap

Methods

renderPlotable :: forall (v :: Type -> Type) n0. InSpace v n0 (HeatMap b n) => AxisSpec v n0 -> PlotStyle b v n0 -> HeatMap b n -> QDiagram b v n0 Any Source #

defLegendPic :: forall (v :: Type -> Type) n0. InSpace v n0 (HeatMap b n) => PlotStyle b v n0 -> HeatMap b n -> QDiagram b v n0 Any Source #

type N (HeatMap b n) Source # 
Instance details

Defined in Plots.Types.HeatMap

type N (HeatMap b n) = n
type V (HeatMap b n) Source # 
Instance details

Defined in Plots.Types.HeatMap

type V (HeatMap b n) = V2

heatMap Source #

Arguments

:: (Foldable f, Foldable g, TypeableFloat n, Typeable b, MonadState (Axis b V2 n) m, Renderable (Path V2 n) b) 
=> f (g Double) 
-> State (Plot (HeatMap b n) b) ()

changes to plot options

-> m ()

add plot to Axis

Add a HeatMap plot using the extent of the heatmap and a generating function.

heatMap :: [[Double]] -> State (Plot (HeatMap b n)) () -> State (Axis b V2 n) ()

Example

Expand

import Plots
heatMapAxis :: Axis B V2 Double
heatMapAxis = r2Axis &~ do
  display colourBar
  axisExtend .= noExtend

  let xs = [[1,2,3],[4,5,6]]
  heatMap xs $ heatMapSize .= V2 10 10
heatMapExample = renderAxis heatMapAxis

heatMap' Source #

Arguments

:: (Foldable f, Foldable g, TypeableFloat n, Typeable b, MonadState (Axis b V2 n) m, Renderable (Path V2 n) b) 
=> f (g Double) 
-> m ()

add plot to Axis

Add a HeatMap plot using the extent of the heatmap and a generating function.

heatMap' :: [[Double]] -> State (Axis b V2 n) ()

Example

Expand

import Plots
heatMapAxis' :: Axis B V2 Double
heatMapAxis' = r2Axis &~ do
  display colourBar
  axisExtend .= noExtend
  axisColourMap .= Plots.magma

  let xs = [[1,2,3],[4,5,6]]
  heatMap' xs
heatMapExample' = renderAxis heatMapAxis'

heatMapIndexed Source #

Arguments

:: (VectorLike V2 Int i, TypeableFloat n, Typeable b, MonadState (Axis b V2 n) m, Renderable (Path V2 n) b) 
=> i

extent of array

-> (i -> Double)

heat from index

-> State (Plot (HeatMap b n) b) ()

changes to plot options

-> m ()

add plot to Axis

Add a HeatMap plot using the extent of the heatmap and a generating function.

heatMapIndexed :: V2 Int     -> (V2 Int -> Double)     -> State (Plot (HeatMap b n)) () -> State (Axis b V2 n) ()
heatMapIndexed :: (Int, Int) -> ((Int, Int) -> Double) -> State (Plot (HeatMap b n)) () -> State (Axis b V2 n) ()

Example

Expand

import Plots
heatMapIndexedAxis :: Axis B V2 Double
heatMapIndexedAxis = r2Axis &~ do
  display colourBar
  axisExtend .= noExtend

  let f (V2 x y) = fromIntegral x + fromIntegral y
  heatMapIndexed (V2 3 3) f $ heatMapSize .= V2 10 10
heatMapIndexedExample = renderAxis heatMapIndexedAxis

heatMapIndexed' Source #

Arguments

:: (VectorLike V2 Int i, TypeableFloat n, Typeable b, MonadState (Axis b V2 n) m, Renderable (Path V2 n) b) 
=> i

extent of array

-> (i -> Double)

heat from index

-> m ()

add plot to Axis

Add a HeatMap plot using the extent of the heatmap and a generating function without changes to the heap map options.

heatMapIndexed :: V2 Int     -> (V2 Int -> Double)     -> State (Axis b V2 n) ()
heatMapIndexed :: (Int, Int) -> ((Int, Int) -> Double) -> State (Axis b V2 n) ()

Example

Expand

import Plots
heatMapIndexedAxis' :: Axis B V2 Double
heatMapIndexedAxis' = r2Axis &~ do
  display colourBar
  axisExtend .= noExtend
  axisColourMap .= Plots.magma

  let f (V2 x y) = fromIntegral x + fromIntegral y
  heatMapIndexed' (V2 3 3) f
heatMapIndexedExample' = renderAxis heatMapIndexedAxis'

Lenses

class HasHeatMap f a b | a -> b where Source #

Class of things that let you change the heatmap options.

Minimal complete definition

heatMapOptions

Methods

heatMapOptions :: LensLike' f a (HeatMap b (N a)) Source #

Lens onto the heatmap options.

heatMapGridVisible :: Functor f => LensLike' f a Bool Source #

Whether there should be grid lines draw for the heat map.

Default is False.

heatMapGridStyle :: Functor f => LensLike' f a (Style V2 (N a)) Source #

The style applied to the grid lines for the heat map, if they're visible.

Default is mempty.

heatMapSize :: Functor f => LensLike' f a (V2 (N a)) Source #

The size of each individual square in the heat map.

Default is V2 1 1.

heatMapExtent :: (Functor f, Fractional (N a)) => LensLike' f a (V2 (N a)) Source #

The size of the full extent of the heat map.

Default is extent of the heat matrix.

heatMapStart :: Functor f => LensLike' f a (P2 (N a)) Source #

The starting point at the bottom left corner of the heat map.

Default is origin

heatMapCentre :: (Functor f, Fractional (N a)) => LensLike' f a (P2 (N a)) Source #

The center point of the heat map.

heatMapLimits :: Functor f => LensLike' f a (Maybe (Double, Double)) Source #

Limits (a,b) used on the data such that a is the start of the ColourMap and b is the end of the ColourMap. Default is (0,1).

heatMapRender :: Functor f => LensLike' f a (HeatMatrix -> ColourMap -> QDiagram b V2 (N a) Any) Source #

Funtion used to render the heat map. See pathHeatRender and pixelHeatRender.

Default is pathHeatRender.

Instances

Instances details
(Functor f, HasHeatMap f a b) => HasHeatMap f (Plot a b) b Source # 
Instance details

Defined in Plots.Types.HeatMap

HasHeatMap f (HeatMap b n) b Source # 
Instance details

Defined in Plots.Types.HeatMap

Rendering functions

pathHeatRender :: (Renderable (Path V2 n) b, TypeableFloat n) => HeatMatrix -> ColourMap -> QDiagram b V2 n Any Source #

Render the heat map as a collection squares made up of Trails. This method is compatible with all backends and should always look sharp. However it can become slow and large for large heat maps.

It is recommended to use pathHeatRender for small heat maps and pixelHeatRender for larger ones.

Example

Expand

import Plots

pathHeatRenderExample =
  let f (V2 x y) = fromIntegral x + fromIntegral y
      myHM       = mkHeatMatrix (V2 5 5) f
  in  pathHeatRender myHM viridis

pixelHeatRender :: (Renderable (DImage n Embedded) b, TypeableFloat n) => HeatMatrix -> ColourMap -> QDiagram b V2 n Any Source #

Render an heatmap as an ImageRGB8.

Example

Expand

import Plots

pixelHeatRenderExample =
  let f (V2 x y) = fromIntegral x + fromIntegral y
      myHM       = mkHeatMatrix (V2 5 5) f
  in  pixelHeatRender myHM viridis

pixelHeatRender' :: (Renderable (DImage n Embedded) b, TypeableFloat n) => Int -> HeatMatrix -> ColourMap -> QDiagram b V2 n Any Source #

Render an heatmap as an ImageRGB8 with n pixels per heat matrix point.

Example

Expand

import Plots

pixelHeatRenderExample' =
  let f (V2 x y) = fromIntegral x + fromIntegral y
      myHM       = mkHeatMatrix (V2 5 5) f
  in  pixelHeatRender' 10 myHM viridis

Heat matrix

data HeatMatrix Source #

2D Array of Doubles.

heatImage :: HeatMatrix -> ColourMap -> Image PixelRGB8 Source #

Create an image of PixelsRGB8 using the heat matrix.

hmPoints :: IndexedTraversal' (V2 Int) HeatMatrix Double Source #

Indexed traversal over the values of a HeatMatrix.

hmSize :: HeatMatrix -> V2 Int Source #

The size of heat matrix.

Low level construction

mkHeatMap :: (Renderable (Path V2 n) b, TypeableFloat n) => HeatMatrix -> HeatMap b n Source #

Construct a Heatmap using the given HeatMatrix.

mkHeatMatrix :: V2 Int -> (V2 Int -> Double) -> HeatMatrix Source #

Construct a heat matrix from a size and a generating function.

mkHeatMatrix' :: (Foldable f, Foldable g) => f (g Double) -> HeatMatrix Source #

Construct a heat matrix from a foldable of foldables.

mkHeatMatrix' :: [[Double]] -> HeatMatrix
mkHeatMatrix' :: [Vector Double] -> HeatMatrix