interval-algebra-2.2.0: An implementation of Allen's interval algebra for temporal logic
Copyright(c) NoviSci Inc 2020-2022
TargetRWE 2023
LicenseBSD3
Maintainerbsaul@novisci.com 2020-2022, bbrown@targetrwe.com 2023
Safe HaskellSafe-Inferred
LanguageHaskell2010

IntervalAlgebra.IntervalDiagram

Description

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:

Synopsis

Make nice-looking diagrams of intervals

All these functions return an IntervalDiagram, which can then be pretty printed using the pretty function.

parseIntervalDiagram Source #

Arguments

:: (Ord a, SizedIv (Interval a), Enum a, Num a, Enum (Moment (Interval a))) 
=> IntervalDiagramOptions

Document options (see IntervalDiagramOptions)

-> [(Int, Char)]

A list of axis labels

-> Maybe AxisPlacement

An optional AxisPlacement of the axis

-> 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 LayoutOptions is 80 characters. Providing an reference interval wider than 80 characters results in an error.

>>> 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 #

Arguments

:: (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.

Constructors

MkIntervalDiagramOptions 

Fields

data AxisPlacement Source #

A type representing options of where to place the axis in a printed diagram.

Constructors

Top

Print the axis at the top of the diagram

Bottom

Print the axis at the bottom of the diagram

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

Instances details
Intervallic IntervalText Source # 
Instance details

Defined in IntervalAlgebra.IntervalDiagram

Eq a => Eq (IntervalText a) Source # 
Instance details

Defined in IntervalAlgebra.IntervalDiagram

(Show a, Ord a) => Show (IntervalText a) Source # 
Instance details

Defined in IntervalAlgebra.IntervalDiagram

(Enum (Moment (Interval a)), SizedIv (Interval a)) => Pretty (IntervalText a) Source # 
Instance details

Defined in IntervalAlgebra.IntervalDiagram

Methods

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.

Errors

data IntervalTextLineParseError Source #

A type representing errors that may occur when a list of IntervalText is parsed into a IntervalTextLine.

Constructors

ConcurringIntervals

The inputs contains concurring intervals. All inputs should be disjoint.

UnsortedIntervals

The inputs are not sorted.

BeginsLessThanZero

At least one of the inputs has a begin less than zero.

data AxisParseError Source #

A type representing errors that can occur when parsing an axis.

Constructors

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

data IntervalDiagramOptionsError Source #

A type representing the types of invalid IntervalDiagramOptions.

Constructors

UnboundedPageWidth

Indicates that PageWidth is Unbounded, which isn't allowed for an IntervalDiagram.

LeftPaddingLessThan0

Indicates that the left padding in the option is < 0.

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 pageWidth will also cause problems.

Constructors

IntervalsExtendBeyondAxis

Indicates that one or more of the input intervals extend beyond the axis.

AxisWiderThanAvailable

Indicates that the reference axis is longer than the PageWidth given in the IntervalDiagramOptions.

PaddingWithNoAxis

Indicates that left padding is >0 and no axis is printed. This is considered an error because it be impossible to know the begin values of intervals in a printed IntervalDiagram that has been padded and has no axis.

OptionsError IntervalDiagramOptionsError

Indicates that an error occurring when checking the document options.

AxisError AxisParseError

Indicates something is wrong with the Axis.

IntervalLineError IntervalTextLineParseError

Indicates that at least one error occurred when parsing the interval lines.

Re-exports

class Pretty a where #

Overloaded conversion to Doc.

Laws:

  1. output should be pretty. :-)

Minimal complete definition

pretty

Methods

pretty :: a -> Doc ann #

>>> pretty 1 <+> pretty "hello" <+> pretty 1.234
1 hello 1.234

prettyList :: [a] -> Doc ann #

prettyList is only used to define the instance Pretty a => Pretty [a]. In normal circumstances only the pretty function is used.

>>> prettyList [1, 23, 456]
[1, 23, 456]

Instances

Instances details
Pretty Bool
>>> pretty True
True
Instance details

Defined in Prettyprinter.Internal

Methods

pretty :: Bool -> Doc ann #

prettyList :: [Bool] -> Doc ann #

Pretty Char

Instead of (pretty 'n'), consider using line as a more readable alternative.

>>> pretty 'f' <> pretty 'o' <> pretty 'o'
foo
>>> pretty ("string" :: String)
string
Instance details

Defined in Prettyprinter.Internal

Methods

pretty :: Char -> Doc ann #

prettyList :: [Char] -> Doc ann #

Pretty Double
>>> pretty (exp 1 :: Double)
2.71828182845904...
Instance details

Defined in Prettyprinter.Internal

Methods

pretty :: Double -> Doc ann #

prettyList :: [Double] -> Doc ann #

Pretty Float
>>> pretty (pi :: Float)
3.1415927
Instance details

Defined in Prettyprinter.Internal

Methods

pretty :: Float -> Doc ann #

prettyList :: [Float] -> Doc ann #

Pretty Int
>>> pretty (123 :: Int)
123
Instance details

Defined in Prettyprinter.Internal

Methods

pretty :: Int -> Doc ann #

prettyList :: [Int] -> Doc ann #

Pretty Int8 
Instance details

Defined in Prettyprinter.Internal

Methods

pretty :: Int8 -> Doc ann #

prettyList :: [Int8] -> Doc ann #

Pretty Int16 
Instance details

Defined in Prettyprinter.Internal

Methods

pretty :: Int16 -> Doc ann #

prettyList :: [Int16] -> Doc ann #

Pretty Int32 
Instance details

