pro-source-0.1.0.0: Utilities for tracking source locations
Copyright© 2020 James Alexander Feldman-Crough
LicenseMPL-2.0
Safe HaskellNone
LanguageHaskell2010

ProSource

Description

 
Synopsis

Source

data 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.

Constructors

Source 

Fields

  • sourceName :: String

    The reported file-name of the Source.

    When read from file handles, a non-filepath description such as "<stdin>" is typically chosen. This field doesn't have semantic meaning, and should only be used to enrich the output displayed to users.

  • sourceText :: Text

    The full source, as Text.

  • sourceLineMap :: LineMap

    A mapping of the start position of each line in the Source.

Instances

Instances details
Eq Source Source # 
Instance details

Defined in ProSource.Source

Methods

(==) :: Source -> Source -> Bool #

(/=) :: Source -> Source -> Bool #

Show Source Source # 
Instance details

Defined in ProSource.Source

Generic Source Source # 
Instance details

Defined in ProSource.Source

Associated Types

type Rep Source :: Type -> Type #

Methods

from :: Source -> Rep Source x #

to :: Rep Source x -> Source #

NFData Source Source # 
Instance details

Defined in ProSource.Source

Methods

rnf :: Source -> () #

Hashable Source Source # 
Instance details

Defined in ProSource.Source

Methods

hashWithSalt :: Int -> Source -> Int #

hash :: Source -> Int #

Pretty Source Source # 
Instance details

Defined in ProSource.Source

Methods

pretty :: Source -> Doc ann #

prettyList :: [Source] -> Doc ann #

type Rep Source Source # 
Instance details

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>.

getSourceLine :: Line -> Source -> Maybe Text Source #

Fetch a single line from a source.

Location

data Location Source #

A location in a Source, with the line and column number computed lazily.

Constructors

Location 

Fields

Instances

Instances details
Eq Location Source # 
Instance details

Defined in ProSource.Location

Show Location Source # 
Instance details

Defined in ProSource.Location

Generic Location Source # 
Instance details

Defined in ProSource.Location

Associated Types

type Rep Location :: Type -> Type #

Methods

from :: Location -> Rep Location x #

to :: Rep Location x -> Location #

NFData Location Source # 
Instance details

Defined in ProSource.Location

Methods

rnf :: Location -> () #

Hashable Location Source # 
Instance details

Defined in ProSource.Location

Methods

hashWithSalt :: Int -> Location -> Int #

hash :: Location -> Int #

Pretty Location Source # 
Instance details

Defined in ProSource.Location

Methods

pretty :: Location -> Doc ann #

prettyList :: [Location] -> Doc ann #

HasLocation Location Source # 
Instance details

Defined in ProSource.HasLocation

type Rep Location Source # 
Instance details

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.

Constructors

SparseLocation 

Fields

Instances

Instances details
Eq SparseLocation Source # 
Instance details

Defined in ProSource.SparseLocation

Show SparseLocation Source # 
Instance details

Defined in ProSource.SparseLocation

Generic SparseLocation Source # 
Instance details

Defined in ProSource.SparseLocation

Associated Types

type Rep SparseLocation :: Type -> Type #

NFData SparseLocation Source # 
Instance details

Defined in ProSource.SparseLocation

Methods

rnf :: SparseLocation -> () #

Hashable SparseLocation Source # 
Instance details

Defined in ProSource.SparseLocation

type Rep SparseLocation Source # 
Instance details

Defined in ProSource.SparseLocation

