Copyright | Copyright 2017 Awake Security |
---|---|
License | Apache-2.0 |
Maintainer | opensource@awakesecurity.com |
Stability | experimental |
Safe Haskell | None |
Language | Haskell2010 |
Tokenize text into a list of non-whitespace chunks, each of which is annotated with its source location.
Since: 0.1.0
- data Located t
- tokenize :: Maybe Path -> Text -> [Located Text]
- tokenizeFile :: MonadReadFile m => Path -> m [Located Text]
- tokenizeText :: Text -> [Located Text]
- locatedPos :: Lens' (Located t) Position
- locatedVal :: Lens' (Located t) t
- data Spans
- makeSpans :: [Span] -> Spans
- spansSet :: Iso' Spans (HashSet Span)
- data Span
- makeSpan :: Maybe Path -> Offset -> Offset -> Span
- spanPath :: Lens' Span (Maybe Path)
- spanRange :: Lens' Span (Offset, Offset)
- spanStart :: Lens' Span Offset
- spanEnd :: Lens' Span Offset
- spanStartPos :: Getter Span Position
- spanEndPos :: Getter Span Position
- data Position
- makePosition :: Maybe Path -> Offset -> Position
- positionFile :: Lens' Position (Maybe Path)
- positionOffset :: Lens' Position Offset
- positionLine :: Lens' Position Line
- positionCol :: Lens' Position Column
- comparePosition :: Position -> Position -> Maybe Ordering
- type Offset = (Line, Column)
- compareOffset :: Offset -> Offset -> Ordering
- offsetLine :: Lens' Offset Line
- offsetColumn :: Lens' Offset Column
- type Line = Int
- type Column = Int
Located
This datatype represents a value annotated with a source location.
Since: 0.1.0
Functor Located Source # | |
Foldable Located Source # | |
Traversable Located Source # | |
(Monad m, Serial m Text, Serial m t) => Serial m (Located t) Source # | Default Since: 0.1.0 |
(Monad m, CoSerial m Text, CoSerial m t) => CoSerial m (Located t) Source # | Default Since: 0.1.0 |
Eq t => Eq (Located t) Source # | |
Show t => Show (Located t) Source # | |
Generic (Located t) Source # | |
Hashable t => Hashable (Located t) Source # | Default Since: 0.1.0 |
ToJSON t => ToJSON (Located t) Source # | Converts to Since: 0.1.0 |
FromJSON t => FromJSON (Located t) Source # | Inverse of the Since: 0.1.0 |
NFData t => NFData (Located t) Source # | Default Since: 0.1.0 |
type Rep (Located t) Source # | |
tokenizeFile :: MonadReadFile m => Path -> m [Located Text] Source #
tokenizeText :: Text -> [Located Text] Source #
This function is equivalent to tokenize Nothing
.
Since: 0.1.0
locatedVal :: Lens' (Located t) t Source #
The value underlying this located value.
Since: 0.1.0
Spans
A type representing a set of source spans.
Since: 0.1.0
Eq Spans Source # | |
Show Spans Source # | |
Generic Spans Source # | |
Semigroup Spans Source # | |
Monoid Spans Source # | |
Hashable Spans Source # | |
ToJSON Spans Source # | |
FromJSON Spans Source # | |
NFData Spans Source # | |
(Monad m, Serial m (HashSet Span)) => Serial m Spans Source # | Default Since: 0.1.0 |
(Monad m, CoSerial m (HashSet Span)) => CoSerial m Spans Source # | Default Since: 0.1.0 |
type Rep Spans Source # | |
Span
Represents a span of source code.
Since: 0.1.0
Eq Span Source # | |
Show Span Source # | |
Generic Span Source # | |
Hashable Span Source # | Default Since: 0.1.0 |
ToJSON Span Source # | Converts to Since: 0.1.0 |
FromJSON Span Source # | Inverse of the Since: 0.1.0 |
NFData Span Source # | Default Since: 0.1.0 |
(Monad m, Serial m Text) => Serial m Span Source # | Default Since: 0.1.0 |
(Monad m, CoSerial m Text) => CoSerial m Span Source # | Default Since: 0.1.0 |
type Rep Span Source # | |
:: Maybe Path | The file in which this span resides, if any. |
-> Offset | The start offset. |
-> Offset | The end offset. |
-> Span |
Construct a Span
from a given start position to a given end position.
Since: 0.1.0
spanPath :: Lens' Span (Maybe Path) Source #
A lens into the (nullable) path associated with a Span
.
Since: 0.1.0
Position
This datatype represents the position of a cursor in a text file.
Since: 0.1.0
Eq Position Source # | |
Show Position Source # | |
Generic Position Source # | |
Hashable Position Source # | Default Since: 0.1.0 |
ToJSON Position Source # | Converts to Since: 0.1.0 |
FromJSON Position Source # | Inverse of the Since: 0.1.0 |
NFData Position Source # | Default Since: 0.1.0 |
(Monad m, Serial m Text) => Serial m Position Source # | Default Since: 0.1.0 |
(Monad m, CoSerial m Text) => CoSerial m Position Source # | Default Since: 0.1.0 |
type Rep Position Source # | |
makePosition :: Maybe Path -> Offset -> Position Source #
Construct a Position
from a (nullable) path and a (line, column)
pair.
Since: 0.1.0
positionFile :: Lens' Position (Maybe Path) Source #
The path of the file pointed to by this position, if any.
Since: 0.1.0
positionOffset :: Lens' Position Offset Source #
The offset in the file pointed to by this position.
Since: 0.1.0
positionLine :: Lens' Position Line Source #
The line number in the file pointed to by this position.
Since: 0.1.0
positionCol :: Lens' Position Column Source #
The column number in the line pointed to by this position.
Since: 0.1.0
Offset
offsetColumn :: Lens' Offset Column Source #
A lens into the Line
associated with an Offset
.
Read the description of offsetLine
for an understanding of why this
exists and why you should use it instead of _2
.
Since: 0.1.0