interval-algebra-2.0.2: An implementation of Allen's interval algebra for temporal logic
Safe HaskellNone
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
--                            
          -----               
                ------        
==============================
>>> 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:

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, IntervalSizeable a b, Enum b) 
=> 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:

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

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.

The Interval a type needs to be an instance of IntervalSizeable a b; Moreover, the type b should be castable to Int, using its From b Int instance.

>>> import Prettyprinter (pretty)
>>> import IntervalAlgebra (beginerval)
>>> pretty $ MkIntervalText '-' (beginerval 5 (0::Int))
-----
>>> pretty $ MkIntervalText '*' (beginerval 10 (0::Int))
**********

Instances

Instances details
Functor IntervalText Source # 
Instance details

Defined in IntervalAlgebra.IntervalDiagram

Methods

fmap :: (a -> b) -> IntervalText a -> IntervalText b #

(<$) :: a -> IntervalText b -> IntervalText a #

Ord a => Intervallic IntervalText a 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 b, IntervalSizeable a b) => Pretty (IntervalText a) Source # 
Instance details

Defined in IntervalAlgebra.IntervalDiagram

Methods

pretty :: IntervalText a -> Doc ann #

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

From (IntervalText a) Char Source # 
Instance details

Defined in IntervalAlgebra.IntervalDiagram

Methods

from :: IntervalText a -> Char #

From (IntervalText a) (Interval a) Source # 
Instance details

Defined in IntervalAlgebra.IntervalDiagram

Methods

from :: IntervalText a -> Interval a #

From (Char, Interval a) (IntervalText a) Source # 
Instance details

Defined in IntervalAlgebra.IntervalDiagram

Methods

from :: (Char, Interval a) -> IntervalText a #

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.