| Safe Haskell | None |
|---|---|
| Language | Haskell2010 |
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.
- data Intervals a = Intervals {}
- include :: a -> a -> Intervals a
- exclude :: a -> a -> Intervals a
- solo :: a -> Intervals a
- pariah :: a -> Intervals a
- endLeft :: Ord a => (a, a) -> a
- endRight :: Ord a => (a, a) -> a
- inInterval :: Ord a => a -> (a, a) -> Bool
- members :: (Ord a, Enum a) => (a, a) -> Seq a
- sortIntervalSeq :: Ord a => Seq (a, a) -> Seq (a, a)
- standardizeInterval :: Ord a => (a, a) -> (a, a)
- standardizeIntervalSeq :: (Ord a, Enum a) => Seq (a, a) -> Seq (a, a)
- flattenIntervalSeq :: (Ord a, Enum a) => Seq (a, a) -> Seq (a, a)
- removeExcludes :: (Ord a, Enum a) => Seq (a, a) -> Seq (a, a) -> Seq (a, a)
- remover :: (Ord a, Enum a) => (a, a) -> Seq (a, a) -> Seq (a, a)
- removeInterval :: (Ord a, Enum a) => (a, a) -> (a, a) -> (Maybe (a, a), Maybe (a, a))
- standardizeIntervals :: (Ord a, Enum a) => Intervals a -> Intervals a
- splitIntervals :: (Ord a, Enum a) => Intervals a -> Seq (a, a)
- inIntervals :: (Enum a, Ord a) => Intervals a -> a -> Bool
- liftSeq :: Lift a => Seq a -> ExpQ
Documentation
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
| |
include :: a -> a -> Intervals a Source
Include a range of symbols in the Intervals. For instance, to
include the characters , a, and b, use cinclude .a
c
inInterval :: Ord a => a -> (a, a) -> Bool Source
Is this symbol included in the 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:
uniqueMembersa ==uniqueMembersb let go [] = True go (_:[]) = True go (x:y:xs) |endRightx <endLefty &&endRightx < pred (endLeftx) = 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.
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
]
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
standardizeIntervals :: (Ord a, Enum a) => Intervals a -> Intervals a Source
Runs standardizeIntervalSeq on the included and excluded
intervals.
splitIntervals :: (Ord a, Enum a) => Intervals a -> Seq (a, a) Source
Sorts the intervals using standardizeIntervalSeq, and then removes the
excludes with removeExcludes.