Safe Haskell | Safe |
---|---|
Language | Haskell2010 |
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.
- class Graphable a where
- graph :: MonadIO m => Graphable a => a -> m ()
- animateWith :: MonadIO m => Graphable a => GraphSettings -> [a] -> m ()
- animate :: MonadIO m => Graphable a => [a] -> m ()
- transientAnim :: (MonadIO m, Graphable a) => [a] -> m ()
- transientAnimWith :: MonadIO m => Graphable a => GraphSettings -> [a] -> m ()
- data GraphSettings = GraphSettings {}
- graphDefaults :: GraphSettings
- blue :: AnsiColor
- pink :: AnsiColor
- white :: AnsiColor
- red :: AnsiColor
- green :: AnsiColor
- noColoring :: Coloring
- data Color :: *
- data ColorIntensity :: *
- data AnsiColor = AnsiColor {}
- data Coloring = Coloring {}
- mkColoring :: AnsiColor -> AnsiColor -> Coloring
- fromFG :: AnsiColor -> Coloring
- fromBG :: AnsiColor -> Coloring
- realColors :: GraphSettings -> Coloring
- imagColors :: GraphSettings -> Coloring
- colorSets :: GraphSettings -> (Coloring, Coloring)
- invert :: Coloring -> Coloring
- interpAnsiColor :: ConsoleLayer -> AnsiColor -> SGR
- setColor :: MonadIO m => ConsoleLayer -> AnsiColor -> m ()
- clear :: MonadIO m => m ()
- clearLn :: MonadIO m => m ()
- applyColoring :: MonadIO m => Coloring -> m ()
- colorStr :: MonadIO m => Coloring -> String -> m ()
- colorStrLn :: MonadIO m => Coloring -> String -> m ()
- boldStr :: MonadIO m => Coloring -> String -> m ()
- boldStrLn :: MonadIO m => Coloring -> String -> m ()
- newtype Graph = Graph {}
- newtype CGraph = CGraph {}
- newtype PosGraph = PosGraph {
- unPosGraph :: [Double]
- newtype Mat = Mat {}
- newtype CMat = CMat {}
- displayPV :: MonadIO m => GraphSettings -> [Double] -> m ()
- displayRV :: MonadIO m => GraphSettings -> [Double] -> m ()
- displayCV :: MonadIO m => GraphSettings -> [Complex Double] -> m ()
- renderPV :: [Double] -> String
- renderRV :: [Double] -> (String, String)
- renderCV :: [Complex Double] -> (String, String, String, String)
- displayMat :: MonadIO m => GraphSettings -> [[Double]] -> m ()
- displayCMat :: MonadIO m => GraphSettings -> [[Complex Double]] -> m ()
- matShow :: [[Double]] -> [String]
- posGraph :: MonadIO m => [Double] -> m ()
- posAnim :: MonadIO m => [[Double]] -> m ()
- clearBack :: MonadIO m => Int -> m ()
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
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
graph
ing 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 graph
ing 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.
GraphSettings | |
|
Default options
graphDefaults :: GraphSettings Source #
Default graph settings.
ANSI data
Basic types from ANSI package
ANSI colors: come in various intensities, which are controlled by ColorIntensity
data ColorIntensity :: * #
ANSI colors come in two intensities
Custom composite data types
ANSI colors are characterized by a Color
and a ColorIntensity
.
ANSI helpers
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 Coloring
s for real and imaginary graph components respectively.
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
.
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.
Graphable wrapper types
Wrapper type for graph of a real vector/function.
Wrapper type for graph of a complex vector/function.
Wrapper type for graph of a non-negative real vector/function.
PosGraph | |
|
Wrapper type for graph of a real two-index vector/two-argument function.
Wrapper type for graph of a complex two-index vector/two-argument function.
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.