pinchot-0.20.0.0: Write grammars, not parsers

Safe HaskellNone
LanguageHaskell2010

Pinchot.Intervals

Description

Intervals describe terminal symbols. Ordinarily you will not need to use this module, as Pinchot re-exports the things you usually need.

Synopsis

Documentation

data Intervals a Source #

Groups of terminals. Create an Intervals using include, exclude, solo and pariah. Combine Intervals using mappend, which will combine both the included and excluded terminal symbols from each operand.

Constructors

Intervals 

Fields

  • _included :: Seq (a, a)

    Each pair (a, b) is an inclusive range of terminal symbols, in order. For instance, (a, c) includes the characters a, b, and c. The included sequence contains all terminals that are included in the Intervals, except for those that are excluded.

  • _excluded :: Seq (a, a)

    Each symbol in excluded is not in the Intervals, even if the symbol is included.

Instances

Functor Intervals Source # 

Methods

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

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

Eq a => Eq (Intervals a) Source # 

Methods

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

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

Data a => Data (Intervals a) Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Intervals a -> c (Intervals a) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Intervals a) #

toConstr :: Intervals a -> Constr #

dataTypeOf :: Intervals a -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c (Intervals a)) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Intervals a)) #

gmapT :: (forall b. Data b => b -> b) -> Intervals a -> Intervals a #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Intervals a -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Intervals a -> r #

gmapQ :: (forall d. Data d => d -> u) -> Intervals a -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Intervals a -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Intervals a -> m (Intervals a) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Intervals a -> m (Intervals a) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Intervals a -> m (Intervals a) #

Ord a => Ord (Intervals a) Source # 
Show a => Show (Intervals a) Source # 
Monoid (Intervals a) Source # 
Lift a => Lift (Intervals a) Source # 

Methods

lift :: Intervals a -> Q Exp #

PrettyVal a => PrettyVal (Intervals a) Source # 

included :: forall a. Lens' (Intervals a) (Seq (a, a)) Source #

excluded :: forall a. Lens' (Intervals a) (Seq (a, a)) Source #

include :: a -> a -> Intervals a Source #

Include a range of symbols in the Intervals. For instance, to include the characters a, b, and c, use include a c. Example: rLetter.

exclude :: a -> a -> Intervals a Source #

Exclude a range of symbols in the Intervals. Each symbol that is excluded is not included in the Intervals, even if it is also included.

solo :: a -> Intervals a Source #

Include a single symbol. Example: rNorth.

pariah :: a -> Intervals a Source #

Exclude a single symbol.

endLeft :: Ord a => (a, a) -> a Source #

Left endpoint.

endRight :: Ord a => (a, a) -> a Source #

Right endpoint.

inInterval :: Ord a => a -> (a, a) -> Bool Source #

Is this symbol included in the interval?

members :: (Ord a, Enum a) => (a, a) -> Seq a Source #

Enumerate all members of an interval.

sortIntervalSeq :: Ord a => Seq (a, a) -> Seq (a, a) Source #

Sort a sequence of intervals.

standardizeInterval :: Ord a => (a, a) -> (a, a) Source #

Arrange an interval so the lower bound is first in the pair.

standardizeIntervalSeq :: (Ord a, Enum a) => Seq (a, a) -> Seq (a, a) Source #

Sorts the intervals using sortIntervalSeq and presents them in a regular order using flatten. The function standardizeIntervalSeq a has the following properties, where b is the result:

uniqueMembers a == uniqueMembers b

let go [] = True
    go (_:[]) = True
    go (x:y:xs)
         | endRight x < endLeft y
             && endRight x < pred (endLeft x)
             = go (y:xs)
         | otherwise = False
in go b

The second property means that adjacent intervals in the list must be separated by at least one point on the number line.

flattenIntervalSeq :: (Ord a, Enum a) => Seq (a, a) -> Seq (a, a) Source #

Presents the intervals in a standard order, as described in standardizeIntervalSeq. If the input has already been sorted with sortIntervalSeq, the same properties for standardizeIntervalSeq hold for this function. Otherwise, its properties are undefined.

removeExcludes Source #

Arguments

:: (Ord a, Enum a) 
=> Seq (a, a)

Included intervals (not necessarily sorted)

-> Seq (a, a)

Excluded intervals (not necessarily sorted)

-> Seq (a, a) 

Removes excluded members from a list of Interval. The following properties hold:

removeProperties
  :: (Ord a, Enum a)
  => Seq (a, a)
  -> Seq (a, a)
  -> [Bool]
removeProperties inc exc =

 let r = removeExcludes inc exc
     allExcluded = concatMap members exc
     allIncluded = concatMap members inc
     allResults = concatMap members r
 in [
   -- intervals remain in original order
   allResults == filter (not . (`elem` allExcluded)) allIncluded

 -- Every resulting member was a member of the original include list
 , all (`elem` allIncluded) allResults

 -- No resulting member is in the exclude list
 , all (not . (`elem` allExcluded)) allResults

 -- Every included member that is not in the exclude list is
 -- in the result
 , all (x -> x `elem` allExcluded || x `elem` allResults)
       allIncluded

 ]

remover Source #

Arguments

:: (Ord a, Enum a) 
=> (a, a)

Remove this interval

-> Seq (a, a)

From this sequence of intervals

-> Seq (a, a) 

removeInterval Source #

Arguments

:: (Ord a, Enum a) 
=> (a, a)

Remove this interval

-> (a, a)

From this interval

-> (Maybe (a, a), Maybe (a, a)) 

Removes a single interval from a single other interval. Returns a sequence of intervals, which always

splitIntervals :: (Ord a, Enum a) => Intervals a -> Seq (a, a) Source #

Sorts the intervals using standardizeIntervalSeq, and then removes the excludes with removeExcludes.

inIntervals :: (Enum a, Ord a) => Intervals a -> a -> Bool Source #

True if the given element is a member of the Intervals.

liftSeq :: Lift a => Seq a -> ExpQ Source #