ansigraph-0.3.0.5: Terminal-based graphing via ANSI and Unicode

Safe HaskellSafe
LanguageHaskell2010

System.Console.Ansigraph.Core

Contents

Description

This module provides the core functionality of the ansigraph package: terminal-based graphing for vectors and matrices of real and complex numbers.

This is implemented via a Graphable type class.

Ansigraph is intended to be used in on of two ways:

  • By importing System.Console.Ansigraph. This provides all the functionality we typically use, including the FlexibleInstances extension which makes it easier to use graphing functions by allowing instances like 'Graphable [Double]'.
  • By directly importing System.Console.Ansigraph.Core, which does not activate FlexibleInstances but includes everything else provided by the other module. This just means you must use one of a few newtype wrappers, namely: Graph, PosGraph, CGraph, Mat, CMat. They are also available from the standard module.

Synopsis

Core Functionality

The Graphable class

class Graphable a where Source #

Things that ansigraph knows how to render at the terminal are instances of this class.

In general, when ANSI codes are involved, a graphWith method should fush stdout when finished, and whenever codes are invoked to i.e. change terminal colors. This is easily handled by defining it in terms of colorStr and colorStrLn.

The graphHeight function specifies how many vertical lines a graph occupies and is needed for animations to work properly

Minimal complete definition

graphWith, graphHeight

Methods

graphWith :: MonadIO m => GraphSettings -> a -> m () Source #

Render a graph to standard output.

graphHeight :: a -> Int Source #

The number of vertical lines a graph occupies.

graph :: MonadIO m => Graphable a => a -> m () Source #

Invokes the Graphable type class method graphWith with the default GraphSettings record, graphDefaults.

animateWith :: MonadIO m => Graphable a => GraphSettings -> [a] -> m () Source #

Any list of a Graphable type can be made into an animation, by graphing each element with a time delay and screen-clear after each. GraphSettings are used to determine the time delta and any coloring/scaling options.

animate :: MonadIO m => Graphable a => [a] -> m () Source #

Perform animateWith using default options. Equivalent to graphing each member of the supplied list with a short delay and screen-clear after each.

transientAnim :: (MonadIO m, Graphable a) => [a] -> m () Source #

Like animate, only it does not leave the final frame of the animation visible.

transientAnimWith :: MonadIO m => Graphable a => GraphSettings -> [a] -> m () Source #

Like animateWith, only it does not leave the final frame of the animation visible.

Graphing options

data GraphSettings Source #

Record that holds graphing options.

Constructors

GraphSettings 

Fields

Default options

graphDefaults :: GraphSettings Source #

Default graph settings.

blue :: AnsiColor Source #

Vivid Blue – used as the default real foreground color.

pink :: AnsiColor Source #

Vivid Magenta – used as the default foreground color for imaginary graph component.

white :: AnsiColor Source #

Vivid White – used as the default graph background color for both real and imaginary graph components.

red :: AnsiColor Source #

Vivid Red – used as the default foreground color for negative real component.

green :: AnsiColor Source #

Dull Green – used as the default foreground color for negative imaginary component.

noColoring :: Coloring Source #

A Coloring representing default terminal colors, i.e. two Nothings.

ANSI data

Basic types from ANSI package

data Color :: * #

ANSI colors: come in various intensities, which are controlled by ColorIntensity

Constructors

Black 
Red 
Green 
Yellow 
Blue 
Magenta 
Cyan 
White 

data ColorIntensity :: * #

ANSI colors come in two intensities

Constructors

Dull 
Vivid 

Instances

Bounded ColorIntensity 
Enum ColorIntensity 
Eq ColorIntensity 
Ord ColorIntensity 
Read ColorIntensity 
Show ColorIntensity 
Ix ColorIntensity 

Custom composite data types

data AnsiColor Source #

ANSI colors are characterized by a Color and a ColorIntensity.

Constructors

AnsiColor 

data Coloring Source #

Holds two Maybe AnsiColors representing foreground and background colors for display via ANSI. Nothing means use the default terminal color.

ANSI helpers

mkColoring :: AnsiColor -> AnsiColor -> Coloring Source #

Helper constructor function for Coloring that takes straight AnsiColors without Maybe.

fromFG :: AnsiColor -> Coloring Source #

Easily create a Coloring by specifying the foreground AnsiColor and no custom background.

fromBG :: AnsiColor -> Coloring Source #

Easily create a Coloring by specifying the background AnsiColor and no custom foreground.

realColors :: GraphSettings -> Coloring Source #

