Safe Haskell | None |
---|---|
Language | Haskell2010 |
This module provides functions for creating diagrams of intervals as text. For example,
>>>
let ref = bi 30 (0 :: Int)
>>>
let ivs = [ bi 2 0, bi 5 10, bi 6 16 ]
>>>
pretty $ simpleIntervalDiagram ref ivs
-- ----- ------ ==============================
>>>
import Data.Time
>>>
let ref = bi 30 (fromGregorian 2022 5 6)
>>>
let ivs = [ bi 2 (fromGregorian 2022 5 6), bi 5 (fromGregorian 2022 5 10)]
>>>
pretty $ simpleIntervalDiagram ref ivs
-- ----- ==============================
Such diagrams are useful for documentation, examples, and learning to reason with the interval algebra.
There are two main functions available:
: exposes all available options and gives the most flexibility in producing diagramsparseIntervalDiagram
produces simple diagram using defaults.simpleIntervalDiagram
Synopsis
- parseIntervalDiagram :: (Ord a, IntervalSizeable a b, Enum b) => IntervalDiagramOptions -> [(Int, Char)] -> Maybe AxisPlacement -> IntervalText a -> [([IntervalText a], [Text])] -> Either IntervalDiagramParseError (IntervalDiagram a)
- simpleIntervalDiagram :: (Ord a, IntervalSizeable a b, Intervallic i a, Enum b) => i a -> [i a] -> Either IntervalDiagramParseError (IntervalDiagram a)
- data IntervalDiagramOptions = MkIntervalDiagramOptions {}
- defaultIntervalDiagramOptions :: IntervalDiagramOptions
- data AxisPlacement
- data IntervalText a
- data IntervalDiagram a
- data IntervalTextLineParseError
- data AxisParseError
- data IntervalDiagramOptionsError
- data IntervalDiagramParseError
Make nice-looking diagrams of intervals
All these functions return an
,
which can then be pretty printed using the IntervalDiagram
function.pretty
:: (Ord a, IntervalSizeable a b, Enum b) | |
=> IntervalDiagramOptions | Document options (see |
-> [(Int, Char)] | A list of axis labels |
-> Maybe AxisPlacement | An optional |
-> IntervalText a | The reference (axis interval) |
-> [([IntervalText a], [Text])] | Intervals to include in the diagram. Each item in the list creates a new line in the printed diagram. Text creates an optional label for the line. |
-> Either IntervalDiagramParseError (IntervalDiagram a) |
Parse inputs into a pretty printable document.
This function provides the most flexibility in producing interval diagrams.
Here's a basic diagram that shows how to put more than one interval interval on a line:
>>>
:set -XTypeApplications -XFlexibleContexts -XOverloadedStrings
>>>
let mkIntrvl c d b = into @(IntervalText Int) (c, bi d (b :: Int))
>>>
let x = mkIntrvl '=' 20 0
>>>
let l1 = [ mkIntrvl '-' 1 4 ]
>>>
let l2 = [ mkIntrvl '*' 3 5, mkIntrvl '*' 5 10, mkIntrvl 'x' 1 17 ]
>>>
let l3 = [ mkIntrvl '#' 2 18]
>>>
pretty $ parseIntervalDiagram defaultIntervalDiagramOptions [] (Just Bottom) x [ (l1, []), (l2, []), (l3, []) ]
- *** ***** x ## ====================
We can put the axis on the top:
>>>
pretty $ parseIntervalDiagram defaultIntervalDiagramOptions [] (Just Top) x [ (l1, []), (l2, []), (l3, []) ]
==================== - *** ***** x ##
We can annotate the axis:
>>>
pretty $ parseIntervalDiagram defaultIntervalDiagramOptions [(5, 'a')] (Just Bottom) x [ (l1, []), (l2, []), (l3, []) ]
- *** ***** x ## ==================== | a
We can also annotate each line with labels:
>>>
pretty $ parseIntervalDiagram defaultIntervalDiagramOptions [] (Just Bottom) x [ (l1, ["line1"]), (l2, ["line2a", "line2b"]), (l3, ["line3"]) ]
- <- [line1] *** ***** x <- [line2a, line2b] ## <- [line3] ====================
The parser tries to check that the data can be printed.
For example, the default
is 80 characters.
Providing an reference interval wider than 80 characters
results in an error.LayoutOptions
>>>
let x = mkIntrvl '=' 100 5
>>>
let ivs = [ mkIntrvl '-' 1 1 ]
>>>
parseIntervalDiagram defaultIntervalDiagramOptions [] Nothing x [ (ivs, []) ]
Left AxisWiderThanAvailable
See IntervalDiagramParseError
for all the cases handled.
simpleIntervalDiagram Source #
:: (Ord a, IntervalSizeable a b, Intervallic i a, Enum b) | |
=> i a | The axis interval |
-> [i a] | List of intervals to be printed one per line |
-> Either IntervalDiagramParseError (IntervalDiagram a) |
Given a reference interval and a list of intervals,
produces an IntervalDiagram
with one line per interval,
using the defaultIntervalDiagramOptions
.
>>>
import Data.Maybe (fromMaybe)
>>>
import IntervalAlgebra.IntervalUtilities (gapsWithin)
>>>
pretty $ simpleIntervalDiagram (bi 10 (0 :: Int)) (fmap (bi 1) [0..9])
- - - - - - - - - - ==========
>>>
let ref = bi 30 (0 :: Int)
>>>
let ivs = [ bi 2 0, bi 5 10, bi 6 16 ]
>>>
pretty $ simpleIntervalDiagram ref ivs
-- ----- ------ ==============================
>>>
pretty $ simpleIntervalDiagram ref (fromMaybe [] (gapsWithin ref ivs))
-------- - -------- ==============================
Diagram options
data IntervalDiagramOptions Source #
A record containing options for printing an
.IntervalDiagram
MkIntervalDiagramOptions | |
|
Instances
Eq IntervalDiagramOptions Source # | |
Defined in IntervalAlgebra.IntervalDiagram | |
Show IntervalDiagramOptions Source # | |
Defined in IntervalAlgebra.IntervalDiagram showsPrec :: Int -> IntervalDiagramOptions -> ShowS # show :: IntervalDiagramOptions -> String # showList :: [IntervalDiagramOptions] -> ShowS # |
defaultIntervalDiagramOptions :: IntervalDiagramOptions Source #
Default IntervalDiagramOptions
options
data AxisPlacement Source #
A type representing options of where to place the axis in a printed diagram.
Instances
Eq AxisPlacement Source # | |
Defined in IntervalAlgebra.IntervalDiagram (==) :: AxisPlacement -> AxisPlacement -> Bool # (/=) :: AxisPlacement -> AxisPlacement -> Bool # | |
Show AxisPlacement Source # | |
Defined in IntervalAlgebra.IntervalDiagram showsPrec :: Int -> AxisPlacement -> ShowS # show :: AxisPlacement -> String # showList :: [AxisPlacement] -> ShowS # |
Internal types
data IntervalText a Source #
IntervalText
is an internal type
which contains an Interval a
and the Char
used to print
the interval in a diagram.
The Interval a
type needs to be an instance of IntervalSizeable a b
;
Moreover, the type b
should be castable to Int
,
using its
instance.From
b Int
>>>
import Prettyprinter (pretty)
>>>
import IntervalAlgebra (beginerval)
>>>
pretty $ MkIntervalText '-' (beginerval 5 (0::Int))
----->>>
pretty $ MkIntervalText '*' (beginerval 10 (0::Int))
**********
Instances
data IntervalDiagram a Source #
Type containing the data needed to pretty print an interval document.
Instances
(Show a, Ord a) => Show (IntervalDiagram a) Source # | |
Defined in IntervalAlgebra.IntervalDiagram showsPrec :: Int -> IntervalDiagram a -> ShowS # show :: IntervalDiagram a -> String # showList :: [IntervalDiagram a] -> ShowS # | |
IntervalSizeable a b => Pretty (IntervalDiagram a) Source # | |
Defined in IntervalAlgebra.IntervalDiagram pretty :: IntervalDiagram a -> Doc ann # prettyList :: [IntervalDiagram a] -> Doc ann # | |
IntervalSizeable a b => Pretty (Either IntervalDiagramParseError (IntervalDiagram a)) Source # | |
Defined in IntervalAlgebra.IntervalDiagram pretty :: Either IntervalDiagramParseError (IntervalDiagram a) -> Doc ann # prettyList :: [Either IntervalDiagramParseError (IntervalDiagram a)] -> Doc ann # |
Errors
data IntervalTextLineParseError Source #
A type representing errors that may occur
when a list of IntervalText
is parsed into a IntervalTextLine
.
ConcurringIntervals | The inputs contains concurring intervals.
All inputs should be |
UnsortedIntervals | The inputs are not sorted. |
BeginsLessThanZero | At least one of the inputs has a |
Instances
data AxisParseError Source #
A type representing errors that can occur when parsing an axis.
LabelsBeyondReference | Indicates that the position of one ore more axis labels is outside the reference interval |
MultipleLabelAtSamePosition | Indicates that multiple labels have been put at the same position |
Instances
Eq AxisParseError Source # | |
Defined in IntervalAlgebra.IntervalDiagram (==) :: AxisParseError -> AxisParseError -> Bool # (/=) :: AxisParseError -> AxisParseError -> Bool # | |
Show AxisParseError Source # | |
Defined in IntervalAlgebra.IntervalDiagram showsPrec :: Int -> AxisParseError -> ShowS # show :: AxisParseError -> String # showList :: [AxisParseError] -> ShowS # |
data IntervalDiagramOptionsError Source #
A type representing the types of invalid
.IntervalDiagramOptions
UnboundedPageWidth | Indicates that |
LeftPaddingLessThan0 | Indicates that the left padding in the option is < 0. |
Instances
data IntervalDiagramParseError Source #
Type representing errors that may occur
when parsing inputs into an
.IntervalDiagram
Not every possible state of a "bad" diagram is currently captured
by parseIntervalDiagram
.
In particular, line labels can be a source of problems.
The labels accept arbitrary Text
.
Newline characters in a label would, for example, throw things off.
Labels that extend beyond the
will also cause problems.pageWidth
IntervalsExtendBeyondAxis | Indicates that one or more of the input intervals extend beyond the axis. |
AxisWiderThanAvailable | Indicates that the reference axis is longer than the |
PaddingWithNoAxis | Indicates that left padding is >0
and no axis is printed.
This is considered an error because it be impossible
to know the |
OptionsError IntervalDiagramOptionsError | Indicates that an error occurring when checking the document options. |
AxisError AxisParseError | Indicates something is wrong with the |
IntervalLineError IntervalTextLineParseError | Indicates that at least one error occurred when parsing the interval lines. |
Instances
Eq IntervalDiagramParseError Source # | |
Defined in IntervalAlgebra.IntervalDiagram | |
Show IntervalDiagramParseError Source # | |
Defined in IntervalAlgebra.IntervalDiagram showsPrec :: Int -> IntervalDiagramParseError -> ShowS # show :: IntervalDiagramParseError -> String # showList :: [IntervalDiagramParseError] -> ShowS # | |
IntervalSizeable a b => Pretty (Either IntervalDiagramParseError (IntervalDiagram a)) Source # | |
Defined in IntervalAlgebra.IntervalDiagram pretty :: Either IntervalDiagramParseError (IntervalDiagram a) -> Doc ann # prettyList :: [Either IntervalDiagramParseError (IntervalDiagram a)] -> Doc ann # |