regexdot-0.12.2.0: A polymorphic, POSIX, extended regex-engine.

Safe HaskellSafe
LanguageHaskell2010

RegExDot.Repeatable

Contents

Description

AUTHOR
Dr. Alistair Ward
DESCRIPTION
  • A data-type, which represents the permissible range of instances, of the underlying polymorphic datum.
  • Designed for use in a polymorphic regex-engine, which specifies patterns composed of repeated greedy & non-greedy sequences of Meta-data;
		*	+	?	{fewest, most}	{fewest,}	{fewest}
		*?	+?	??	{fewest, most}?	{fewest,}?
  • In the context of regexes, this concept is known as Quantification.
  • regexes evolved from the minimal ability to optionally qualify the datum with a https://en.wikipedia.org/wiki/Kleene_star suffix. More exotic repetition-specifications could be composed by concatenating these atomic building-blocks. Here, I've taken the contrary top-down view, & assumed that all data are qualified by a full RepetitionBounds, which in most cases will degenerate into a simpler form.
  • The type of entity which is being repeated, isn't the domain of this data-type; it's polymorphic.
Synopsis

Types

Type-synonyms

type Repetitions = Int Source #

A number of repetitions.

type RepetitionBounds = (Repetitions, Maybe Repetitions) Source #

Defines the bounds of a range of permissible repetitions.

Data-types

data Repeatable a Source #

Declares a polymorphic data-type, which augments the underlying base datum, with the range of times it may be used.

Constructors

MkRepeatable 

Fields

Instances
Functor Repeatable Source # 
Instance details

Defined in RegExDot.Repeatable

Methods

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

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

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

Defined in RegExDot.Repeatable

Methods

(==) :: Repeatable a -> Repeatable a -> Bool #

(/=) :: Repeatable a -> Repeatable a -> Bool #

Read a => Read (Repeatable a) Source # 
Instance details

Defined in RegExDot.Repeatable

Show a => Show (Repeatable a) Source # 
Instance details

Defined in RegExDot.Repeatable

NFData a => NFData (Repeatable a) Source # 
Instance details

Defined in RegExDot.Repeatable

Methods

rnf :: Repeatable a -> () #

SelfValidator a => SelfValidator (Repeatable a) Source # 
Instance details

Defined in RegExDot.Repeatable

Consumer a => Consumer (Repeatable a) Source # 
Instance details

Defined in RegExDot.Repeatable

Constants

oneOrMoreToken :: Char Source #

The token used to denote oneOrMore, when in the String-form.

rangeDelimiters :: (Char, Char) Source #

The delimiters of ^#->#, when in the String-form.

rangeSeparatorToken :: Char Source #

The token used to separate RepetitionBounds, when in the String-form.

tokens :: String Source #

The set of Char to which a specific meaning is attributed, when reading from String.

zeroOrMoreToken :: Char Source #

zeroOrOneToken :: Char Source #

The token used to denote zeroOrOne, when in the String-form.

Functions

one :: a -> Repeatable a Source #

  • Construct a Repeatable, tailored for unrepeated data.
  • A degenerate case of ^#.

oneOrMore :: a -> Repeatable a Source #

oneOrMore' :: a -> Repeatable a Source #

Construct a non-greedy version of oneOrMore.

zeroOrMore :: a -> Repeatable a Source #

  • Construct a greedy Repeatable, from a polymorphic datum, with fewest == 0.
  • A specific case of ^#->.

zeroOrMore' :: a -> Repeatable a Source #

Construct a non-greedy version of zeroOrMore.

zeroOrOne :: a -> Repeatable a Source #

  • Construct a greedy Repeatable, from a polymorphic datum, with fewest == 0 & most == 1.
  • A specific case of ^#->#.

zeroOrOne' :: a -> Repeatable a Source #

Construct a non-greedy version of zeroOrOne.

repeatableParser :: a -> Parser (Repeatable a) Source #

Builds a parser for a specification of the number of permissible instances of the specified polymorphic parameter.

showSuffix :: Repeatable a -> ShowS Source #

  • A ShowS-function for the suffix, denoting the permissible repetitions, of base.
  • This function converts the internal, into the tradition greedy & non-greedy quantifiers of various specific varieties.

Accessors

Mutators

focus :: Repeatable a -> Repetitions -> Repeatable a Source #

Reduces a Repeatable, with a range of RepetitionBounds, to a precise number of repetitions.

toSingleton :: Repeatable a -> Repeatable a Source #

Operators

(^#->#) infix 6 Source #

Arguments

:: a

The polymorphic payload from which to construct the Repeatable.

-> RepetitionBounds

The permissible repetition-bounds for the polymorphic data.

-> Repeatable a 
  • Construct a greedy Repeatable, from a polymorphic datum, with the specified range of permissible instances.
  • The #s in the identifier represent the two bounds.
  • a{f, m}

(^#->#?) infix 6 Source #

Arguments

:: a

The polymorphic payload from which to construct the Repeatable.

-> RepetitionBounds

The permissible repetition-bounds for the polymorphic data.

-> Repeatable a 
  • Construct a non-greedy version of ^#->#.
  • a{f, m}?

(^#->) infix 6 Source #

Arguments

:: a

The polymorphic payload from which to construct the Repeatable.

-> Repetitions

The minimum permissible repetitions of the polymorphic data.

-> Repeatable a 
  • Construct a greedy Repeatable, tailored for data repeated at least the specified number of times.
  • The # in the identifier represents the single bound.
  • a{f,}

(^#->?) infix 6 Source #

Arguments

:: a

The polymorphic payload from which to construct the Repeatable.

-> Repetitions

The minimum permissible repetitions of the polymorphic data.

-> Repeatable a 
  • Construct a non-greedy version of ^#->.
  • a{f,}?

(^#) infix 6 Source #

Arguments

:: a

The polymorphic payload from which to construct the Repeatable.

-> Repetitions

The precise number of repetitions of the polymorphic data which is required.

-> Repeatable a 
  • Construct a Repeatable, tailored for data repeated a precise number of times.
  • The # in the identifier represents the single bound.
  • a{f}

Predicates

isPrecise :: Repeatable a -> Bool Source #

True if there's no choice in the number of repetitions; implemented via isPrecise.

hasPreciseBounds :: RepetitionBounds -> Bool Source #

Predicate which is True if exactly one value is permissible, ie lower & upper bounds on the number of Repetitions are identical.