granite-0.3.0.4: Easy terminal plotting.
Copyright(c) 2024
LicenseBSD3
Maintaineryour-email@example.com
Stabilityexperimental
PortabilityPOSIX
Safe HaskellNone
LanguageGHC2021

Granite.String

Description

A String-based interface to the Granite plotting library. This module provides the same functionality as Granite but uses String instead of Text for easier use in simple scripts and educational contexts.

Basic Usage

Create a simple scatter plot:

import Granite.String

main = do
  let points = [(x, sin x) | x <- [0, 0.1 .. 6.28]]
      chart = scatter [series "sin(x)" points] defPlot
  putStrLn chart

Note on Performance

This module internally converts between String and Text. For performance-critical applications with large datasets, consider using the Granite module directly which works with Text natively.

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

Plot Configuration

data Plot Source #

Plot configuration parameters.

Controls the appearance and layout of generated charts.

Constructors

Plot 

Fields

defPlot :: Plot Source #

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   = _ d -> show d
  , yFormatter   = _ d -> show d
  , xNumTicks    = 2
  , yNumTicks    = 2
  }

Data Preparation

series Source #

Arguments

:: String

Name of the series (appears in legend)

-> [(Double, Double)]

List of (x, y) data points

-> (String, [(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

data LegendPos Source #

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.

Instances

Instances details
Show LegendPos Source # 
Instance details

Defined in Granite

Eq LegendPos Source # 
Instance details

Defined in Granite

data Color Source #

Supported ANSI colo(u)rs.

Instances

Instances details
Show Color Source # 
Instance details

Defined in Granite

Methods

showsPrec :: Int -> Color -> ShowS #

show :: Color -> String #

showList :: [Color] -> ShowS #

Eq Color Source # 
Instance details

Defined in Granite

Methods

(==) :: Color -> Color -> Bool #

(/=) :: Color -> Color -> Bool #

data AxisEnv Source #

What the formatter gets to know about the axis/ticks

Constructors

AxisEnv 

Fields

data Bins Source #

Defines the binning parameters.

Instances

Instances details
Show Bins Source # 
Instance details

Defined in Granite

Methods

showsPrec :: Int -> Bins -> ShowS #

show :: Bins -> String #

showList :: [Bins] -> ShowS #

Eq Bins Source # 
Instance details

Defined in Granite

Methods

(==) :: Bins -> Bins -> Bool #

(/=) :: Bins -> Bins -> Bool #

bins Source #

Arguments

:: Int

Number of bins (will be clamped to minimum 1)

-> Double

Lower bound

-> Double

Upper bound

-> Bins 

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

Formatting

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

-> String

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.

Chart Types

scatter Source #

Arguments

:: [(String, [(Double, Double)])]

List of named data series

-> Plot

Plot configuration

-> String

Rendered chart as String

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

Expand
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

lineGraph Source #

Arguments

:: [(String, [(Double, Double)])]

List of named data series

-> Plot

Plot configuration

-> String

Rendered chart as String

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

Expand
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

bars Source #

Arguments

:: [(String, Double)]

List of (category, value) pairs

-> Plot

Plot configuration

-> String

Rendered chart as String

Create a bar chart from categorical data.

Each bar is colored differently and labeled with its category name.

Example

Expand
let data = [(Apple, 45.2), (Banana, 38.1), (Orange, 52.7)]
    chart = bars data defPlot { plotTitle = "Fruit Sales" }

stackedBars Source #

Arguments

:: [(String, [(String, Double)])]

Categories with stacked components

-> Plot

Plot configuration

-> String

Rendered chart as String

Create a stacked bar chart.

Each category can have multiple stacked components.

Example

Expand
let data = [(Q1, [("Product A", 100), ("Product B", 150)]),
            (Q2, [("Product A", 120), ("Product B", 180)])]
    chart = stackedBars data defPlot

histogram Source #

Arguments

:: Bins

Binning configuration

-> [Double]

Raw data values to bin

-> Plot

Plot configuration

-> String

Rendered chart as String

Create a histogram from numerical data.

Data is binned according to the provided Bins configuration.

Example

Expand
import System.Random

-- Generate random normal-like distribution
let values = take 1000 $ randomRs (0, 100) gen
    chart = histogram (bins 20 0 100) values defPlot

pie Source #

Arguments

:: [(String, Double)]

List of (category, value) pairs

-> Plot

Plot configuration

-> String

Rendered chart as String

Create a pie chart showing proportions.

Values are normalized to sum to 100%. Negative values are treated as zero.

Example

Expand
let data = [(Chrome, 65), (Firefox, 20), (Safari, 10), (Other, 5)]
    chart = pie data defPlot { plotTitle = "Browser Market Share" }

heatmap Source #

Arguments

:: [[Double]]

2D matrix of values (rows × columns)

-> Plot

Plot configuration

-> String

Rendered chart as String

Create a heatmap visualization of a 2D matrix.

Values are mapped to a color gradient from blue (low) to red (high).

Example

Expand
let matrix = [[x * y | x <- [1..10]] | y <- [1..10]]
    chart = heatmap matrix defPlot { plotTitle = "Multiplication Table" }

boxPlot Source #

Arguments

:: [(String, [Double])]

Named datasets

-> Plot

Plot configuration

-> String

Rendered chart as String

Create a box plot showing statistical distributions.

Displays quartiles, median, and min/max values for each dataset.

Example

Expand
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