Copyright | (c) NoviSci Inc 2020-2022 TargetRWE 2023 |
---|---|
License | BSD3 |
Maintainer | bsaul@novisci.com 2020-2022, bbrown@targetrwe.com 2023 |
Safe Haskell | Safe-Inferred |
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
-- ----- ------ ==============================
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, SizedIv (Interval a), Enum a, Num a, Enum (Moment (Interval a))) => IntervalDiagramOptions -> [(Int, Char)] -> Maybe AxisPlacement -> IntervalText a -> [([IntervalText a], [Text])] -> Either IntervalDiagramParseError (IntervalDiagram a)
- simpleIntervalDiagram :: (Ord a, SizedIv (Interval a), Intervallic i, Enum a, Num a, Enum (Moment (Interval a))) => i a -> [i a] -> Either IntervalDiagramParseError (IntervalDiagram a)
- standardExampleDiagram :: (Num a, Enum a, Ord a, Enum (Moment (Interval a)), Ord (Moment (Interval a)), SizedIv (Interval a)) => [(Interval a, String)] -> [([Interval a], String)] -> 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
- class Pretty a where
- pretty :: a -> Doc ann
- prettyList :: [a] -> Doc ann
Make nice-looking diagrams of intervals
All these functions return an
,
which can then be pretty printed using the IntervalDiagram
function.pretty
:: (Ord a, SizedIv (Interval a), Enum a, Num a, Enum (Moment (Interval a))) | |
=> 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:
>>>
let mkIntrvl c d b = makeIntervalText 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, SizedIv (Interval a), Intervallic i, Enum a, Num a, Enum (Moment (Interval a))) | |
=> 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
.
>>>
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
-- ----- ------ ==============================
standardExampleDiagram :: (Num a, Enum a, Ord a, Enum (Moment (Interval a)), Ord (Moment (Interval a)), SizedIv (Interval a)) => [(Interval a, String)] -> [([Interval a], String)] -> Either IntervalDiagramParseError (IntervalDiagram a) Source #
Given various inputs containing intervals and their label, creates an interval diagram with labels, along with a reference range that spans all of the intervals and is extended to include 0 if necesary.
In more detail, an interval diagram is created with one row in the diagram for each interval and label pair provided as the first input, and followed by a sequence of additional rows with one row per list element in the second input and such that each row displays each interval provided in the intervals list and label pair.
>>>
x1 = beginerval 4 1
>>>
x2 = beginerval 3 7
>>>
x3 = beginerval 2 13
>>>
ivs = [x1, x2, x3]
>>>
gaps = [beginerval 2 5, beginerval 3 10]
>>>
:{
pretty $ standardExampleDiagram (zip ivs ["x1", "x2", "x3"]) [(gaps, "gaps")] :} ---- <- [x1] --- <- [x2] -- <- [x3] -- --- <- [gaps] ===============
>>>
:{
pretty $ standardExampleDiagram (zip ivs ["x1", "x2", "x3"]) [] :} ---- <- [x1] --- <- [x2] -- <- [x3] ===============
>>>
pretty $ standardExampleDiagram [] [(gaps, "gaps")]
-- --- <- [gaps] =============
>>>
pretty $ standardExampleDiagram [] []
IntervalsExtendBeyondAxis
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.
>>>
pretty $ makeIntervalText '-' (beginerval 5 (0::Int))
----->>>
pretty $ makeIntervalText '*' (beginerval 10 (0::Int))
**********
Instances
Intervallic IntervalText Source # | |
Defined in IntervalAlgebra.IntervalDiagram getInterval :: IntervalText a -> Interval a Source # setInterval :: IntervalText a -> Interval b -> IntervalText b Source # | |
Eq a => Eq (IntervalText a) Source # | |
Defined in IntervalAlgebra.IntervalDiagram (==) :: IntervalText a -> IntervalText a -> Bool # (/=) :: IntervalText a -> IntervalText a -> Bool # | |
(Show a, Ord a) => Show (IntervalText a) Source # | |
Defined in IntervalAlgebra.IntervalDiagram showsPrec :: Int -> IntervalText a -> ShowS # show :: IntervalText a -> String # showList :: [IntervalText a] -> ShowS # | |
(Enum (Moment (Interval a)), SizedIv (Interval a)) => Pretty (IntervalText a) Source # | |
Defined in IntervalAlgebra.IntervalDiagram pretty :: IntervalText a -> Doc ann # prettyList :: [IntervalText a] -> Doc ann # |
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 # | |
SizedIv (Interval a) => Pretty (IntervalDiagram a) Source # | |
Defined in IntervalAlgebra.IntervalDiagram pretty :: IntervalDiagram a -> Doc ann # prettyList :: [IntervalDiagram a] -> Doc ann # | |
SizedIv (Interval a) => 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 # | |
SizedIv (Interval a) => Pretty (Either IntervalDiagramParseError (IntervalDiagram a)) Source # | |
Defined in IntervalAlgebra.IntervalDiagram pretty :: Either IntervalDiagramParseError (IntervalDiagram a) -> Doc ann # prettyList :: [Either IntervalDiagramParseError (IntervalDiagram a)] -> Doc ann # |
Re-exports
>>>
pretty 1 <+> pretty "hello" <+> pretty 1.234
1 hello 1.234
prettyList :: [a] -> Doc ann #
is only used to define the prettyList
instance
. In normal circumstances only the Pretty
a => Pretty
[a]
function is used.pretty
>>>
prettyList [1, 23, 456]
[1, 23, 456]
Instances
Pretty Bool |
|
Defined in Prettyprinter.Internal | |
Pretty Char | Instead of
|
Defined in Prettyprinter.Internal | |
Pretty Double |
|
Defined in Prettyprinter.Internal | |
Pretty Float |
|
Defined in Prettyprinter.Internal | |
Pretty Int |
|
Defined in Prettyprinter.Internal | |
Pretty Int8 | |
Defined in Prettyprinter.Internal | |
Pretty Int16 | |
Defined in Prettyprinter.Internal | |
Pretty Int32 | |
Defined in Prettyprinter.Internal | |
Pretty Int64 | |
Defined in Prettyprinter.Internal | |
Pretty Integer |
|
Defined in Prettyprinter.Internal | |
Pretty Natural | |
Defined in Prettyprinter.Internal | |
Pretty Word | |
Defined in Prettyprinter.Internal | |
Pretty Word8 | |
Defined in Prettyprinter.Internal | |
Pretty Word16 | |
Defined in Prettyprinter.Internal | |
Pretty Word32 | |
Defined in Prettyprinter.Internal | |
Pretty Word64 | |
Defined in Prettyprinter.Internal | |
Pretty () |
The argument is not used:
|
Defined in Prettyprinter.Internal | |
Pretty Void | Finding a good example for printing something that does not exist is hard, so here is an example of printing a list full of nothing.
|
Defined in Prettyprinter.Internal | |
Pretty Text | Automatically converts all newlines to
Note that
Manually use |
Defined in Prettyprinter.Internal | |
Pretty Text | (lazy |
Defined in Prettyprinter.Internal | |
Pretty a => Pretty [a] |
|
Defined in Prettyprinter.Internal | |
Pretty a => Pretty (Maybe a) | Ignore
|
Defined in Prettyprinter.Internal | |
Pretty a => Pretty (Identity a) |
|
Defined in Prettyprinter.Internal | |
Pretty a => Pretty (NonEmpty a) | |
Defined in Prettyprinter.Internal | |
SizedIv (Interval a) => Pretty (IntervalDiagram a) Source # | |
Defined in IntervalAlgebra.IntervalDiagram pretty :: IntervalDiagram a -> Doc ann # prettyList :: [IntervalDiagram a] -> Doc ann # | |
(Enum (Moment (Interval a)), SizedIv (Interval a)) => Pretty (IntervalText a) Source # | |
Defined in IntervalAlgebra.IntervalDiagram pretty :: IntervalText a -> Doc ann # prettyList :: [IntervalText a] -> Doc ann # | |
SizedIv (Interval a) => Pretty (Either IntervalDiagramParseError (IntervalDiagram a)) Source # | |
Defined in IntervalAlgebra.IntervalDiagram pretty :: Either IntervalDiagramParseError (IntervalDiagram a) -> Doc ann # prettyList :: [Either IntervalDiagramParseError (IntervalDiagram a)] -> Doc ann # | |
(Pretty a1, Pretty a2) => Pretty (a1, a2) |
|
Defined in Prettyprinter.Internal | |
(Pretty a1, Pretty a2, Pretty a3) => Pretty (a1, a2, a3) |
|
Defined in Prettyprinter.Internal | |
Pretty a => Pretty (Const a b) | |
Defined in Prettyprinter.Internal |