Copyright | (c) 2025 |
---|---|
License | MIT |
Maintainer | mschavinda@gmail.com |
Stability | experimental |
Portability | POSIX |
Safe Haskell | None |
Language | GHC2021 |
Granite
Description
A terminal-based plotting library that renders beautiful charts using Unicode Braille characters and ANSI colors. Granite provides a variety of chart types including scatter plots, line graphs, bar charts, pie charts, histograms, heatmaps, and box plots.
Basic Usage
Create a simple scatter plot:
{-# LANGUAGE OverloadedStrings #-} import Granite import Data.Text.IO as T main = do let points = [(x, sin x) | x <- [0, 0.1 .. 6.28]] chart = scatter [series "sin(x)" points] defPlot T.putStrLn chart
Customization
Plots can be customized using record update syntax:
let customPlot = defPlot { widthChars = 80 , heightChars = 30 , plotTitle = "My Chart" , legendPos = LegendBottom }
Terminal Requirements
This library requires a terminal that supports:
- Unicode (specifically Braille patterns U+2800-U+28FF)
- ANSI color codes
- Monospace font with proper Braille character rendering
Synopsis
- data Plot = Plot {
- widthChars :: Int
- heightChars :: Int
- leftMargin :: Int
- bottomMargin :: Int
- titleMargin :: Int
- xBounds :: (Maybe Double, Maybe Double)
- yBounds :: (Maybe Double, Maybe Double)
- plotTitle :: Text
- legendPos :: LegendPos
- colorPalette :: [Color]
- xFormatter :: LabelFormatter
- yFormatter :: LabelFormatter
- xNumTicks :: Int
- yNumTicks :: Int
- defPlot :: Plot
- data LegendPos
- data Color
- = Default
- | Black
- | Red
- | Green
- | Yellow
- | Blue
- | Magenta
- | Cyan
- | White
- | BrightBlack
- | BrightRed
- | BrightGreen
- | BrightYellow
- | BrightBlue
- | BrightMagenta
- | BrightCyan
- | BrightWhite
- type LabelFormatter = AxisEnv -> Int -> Double -> Text
- data AxisEnv = AxisEnv {}
- series :: Text -> [(Double, Double)] -> (Text, [(Double, Double)])
- bins :: Int -> Double -> Double -> Bins
- data Bins = Bins {}
- histogram :: Bins -> [Double] -> Plot -> Text
- bars :: [(Text, Double)] -> Plot -> Text
- scatter :: [(Text, [(Double, Double)])] -> Plot -> Text
- pie :: [(Text, Double)] -> Plot -> Text
- stackedBars :: [(Text, [(Text, Double)])] -> Plot -> Text
- heatmap :: [[Double]] -> Plot -> Text
- lineGraph :: [(Text, [(Double, Double)])] -> Plot -> Text
- boxPlot :: [(Text, [Double])] -> Plot -> Text
Plot Configuration
Plot configuration parameters.
Controls the appearance and layout of generated charts.
Constructors
Plot | |
Fields
|
Default plot configuration.
Creates a 60×20 character plot with reasonable defaults:
defPlot = Plot { widthChars = 60 , heightChars = 20 , leftMargin = 6 , bottomMargin = 2 , titleMargin = 1 , xBounds = (Nothing, Nothing) , yBounds = (Nothing, Nothing) , plotTitle = "" , legendPos = LegendRight , colorPalette = [ BrightBlue, BrightMagenta, BrightCyan, BrightGreen, BrightYellow, BrightRed, BrightWhite, BrightBlack] , xFormatter = _ _ v -> show v , yFormatter = _ _ v -> show v , xNumTicks = 2 , yNumTicks = 2 }
Position of the legend in the plot.
Constructors
LegendRight | Display legend on the right side of the plot |
LegendBottom | Display legend below the plot |
LegendNone | Do not display legend. |
Formatting
Supported ANSI colo(u)rs.
type LabelFormatter Source #
Arguments
= AxisEnv | Axis context (domain, tick index/count, etc) |
-> Int | Slot width budget in characters for this tick. |
-> Double | Raw data value for the tick |
-> Text | Rendered label (if it doesn't fit in the slot it will be truncated) |
Axis-aware, width-limited, tick-label formatter.
Given: * axis context * a per-tick width budget (in terminal cells) * and the raw tick value. returns the label to render.
What the formatter gets to know about the axis/ticks
Data Preparation
Arguments
:: Text | Name of the series (appears in legend) |
-> [(Double, Double)] | List of (x, y) data points |
-> (Text, [(Double, Double)]) |
Create a named data series for multi-series plots.
let s1 = series "Dataset A" [(1,2), (2,4), (3,6)] s2 = series "Dataset B" [(1,3), (2,5), (3,7)] chart = scatter [s1, s2] defPlot
bins :: Int -> Double -> Double -> Bins Source #
Create a bin configuration for histograms.
bins 10 0 100 -- 10 bins from 0 to 100 bins 20 (-5) 5 -- 20 bins from -5 to 5
Defines the binning parameters.
Chart Types
Arguments
:: Bins | Binning configuration |
-> [Double] | Raw data values to bin |
-> Plot | Plot configuration |
-> Text | Rendered chart as Text |
Create a histogram from numerical data.
Data is binned according to the provided Bins
configuration.
Example
import System.Random -- Generate random normal-like distribution let values = take 1000 $ randomRs (0, 100) gen chart = histogram (bins 20 0 100) values defPlot
Arguments
:: [(Text, [(Double, Double)])] | List of named data series |
-> Plot | Plot configuration |
-> Text | Rendered chart as Text |
Create a scatter plot from multiple data series.
Each series is rendered with a different color and pattern. Points are plotted using Braille characters for sub-character resolution.
Example
let points1 = [(x, x^2) | x <- [-3, -2.5 .. 3]] points2 = [(x, 2*x + 1) | x <- [-3, -2.5 .. 3]] chart = scatter [series "y = x²" points1, series "y = 2x + 1" points2] defPlot
Arguments
:: [[Double]] | 2D matrix of values (rows × columns) |
-> Plot | Plot configuration |
-> Text | Rendered chart as Text |
Create a heatmap visualization of a 2D matrix.
Values are mapped to a color gradient from blue (low) to red (high).
Example
let matrix = [[x * y | x <- [1..10]] | y <- [1..10]] chart = heatmap matrix defPlot { plotTitle = "Multiplication Table" }
Arguments
:: [(Text, [(Double, Double)])] | List of named data series |
-> Plot | Plot configuration |
-> Text | Rendered chart as Text |
Create a line graph connecting data points.
Similar to scatter
but connects consecutive points with lines.
Points are automatically sorted by x-coordinate before connecting.
Example
let sine = [(x, sin x) | x <- [0, 0.1 .. 2*pi]] cosine = [(x, cos x) | x <- [0, 0.1 .. 2*pi]] chart = lineGraph [series "sin" sine, series "cos" cosine] defPlot
Create a box plot showing statistical distributions.
Displays quartiles, median, and min/max values for each dataset.
Example
let data1 = [1.2, 2.3, 2.1, 3.4, 2.8, 4.1, 3.9] data2 = [5.1, 4.8, 6.2, 5.9, 7.1, 6.5, 5.5] chart = boxPlot [("Group A", data1), ("Group B", data2)] defPlot
The box plot displays:
- Box: First quartile (Q1) to third quartile (Q3)
- Line inside box: Median (Q2)
- Whiskers: Minimum and maximum values