[Chart] Horizontal Bar Charts

Tim Docker tim at dockerz.net
Wed Feb 26 18:59:13 GMT 2014


Hi.

Unfortunately there is no simple way currently. Given that the type of a bar chart is currently:

data PlotBars x y = PlotBars {
    ...
    _plot_bars_values          :: [ (x,[y]) ]
}

one possibility would be an alternative type for a horizontal bar chart:

data PlotHBars x y = PlotHBars {
    ...
    _plot_hbars_values          :: [ (y,[x]) ]
}

which would (presumably) reuse much of the existing vertical bars implementation.

Tim

On 27/02/2014, at 5:12 AM, trevor cook <trevor.j.cook at gmail.com> wrote:

> Hi All,
> 
> Is there a simple way to make a horizontal bar chart using Charts-1.2? I can't find any obvious solution in the library documentation. How would I make example 11 from the wiki (pasted below) into a horizontal chart?
> 
> Thanks,
> Trevor
> 
> 
>   
> import Graphics.Rendering.Chart
> import Graphics.Rendering.Chart.Backend.Cairo
> import Data.Colour
> import Data.Colour.Names
> import Data.Default.Class
> import Control.Lens
> import System.Environment(getArgs)
> 
> chart borders = toRenderable layout
>  where
>   layout = 
>         layout_title .~ "Sample Bars" ++ btitle
>       $ layout_title_style . font_size .~ 10
>       $ layout_x_axis . laxis_generate .~ autoIndexAxis alabels
>       $ layout_y_axis . laxis_override .~ axisGridHide
>       $ layout_left_axis_visibility . axis_show_ticks .~ False
>       $ layout_plots .~ [ plotBars bars2 ]
>       $ def :: Layout PlotIndex Double
> 
>   bars2 = plot_bars_titles .~ ["Cash","Equity"]
> √      $ plot_bars_values .~ addIndexes [[20,45],[45,30],[30,20],[70,25]]
>       $ plot_bars_style .~ BarsClustered
>       $ plot_bars_spacing .~ BarsFixGap 30 5
>       $ plot_bars_item_styles .~ map mkstyle (cycle defaultColorSeq)
>       $ def
> 
>   alabels = [ "Jun", "Jul", "Aug", "Sep", "Oct" ]
> 
>   btitle = if borders then "" else " (no borders)"
>   bstyle = if borders then Just (solidLine 1.0 $ opaque black) else Nothing
>   mkstyle c = (solidFillStyle c, bstyle)
> 
> main = renderableToFile def (chart True) "example11_big.png"
> _______________________________________________
> Chart mailing list
> Chart at projects.haskell.org
> http://projects.haskell.org/cgi-bin/mailman/listinfo/chart




More information about the Chart mailing list