Defined in Prettyprinter.Internal

Methods

pretty :: Int32 -> Doc ann #

prettyList :: [Int32] -> Doc ann #

Pretty Int64 
Instance details

Defined in Prettyprinter.Internal

Methods

pretty :: Int64 -> Doc ann #

prettyList :: [Int64] -> Doc ann #

Pretty Integer
>>> pretty (2^123 :: Integer)
10633823966279326983230456482242756608
Instance details

Defined in Prettyprinter.Internal

Methods

pretty :: Integer -> Doc ann #

prettyList :: [Integer] -> Doc ann #

Pretty Natural 
Instance details

Defined in Prettyprinter.Internal

Methods

pretty :: Natural -> Doc ann #

prettyList :: [Natural] -> Doc ann #

Pretty Word 
Instance details

Defined in Prettyprinter.Internal

Methods

pretty :: Word -> Doc ann #

prettyList :: [Word] -> Doc ann #

Pretty Word8 
Instance details

Defined in Prettyprinter.Internal

Methods

pretty :: Word8 -> Doc ann #

prettyList :: [Word8] -> Doc ann #

Pretty Word16 
Instance details

Defined in Prettyprinter.Internal

Methods

pretty :: Word16 -> Doc ann #

prettyList :: [Word16] -> Doc ann #

Pretty Word32 
Instance details

Defined in Prettyprinter.Internal

Methods

pretty :: Word32 -> Doc ann #

prettyList :: [Word32] -> Doc ann #

Pretty Word64 
Instance details

Defined in Prettyprinter.Internal

Methods

pretty :: Word64 -> Doc ann #

prettyList :: [Word64] -> Doc ann #

Pretty ()
>>> pretty ()
()

The argument is not used:

>>> pretty (error "Strict?" :: ())
()
Instance details

Defined in Prettyprinter.Internal

Methods

pretty :: () -> Doc ann #

prettyList :: [()] -> Doc ann #

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.

>>> pretty ([] :: [Void])
[]
Instance details

Defined in Prettyprinter.Internal

Methods

pretty :: Void -> Doc ann #

prettyList :: [Void] -> Doc ann #

Pretty Text

Automatically converts all newlines to line.

>>> pretty ("hello\nworld" :: Text)
hello
world

Note that line can be undone by group:

>>> group (pretty ("hello\nworld" :: Text))
hello world

Manually use hardline if you definitely want newlines.

Instance details

Defined in Prettyprinter.Internal

Methods

pretty :: Text -> Doc ann #

prettyList :: [Text] -> Doc ann #

Pretty Text

(lazy Text instance, identical to the strict version)

Instance details

Defined in Prettyprinter.Internal

Methods

pretty :: Text -> Doc ann #

prettyList :: [Text] -> Doc ann #

Pretty a => Pretty [a]
>>> pretty [1,2,3]
[1, 2, 3]
Instance details

Defined in Prettyprinter.Internal

Methods

pretty :: [a] -> Doc ann #

prettyList :: [[a]] -> Doc ann #

Pretty a => Pretty (Maybe a)

Ignore Nothings, print Just contents.

>>> pretty (Just True)
True
>>> braces (pretty (Nothing :: Maybe Bool))
{}
>>> pretty [Just 1, Nothing, Just 3, Nothing]
[1, 3]
Instance details

Defined in Prettyprinter.Internal

Methods

pretty :: Maybe a -> Doc ann #

prettyList :: [Maybe a] -> Doc ann #

Pretty a => Pretty (Identity a)
>>> pretty (Identity 1)
1
Instance details

Defined in Prettyprinter.Internal

Methods

pretty :: Identity a -> Doc ann #

prettyList :: [Identity a] -> Doc ann #

Pretty a => Pretty (NonEmpty a) 
Instance details

Defined in Prettyprinter.Internal

Methods

pretty :: NonEmpty a -> Doc ann #

prettyList :: [NonEmpty a] -> Doc ann #

SizedIv (Interval a) => Pretty (IntervalDiagram a) Source # 
Instance details

Defined in IntervalAlgebra.IntervalDiagram

Methods

pretty :: IntervalDiagram a -> Doc ann #

prettyList :: [IntervalDiagram a] -> Doc ann #

(Enum (Moment (Interval a)), SizedIv (Interval a)) => Pretty (IntervalText a) Source # 
Instance details

Defined in IntervalAlgebra.IntervalDiagram

Methods

pretty :: IntervalText a -> Doc ann #

prettyList :: [IntervalText a] -> Doc ann #

SizedIv (Interval a) => Pretty (Either IntervalDiagramParseError (IntervalDiagram a)) Source # 
Instance details

Defined in IntervalAlgebra.IntervalDiagram

(Pretty a1, Pretty a2) => Pretty (a1, a2)
>>> pretty (123, "hello")
(123, hello)
Instance details

Defined in Prettyprinter.Internal

Methods

pretty :: (a1, a2) -> Doc ann #

prettyList :: [(a1, a2)] -> Doc ann #

(Pretty a1, Pretty a2, Pretty a3) => Pretty (a1, a2, a3)
>>> pretty (123, "hello", False)
(123, hello, False)
Instance details

Defined in Prettyprinter.Internal

Methods

pretty :: (a1, a2, a3) -> Doc ann #

prettyList :: [(a1, a2, a3)] -> Doc ann #

Pretty a => Pretty (Const a b) 
Instance details

Defined in Prettyprinter.Internal

Methods

pretty :: Const a b -> Doc ann #

prettyList :: [Const a b] -> Doc ann #