prosidy-1.5.0.1: A simple language for writing documents.
Copyright©2020 James Alexander Feldman-Crough
LicenseMPL-2.0
Maintaineralex@fldcr.com
Safe HaskellNone
LanguageHaskell2010

Prosidy.Source

Description

 
Synopsis

Documentation

data Source Source #

Information about Prosidy 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 Prosidy.Source

Methods

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

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

Show Source Source # 
Instance details

Defined in Prosidy.Source

Generic Source Source # 
Instance details

Defined in Prosidy.Source

Associated Types

type Rep Source :: Type -> Type #

Methods

from :: Source -> Rep Source x #

to :: Rep Source x -> Source #

Hashable Source Source # 
Instance details

Defined in Prosidy.Source

Methods

hashWithSalt :: Int -> Source -> Int #

hash :: Source -> Int #

Binary Source Source # 
Instance details

Defined in Prosidy.Source

Methods

put :: Source -> Put #

get :: Get Source #

putList :: [Source] -> Put #

NFData Source Source # 
Instance details

Defined in Prosidy.Source

Methods

rnf :: Source -> () #

type Rep Source Source # 
Instance details

Defined in Prosidy.Source

type Rep Source = D1 ('MetaData "Source" "Prosidy.Source" "prosidy-1.5.0.1-inplace" '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))))

data Location Source #

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

Instances

Instances details
Eq Location Source # 
Instance details

Defined in Prosidy.Source

Show Location Source # 
Instance details

Defined in Prosidy.Source

Generic Location Source # 
Instance details

Defined in Prosidy.Source

Associated Types

type Rep Location :: Type -> Type #

Methods

from :: Location -> Rep Location x #

to :: Rep Location x -> Location #

Hashable Location Source # 
Instance details

Defined in Prosidy.Source

Methods

hashWithSalt :: Int -> Location -> Int #

hash :: Location -> Int #

Binary Location Source # 
Instance details

Defined in Prosidy.Source

Methods

put :: Location -> Put #

get :: Get Location #

putList :: [Location] -> Put #

NFData Location Source # 
Instance details

Defined in Prosidy.Source

Methods

rnf :: Location -> () #

HasLocation Location Source # 
Instance details

Defined in Prosidy.Optics.Source

Methods

location :: Affine' Location Location Source #

type Rep Location Source # 
Instance details

Defined in Prosidy.Source

