Copyright | © 2020 James Alexander Feldman-Crough |
---|---|
License | MPL-2.0 |
Safe Haskell | None |
Language | Haskell2010 |
Synopsis
- data Source = Source {}
- makeSource :: String -> LText -> Source
- getSourceLine :: Line -> Source -> Maybe Text
- getLocation :: Offset -> Source -> Maybe Location
- data Location = Location {}
- data SparseLocation = SparseLocation {}
- enrichLocation :: SparseLocation -> Location
- stripLocation :: Location -> SparseLocation
- sparse :: Iso' Location SparseLocation
- newtype Offset = Offset Word
- newtype Line = Line Word
- newtype Column = Column Word
- data LineMap
- lineOffsets :: LineMap -> [Offset]
- lineToOffset :: Line -> LineMap -> Maybe Offset
- offsetToLine :: Offset -> LineMap -> Line
- class HasLocation t where
- offset :: HasLocation l => AffineTraversal' l Offset
- column :: HasLocation l => AffineFold l Column
- line :: HasLocation l => AffineFold l Line
- source :: HasLocation l => AffineFold l Source
Source
Information about a source file.
The Show
instance for ths class does not include the LineMap
or Text
fields, as those are rather noisy.
Source | |
|
Instances
Eq Source Source # | |
Show Source Source # | |
Generic Source Source # | |
NFData Source Source # | |
Defined in ProSource.Source | |
Hashable Source Source # | |
Defined in ProSource.Source | |
Pretty Source Source # | |
Defined in ProSource.Source | |
type Rep Source Source # | |
Defined in ProSource.Source type Rep Source = D1 ('MetaData "Source" "ProSource.Source" "pro-source-0.1.0.0-Aka5hIIzvNFHIHVEFICznz" 'False) (C1 ('MetaCons "Source" 'PrefixI 'True) (S1 ('MetaSel ('Just "sourceName") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 String) :*: (S1 ('MetaSel ('Just "sourceText") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Text) :*: S1 ('MetaSel ('Just "sourceLineMap") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 LineMap)))) |
makeSource :: String -> LText -> Source Source #
Create a Source
from a descriptive name and a body. The source name is typically a FilePath
, but this is not guaranteed. For instance, when read from standard-input, a common choice is to name the source <stdin>
.
Location
A location in a Source
, with the line and column number computed lazily.
Location | |
|
Instances
Eq Location Source # | |
Show Location Source # | |
Generic Location Source # | |
NFData Location Source # | |
Defined in ProSource.Location | |
Hashable Location Source # | |
Defined in ProSource.Location | |
Pretty Location Source # | |
Defined in ProSource.Location | |
HasLocation Location Source # | |
Defined in ProSource.HasLocation | |
type Rep Location Source # | |
Defined in ProSource.Location type Rep Location = D1 ('MetaData "Location" "ProSource.Location" "pro-source-0.1.0.0-Aka5hIIzvNFHIHVEFICznz" 'False) (C1 ('MetaCons "Location" 'PrefixI 'True) ((S1 ('MetaSel ('Just "locationSource") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Source) :*: S1 ('MetaSel ('Just "locationOffset") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Offset)) :*: (S1 ('MetaSel ('Just "locationLine") 'NoSourceUnpackedness 'SourceLazy 'DecidedLazy) (Rec0 Line) :*: S1 ('MetaSel ('Just "locationColumn") 'NoSourceUnpackedness 'SourceLazy 'DecidedLazy) (Rec0 Column)))) |
data SparseLocation Source #
A location in a Source
. The line and column numbers of this type are not attached to this type; convert to a Location
to access those values.
SparseLocation | |
|
Instances
enrichLocation :: SparseLocation -> Location Source #
Add lazily computed line and column number information to a SparseLocation
.
stripLocation :: Location -> SparseLocation Source #
Remove line and column number information from a Location
.
sparse :: Iso' Location SparseLocation Source #
An isomorphism between Location
and SparseLocation
. This is allowed because although a Location
has strictly more data than a SparseLocation
, those values are denormalizations of values within SparseLocation
.
Units
An offset into a Source
, counted by UTF-8 codepoint.
Instances
A line number.
The Show
instance for Line
counts from one, while the internal implementation counts from zero.
A column number.
Instances
Enum Column Source # | |
Defined in ProSource.Column | |
Eq Column Source # | |
Ord Column Source # | |
Show Column Source # | |
Generic Column Source # | |
NFData Column Source # | |
Defined in ProSource.Column | |
Hashable Column Source # | |
Defined in ProSource.Column | |
Pretty Column Source # | |
Defined in ProSource.Column | |
type Rep Column Source # | |
Defined in ProSource.Column |
Line map
A dense vector containing offsets poiting to the start of each line. That is, the starting position of the third line of a file can be found at position 2.
lineOffsets :: LineMap -> [Offset] Source #
Polymorphic Location optics
class HasLocation t where Source #
A classy optic for selecting the Location
from a value. Note that location
is affine: a Location
can't be attached to a value which does not -- already have one, and not all values with an instance of HasLocation
have a location.
Instances
HasLocation Location Source # | |
Defined in ProSource.HasLocation |
offset :: HasLocation l => AffineTraversal' l Offset Source #
column :: HasLocation l => AffineFold l Column Source #
line :: HasLocation l => AffineFold l Line Source #
source :: HasLocation l => AffineFold l Source Source #