Projection retrieving foreground and background colors for real number graphs in the form of a Coloring.

imagColors :: GraphSettings -> Coloring Source #

Projection retrieving foreground and background colors for imaginary component of complex number graphs in the form of a Coloring.

colorSets :: GraphSettings -> (Coloring, Coloring) Source #

Retrieves a pair of Colorings for real and imaginary graph components respectively.

invert :: Coloring -> Coloring Source #

Swaps foreground and background colors within a Coloring.

interpAnsiColor :: ConsoleLayer -> AnsiColor -> SGR Source #

The SGR command corresponding to a particular ConsoleLayer and AnsiColor.

setColor :: MonadIO m => ConsoleLayer -> AnsiColor -> m () Source #

Set the given AnsiColor on the given ConsoleLayer.

clear :: MonadIO m => m () Source #

Clear any SGR settings and then flush stdout.

clearLn :: MonadIO m => m () Source #

Clear any SGR settings, flush stdout and print a new line.

applyColoring :: MonadIO m => Coloring -> m () Source #

Apply both foreground and background color contained in a Coloring.

colorStr :: MonadIO m => Coloring -> String -> m () Source #

Use a particular ANSI Coloring to print a string at the terminal (without a new line), then clear all ANSI SGR codes and flush stdout.

colorStrLn :: MonadIO m => Coloring -> String -> m () Source #

Use a particular ANSI Coloring to print a string at the terminal, then clear all ANSI SGR codes, flush stdout and print a new line.

boldStr :: MonadIO m => Coloring -> String -> m () Source #

Like colorStr but prints bold text.

boldStrLn :: MonadIO m => Coloring -> String -> m () Source #

Like colorStrLn but prints bold text.

Graphable wrapper types

newtype Graph Source #

Wrapper type for graph of a real vector/function.

Constructors

Graph 

Fields

newtype CGraph Source #

Wrapper type for graph of a complex vector/function.

Constructors

CGraph 

Fields

newtype PosGraph Source #

Wrapper type for graph of a non-negative real vector/function.

Constructors

PosGraph 

Fields

newtype Mat Source #

Wrapper type for graph of a real two-index vector/two-argument function.

Constructors

Mat 

Fields

Instances

newtype CMat Source #

Wrapper type for graph of a complex two-index vector/two-argument function.

Constructors

CMat 

Fields

Graphing

Horizontal vector graphing (IO actions)

displayPV :: MonadIO m => GraphSettings -> [Double] -> m () Source #

ANSI based display for positive real vectors. Primarily invoked via graph, graphWith, animate, animateWith.

displayRV :: MonadIO m => GraphSettings -> [Double] -> m () Source #

ANSI based display for real vectors. Primarily invoked via graph, graphWith, animate, animateWith.

displayCV :: MonadIO m => GraphSettings -> [Complex Double] -> m () Source #

ANSI based display for complex vectors. Primarily invoked via graph, graphWith, animate, animateWith.

Horizontal rendering logic (producing strings)

renderPV :: [Double] -> String Source #

Simple vector to String rendering that assumes positive input. Yields String of Unicode chars representing graph bars varying in units of 1/8. The IO display functions are preferable for most use cases.

renderRV :: [Double] -> (String, String) Source #

Simple real vector rendering as a pair of strings. The IO display functions are preferable for most use cases.

renderCV :: [Complex Double] -> (String, String, String, String) Source #

Simple complex vector rendering as a pair of strings. The IO display functions are preferable for most use cases.

Matrix graphing

displayMat :: MonadIO m => GraphSettings -> [[Double]] -> m () Source #

Use ANSI coloring (specified by an GraphSettings) to visually display a Real matrix.

displayCMat :: MonadIO m => GraphSettings -> [[Complex Double]] -> m () Source #

Use ANSI coloring (specified by an GraphSettings) to visually display a Complex matrix.

matShow :: [[Double]] -> [String] Source #

Given a matrix of Doubles, return the list of strings illustrating the absolute value of each entry relative to the largest, via unicode chars that denote a particular density. Used for testing purposes.

Simple (non-ANSI) graphing for strictly-positive data

posGraph :: MonadIO m => [Double] -> m () Source #

Display a graph of the supplied (non-negative) real vector.

posAnim :: MonadIO m => [[Double]] -> m () Source #

Display an animation of the supplied list of (non-negative) real vectors.

For clearing

clearBack :: MonadIO m => Int -> m () Source #

Clear the last n lines of terminal text. Used to make graph animations. Rexported as a handy convenience for other uses.