type Rep Location = D1 ('MetaData "Location" "Prosidy.Source" "prosidy-1.5.0.1-inplace" '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 Prosidy.Source

Show SparseLocation Source # 
Instance details

Defined in Prosidy.Source

Generic SparseLocation Source # 
Instance details

Defined in Prosidy.Source

Associated Types

type Rep SparseLocation :: Type -> Type #

Hashable SparseLocation Source # 
Instance details

Defined in Prosidy.Source

Binary SparseLocation Source # 
Instance details

Defined in Prosidy.Source

NFData SparseLocation Source # 
Instance details

Defined in Prosidy.Source

Methods

rnf :: SparseLocation -> () #

type Rep SparseLocation Source # 
Instance details

Defined in Prosidy.Source

type Rep SparseLocation = D1 ('MetaData "SparseLocation" "Prosidy.Source" "prosidy-1.5.0.1-inplace" 'False) (C1 ('MetaCons "SparseLocation" 'PrefixI 'True) (S1 ('MetaSel ('Just "sparseLocationSource") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Source) :*: S1 ('MetaSel ('Just "sparseLocationOffset") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Offset)))

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

Methods

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

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

Show LineMap Source # 
Instance details

Defined in Prosidy.Source

Generic LineMap Source # 
Instance details

Defined in Prosidy.Source

Associated Types

type Rep LineMap :: Type -> Type #

Methods

from :: LineMap -> Rep LineMap x #

to :: Rep LineMap x -> LineMap #

Hashable LineMap Source # 
Instance details

Defined in Prosidy.Source

Methods

hashWithSalt :: Int -> LineMap -> Int #

hash :: LineMap -> Int #

Binary LineMap Source # 
Instance details

Defined in Prosidy.Source

Methods

put :: LineMap -> Put #

get :: Get LineMap #

putList :: [LineMap] -> Put #

NFData LineMap Source # 
Instance details

Defined in Prosidy.Source

Methods

rnf :: LineMap -> () #

type Rep LineMap Source # 
Instance details

Defined in Prosidy.Source

type Rep LineMap = D1 ('MetaData "LineMap" "Prosidy.Source" "prosidy-1.5.0.1-inplace" 'True) (C1 ('MetaCons "LineMap" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Vector Offset))))

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

Eq Offset Source # 
Instance details

Defined in Prosidy.Source

Methods

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

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

Ord Offset Source # 
Instance details

Defined in Prosidy.Source

Show Offset Source # 
Instance details

Defined in Prosidy.Source

Generic Offset Source # 
Instance details

Defined in Prosidy.Source

Associated Types

type Rep Offset :: Type -> Type #

Methods

from :: Offset -> Rep Offset x #

to :: Rep Offset x -> Offset #

Hashable Offset Source # 
Instance details

Defined in Prosidy.Source

Methods

hashWithSalt :: Int -> Offset -> Int #

hash :: Offset -> Int #

ToJSON Offset Source # 
Instance details

Defined in Prosidy.Source

FromJSON Offset Source # 
Instance details

Defined in Prosidy.Source

Binary Offset Source # 
Instance details

Defined in Prosidy.Source

Methods

put :: Offset -> Put #

get :: Get Offset #

putList :: [Offset] -> Put #

NFData Offset Source # 
Instance details

Defined in Prosidy.Source

Methods

rnf :: Offset -> () #

Unbox Offset Source # 
Instance details

Defined in Prosidy.Source

Vector Vector Offset Source # 
Instance details

Defined in Prosidy.Source

MVector MVector Offset Source # 
Instance details

Defined in Prosidy.Source

type Rep Offset Source # 
Instance details

Defined in Prosidy.Source

type Rep Offset = D1 ('MetaData "Offset" "Prosidy.Source" "prosidy-1.5.0.1-inplace" 'True) (C1 ('MetaCons "Offset" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Word)))
newtype Vector Offset Source # 
Instance details

Defined in Prosidy.Source

newtype MVector s Offset Source # 
Instance details

Defined in Prosidy.Source

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

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

Methods

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

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

Ord Line Source # 
Instance details

Defined in Prosidy.Source

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

Methods

showsPrec :: Int -> Line -> ShowS #

show :: Line -> String #

showList :: [Line] -> ShowS #

Generic Line Source # 
Instance details

Defined in Prosidy.Source

Associated Types

type Rep Line :: Type -> Type #

Methods

from :: Line -> Rep Line x #

to :: Rep Line x -> Line #

Hashable Line Source # 
Instance details

Defined in Prosidy.Source

Methods

hashWithSalt :: Int -> Line -> Int #

hash :: Line -> Int #

ToJSON Line Source # 
Instance details

Defined in Prosidy.Source

FromJSON Line Source # 
Instance details

Defined in Prosidy.Source

Binary Line Source # 
Instance details

Defined in Prosidy.Source

Methods

put :: Line -> Put #

get :: Get Line #

putList :: [Line] -> Put #

NFData Line Source # 
Instance details

Defined in Prosidy.Source

Methods

rnf :: Line -> () #

type Rep Line Source # 
Instance details

Defined in Prosidy.Source

type Rep Line = D1 ('MetaData "Line" "Prosidy.Source" "prosidy-1.5.0.1-inplace" '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 Prosidy.Source

Eq Column Source # 
Instance details

Defined in Prosidy.Source

Methods

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

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

Ord Column Source # 
Instance details

Defined in Prosidy.Source

Show Column Source # 
Instance details

Defined in Prosidy.Source

Generic Column Source # 
Instance details

Defined in Prosidy.Source

Associated Types

type Rep Column :: Type -> Type #

Methods

from :: Column -> Rep Column x #

to :: Rep Column x -> Column #

Hashable Column Source # 
Instance details

Defined in Prosidy.Source

Methods

hashWithSalt :: Int -> Column -> Int #

hash :: Column -> Int #

ToJSON Column Source # 
Instance details

Defined in Prosidy.Source

FromJSON Column Source # 
Instance details

Defined in Prosidy.Source

Binary Column Source # 
Instance details

Defined in Prosidy.Source

Methods

put :: Column -> Put #

get :: Get Column #

putList :: [Column] -> Put #

NFData Column Source # 
Instance details

Defined in Prosidy.Source

Methods

rnf :: Column -> () #

type Rep Column Source # 
Instance details

Defined in Prosidy.Source

type Rep Column = D1 ('MetaData "Column" "Prosidy.Source" "prosidy-1.5.0.1-inplace" 'True) (C1 ('MetaCons "Column" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Word)))

locationSource :: Location -> Source Source #

The Source this location references.

locationColumn :: Location -> Column Source #

The column number in the Source.

locationLine :: Location -> Line Source #

The line number in the Source.

locationOffset :: Location -> Offset Source #

The position in the Source, counted by Unicode codepoints.

makeSource :: String -> Text -> Source Source #

Create a Source from a descriptive name and a body. The source name is typically a FilePath, but this is not guarenteed. For instance, when read from standard-input, Prosidy chooses to name the source <stdin>.

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

Fetch a single line from a source.

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.

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.