type Rep SparseLocation = D1 ('MetaData "SparseLocation" "ProSource.SparseLocation" "pro-source-0.1.0.0-Aka5hIIzvNFHIHVEFICznz" 'False) (C1 ('MetaCons "SparseLocation" 'PrefixI 'True) (S1 ('MetaSel ('Just "sparseLocationSource") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Source) :*: S1 ('MetaSel ('Just "sparseLocationOffset") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Offset)))

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

newtype Offset Source #

An offset into a Source, counted by UTF-8 codepoint.

Constructors

Offset Word 

Instances

Instances details
Enum Offset Source # 
Instance details

Defined in ProSource.Offset

Eq Offset Source # 
Instance details

Defined in ProSource.Offset

Methods

(==) :: Offset -> Offset -> Bool #

(/=) :: Offset -> Offset -> Bool #

Ord Offset Source # 
Instance details

Defined in ProSource.Offset

Show Offset Source # 
Instance details

Defined in ProSource.Offset

Generic Offset Source # 
Instance details

Defined in ProSource.Offset

Associated Types

type Rep Offset :: Type -> Type #

Methods

from :: Offset -> Rep Offset x #

to :: Rep Offset x -> Offset #

NFData Offset Source # 
Instance details

Defined in ProSource.Offset

Methods

rnf :: Offset -> () #

Hashable Offset Source # 
Instance details

Defined in ProSource.Offset

Methods

hashWithSalt :: Int -> Offset -> Int #

hash :: Offset -> Int #

Pretty Offset Source # 
Instance details

Defined in ProSource.Offset

Methods

pretty :: Offset -> Doc ann #

prettyList :: [Offset] -> Doc ann #

Unbox Offset Source # 
Instance details

Defined in ProSource.Offset

Vector Vector Offset Source # 
Instance details

Defined in ProSource.Offset

MVector MVector Offset Source # 
Instance details

Defined in ProSource.Offset

type Rep Offset Source # 
Instance details

Defined in ProSource.Offset

type Rep Offset = D1 ('MetaData "Offset" "ProSource.Offset" "pro-source-0.1.0.0-Aka5hIIzvNFHIHVEFICznz" 'True) (C1 ('MetaCons "Offset" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Word)))
newtype Vector Offset Source # 
Instance details

Defined in ProSource.Offset

newtype MVector s Offset Source # 
Instance details

Defined in ProSource.Offset

newtype Line Source #

A line number.

The Show instance for Line counts from one, while the internal implementation counts from zero.

Constructors

Line Word 

Instances

Instances details
Enum Line Source # 
Instance details

Defined in ProSource.Line

Methods

succ :: Line -> Line #

pred :: Line -> Line #

toEnum :: Int -> Line #

fromEnum :: Line -> Int #

enumFrom :: Line -> [Line] #

enumFromThen :: Line -> Line -> [Line] #

enumFromTo :: Line -> Line -> [Line] #

enumFromThenTo :: Line -> Line -> Line -> [Line] #

Eq Line Source # 
Instance details

Defined in ProSource.Line

Methods

(==) :: Line -> Line -> Bool #

(/=) :: Line -> Line -> Bool #

Ord Line Source # 
Instance details

Defined in ProSource.Line

Methods

compare :: Line -> Line -> Ordering #

(<) :: Line -> Line -> Bool #

(<=) :: Line -> Line -> Bool #

(>) :: Line -> Line -> Bool #

(>=) :: Line -> Line -> Bool #

max :: Line -> Line -> Line #

min :: Line -> Line -> Line #

Show Line Source # 
Instance details

Defined in ProSource.Line

Methods

showsPrec :: Int -> Line -> ShowS #

show :: Line -> String #

showList :: [Line] -> ShowS #

Generic Line Source # 
Instance details

Defined in ProSource.Line

Associated Types

type Rep Line :: Type -> Type #

Methods

from :: Line -> Rep Line x #

to :: Rep Line x -> Line #

NFData Line Source # 
Instance details

Defined in ProSource.Line

Methods

rnf :: Line -> () #

Hashable Line Source # 
Instance details

Defined in ProSource.Line

Methods

hashWithSalt :: Int -> Line -> Int #

hash :: Line -> Int #

Pretty Line Source # 
Instance details

Defined in ProSource.Line

Methods

pretty :: Line -> Doc ann #

prettyList :: [Line] -> Doc ann #

type Rep Line Source # 
Instance details

Defined in ProSource.Line

type Rep Line = D1 ('MetaData "Line" "ProSource.Line" "pro-source-0.1.0.0-Aka5hIIzvNFHIHVEFICznz" 'True) (C1 ('MetaCons "Line" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Word)))

newtype Column Source #

A column number.

Constructors

Column Word 

Instances

Instances details
Enum Column Source # 
Instance details

Defined in ProSource.Column

Eq Column Source # 
Instance details

Defined in ProSource.Column

Methods

(==) :: Column -> Column -> Bool #

(/=) :: Column -> Column -> Bool #

Ord Column Source # 
Instance details

Defined in ProSource.Column

Show Column Source # 
Instance details

Defined in ProSource.Column

Generic Column Source # 
Instance details

Defined in ProSource.Column

Associated Types

type Rep Column :: Type -> Type #

Methods

from :: Column -> Rep Column x #

to :: Rep Column x -> Column #

NFData Column Source # 
Instance details

Defined in ProSource.Column

Methods

rnf :: Column -> () #

Hashable Column Source # 
Instance details

Defined in ProSource.Column

Methods

hashWithSalt :: Int -> Column -> Int #

hash :: Column -> Int #

Pretty Column Source # 
Instance details

Defined in ProSource.Column

Methods

pretty :: Column -> Doc ann #

prettyList :: [Column] -> Doc ann #

type Rep Column Source # 
Instance details

Defined in ProSource.Column

type Rep Column = D1 ('MetaData "Column" "ProSource.Column" "pro-source-0.1.0.0-Aka5hIIzvNFHIHVEFICznz" 'True) (C1 ('MetaCons "Column" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Word)))

Line map

data LineMap Source #

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.

Instances

Instances details
Eq LineMap Source # 
Instance details

Defined in ProSource.LineMap

Methods

(==) :: LineMap -> LineMap -> Bool #

(/=) :: LineMap -> LineMap -> Bool #

Show LineMap Source # 
Instance details

Defined in ProSource.LineMap

Generic LineMap Source # 
Instance details

Defined in ProSource.LineMap

Associated Types

type Rep LineMap :: Type -> Type #

Methods

from :: LineMap -> Rep LineMap x #

to :: Rep LineMap x -> LineMap #

NFData LineMap Source # 
Instance details

Defined in ProSource.LineMap

Methods

rnf :: LineMap -> () #

Hashable LineMap Source # 
Instance details

Defined in ProSource.LineMap

Methods

hashWithSalt :: Int -> LineMap -> Int #

hash :: LineMap -> Int #

type Rep LineMap Source # 
Instance details

Defined in ProSource.LineMap

type Rep LineMap = D1 ('MetaData "LineMap" "ProSource.LineMap" "pro-source-0.1.0.0-Aka5hIIzvNFHIHVEFICznz" 'True) (C1 ('MetaCons "LineMap" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Vector Offset))))

lineOffsets :: LineMap -> [Offset] Source #

Convert a LineMap into a list of Offsets, corresponding to the first character of a line. Note that the initial offset is omitted-- the offset at index 0 will be the offset of the second line.

lineToOffset :: Line -> LineMap -> Maybe Offset Source #

Fetch the Offset for the given Line. Evaluates to Nothing if the given Line does not appear in the LineMap

offsetToLine :: Offset -> LineMap -> Line Source #

Fetch the Line number for a given Offset. Newlines will be attributed the line that they terminate, rather than the line started immediately afterwards.

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

Instances details
HasLocation Location Source # 
Instance details

Defined in ProSource.HasLocation

offset :: HasLocation l => AffineTraversal' l Offset Source #

Focus on the Offset from a value parsed from a source file. If the Offset is modified, note that the resulting column and line will also be modified as they are denormalizations of this value.

column :: HasLocation l => AffineFold l Column Source #

Fetch the Column from a value parsed from a source file. Modifications are not allowed as the offset and line may become inconsistent.

line :: HasLocation l => AffineFold l Line Source #

Fetch the Line from a value parsed from a source file. Modifications are not allowed as the offset and column may become inconsistent.

source :: HasLocation l => AffineFold l Source Source #

Fetch the Source a value was parsed from. Modifications are not allowed as the line, offset, and column may become inconsistent.