Copyright | (C) 2016 Christopher Chalmers |
---|---|
License | BSD-style (see the file LICENSE) |
Maintainer | Christopher Chalmers |
Stability | experimental |
Portability | non-portable |
Safe Haskell | None |
Language | Haskell2010 |
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
- data HeatMap v
- heatMap :: (Foldable f, Foldable g, MonadState (Axis V2) m) => f (g Double) -> State (Plot (HeatMap V2)) () -> m ()
- heatMap' :: (Foldable f, Foldable g, MonadState (Axis V2) m) => f (g Double) -> m ()
- heatMapIndexed :: (VectorLike V2 Int i, MonadState (Axis V2) m) => i -> (i -> Double) -> State (Plot (HeatMap V2)) () -> m ()
- heatMapIndexed' :: (VectorLike V2 Int i, MonadState (Axis V2) m) => i -> (i -> Double) -> m ()
- class HasHeatMap f a where
- heatMapOptions :: LensLike' f a (HeatMap (V a))
- heatMapGridVisible :: Functor f => LensLike' f a Bool
- heatMapGridStyle :: Functor f => LensLike' f a (Style (V a) Double)
- heatMapSize :: Functor f => LensLike' f a (V2 Double)
- heatMapExtent :: Functor f => LensLike' f a (V2 Double)
- heatMapStart :: Functor f => LensLike' f a (P2 Double)
- heatMapCentre :: Functor f => LensLike' f a (P2 Double)
- heatMapLimits :: Functor f => LensLike' f a (Maybe (Double, Double))
- heatMapRender :: Functor f => LensLike' f a (HeatMatrix -> ColourMap -> Diagram (V a))
- pathHeatRender :: HeatMatrix -> ColourMap -> Diagram V2
- pixelHeatRender :: HeatMatrix -> ColourMap -> Diagram V2
- pixelHeatRender' :: Int -> HeatMatrix -> ColourMap -> Diagram V2
- data HeatMatrix = HeatMatrix {
- hmSize :: !(V2 Int)
- _hmVector :: !(Vector Double)
- hmBoundLower :: !Double
- hmBoundUpper :: !Double
- heatImage :: HeatMatrix -> ColourMap -> Image PixelRGB8
- hmPoints :: IndexedTraversal' (V2 Int) HeatMatrix Double
- mkHeatMap :: HeatMatrix -> HeatMap V2
- mkHeatSurface :: HeatMatrix -> HeatMap V3
- mkHeatMatrix :: V2 Int -> (V2 Int -> Double) -> HeatMatrix
- mkHeatMatrix' :: (Foldable f, Foldable g) => f (g Double) -> HeatMatrix
Heat map
A mapping from points in a 2D axis do Double
s. These Double
s
are converted to colours using the axis ColourMap
.
Instances
:: (Foldable f, Foldable g, MonadState (Axis V2) m) | |
=> f (g Double) | |
-> State (Plot (HeatMap V2)) () | changes to plot options |
-> m () | add plot to |
Add a HeatMap
plot using the extent of the heatmap and a
generating function.
heatMap
:: [[Double
]] ->State
(Plot
(HeatMap
b n)) () ->State
(Axis
bV2
n) ()
Example
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
Add a HeatMap
plot using the extent of the heatmap and a
generating function.
heatMap'
:: [[Double
]] ->State
(Axis
bV2
n) ()
Example
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'
:: (VectorLike V2 Int i, MonadState (Axis V2) m) | |
=> i | extent of array |
-> (i -> Double) | heat from index |
-> State (Plot (HeatMap V2)) () | changes to plot options |
-> m () | add plot to |
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
bV2
n) ()heatMapIndexed
:: (Int
,Int
) -> ((Int
,Int
) ->Double
) ->State
(Plot
(HeatMap
b n)) () ->State
(Axis
bV2
n) ()
Example
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
:: (VectorLike V2 Int i, MonadState (Axis V2) m) | |
=> i | extent of array |
-> (i -> Double) | heat from index |
-> m () | add plot to |
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
bV2
n) ()heatMapIndexed
:: (Int
,Int
) -> ((Int
,Int
) ->Double
) ->State
(Axis
bV2
n) ()
Example
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 where Source #
Class of things that let you change the heatmap options.
heatMapOptions :: LensLike' f a (HeatMap (V 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 (V a) Double) 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 Double) Source #
The size of each individual square in the heat map.
Default is
.V2
1 1
heatMapExtent :: Functor f => LensLike' f a (V2 Double) 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 Double) Source #
The starting point at the bottom left corner of the heat map.
Default is origin
heatMapCentre :: Functor f => LensLike' f a (P2 Double) 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 -> Diagram (V a)) Source #
Funtion used to render the heat map. See pathHeatRender
and
pixelHeatRender
.
Default is pathHeatRender
.
Instances
Rendering functions
pathHeatRender :: HeatMatrix -> ColourMap -> Diagram V2 Source #
Render the heat map as a collection squares made up of Trail
s.
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
import Plots pathHeatRenderExample = let f (V2 x y) = fromIntegral x + fromIntegral y myHM = mkHeatMatrix (V2 5 5) f in pathHeatRender myHM viridis
pixelHeatRender :: HeatMatrix -> ColourMap -> Diagram V2 Source #
Render an heatmap as an ImageRGB8
.
Example
import Plots pixelHeatRenderExample = let f (V2 x y) = fromIntegral x + fromIntegral y myHM = mkHeatMatrix (V2 5 5) f in pixelHeatRender myHM viridis
pixelHeatRender' :: Int -> HeatMatrix -> ColourMap -> Diagram V2 Source #
Render an heatmap as an ImageRGB8
with n
pixels per heat matrix
point.
Example
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 Double
s.
HeatMatrix | |
|
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
.
Low level construction
mkHeatMap :: HeatMatrix -> HeatMap V2 Source #
Construct a HeatMap
using the given HeatMatrix
.
mkHeatSurface :: HeatMatrix -> HeatMap V3 Source #
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