trifecta-2.1: A modern parser combinator library with convenient diagnostics

Copyright(C) 2011-2019 Edward Kmett
LicenseBSD-style (see the file LICENSE)
MaintainerEdward Kmett <ekmett@gmail.com>
Stabilityexperimental
Portabilitynon-portable
Safe HaskellSafe
LanguageHaskell2010

Text.Trifecta.Delta

Description

A Delta keeps track of the cursor position of the parser, so it can be referred to later, for example in error messages.

Synopsis

Documentation

data Delta Source #

Since there are multiple ways to be at a certain location, Delta captures all these alternatives as a single type.

Constructors

Columns !Int64 !Int64
( number of characters
, number of bytes )
Tab !Int64 !Int64 !Int64
( number of characters before the tab
, number of characters after the tab
, number of bytes )
Lines !Int64 !Int64 !Int64 !Int64
( number of newlines contained
, number of characters since the last newline
, number of bytes
, number of bytes since the last newline )
Directed !ByteString !Int64 !Int64 !Int64 !Int64
( current file name
, number of lines since the last line directive
, number of characters since the last newline
, number of bytes
, number of bytes since the last newline )
Instances
Eq Delta Source # 
Instance details

Defined in Text.Trifecta.Delta

Methods

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

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

Data Delta Source # 
Instance details

Defined in Text.Trifecta.Delta

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Delta -> c Delta #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Delta #

toConstr :: Delta -> Constr #

dataTypeOf :: Delta -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Delta) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Delta) #

gmapT :: (forall b. Data b => b -> b) -> Delta -> Delta #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Delta -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Delta -> r #

gmapQ :: (forall d. Data d => d -> u) -> Delta -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Delta -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Delta -> m Delta #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Delta -> m Delta #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Delta -> m Delta #

Ord Delta Source # 
Instance details

Defined in Text.Trifecta.Delta

Methods

compare :: Delta -> Delta -> Ordering #

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

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

(>) :: Delta -> Delta -> Bool #

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

max :: Delta -> Delta -> Delta #

min :: Delta -> Delta -> Delta #

Show Delta Source # 
Instance details

Defined in Text.Trifecta.Delta

Methods

showsPrec :: Int -> Delta -> ShowS #

show :: Delta -> String #

showList :: [Delta] -> ShowS #

Generic Delta Source # 
Instance details

Defined in Text.Trifecta.Delta

Associated Types

type Rep Delta :: Type -> Type #

Methods

from :: Delta -> Rep Delta x #

to :: Rep Delta x -> Delta #

Semigroup Delta Source # 
Instance details

Defined in Text.Trifecta.Delta

Methods

(<>) :: Delta -> Delta -> Delta #

sconcat :: NonEmpty Delta -> Delta #

stimes :: Integral b => b -> Delta -> Delta #

Monoid Delta Source # 
Instance details

Defined in Text.Trifecta.Delta

Methods

mempty :: Delta #

mappend :: Delta -> Delta -> Delta #

mconcat :: [Delta] -> Delta #

Hashable Delta Source # 
Instance details

Defined in Text.Trifecta.Delta

Methods

hashWithSalt :: Int -> Delta -> Int #

hash :: Delta -> Int #

HasDelta Delta Source # 
Instance details

Defined in Text.Trifecta.Delta

Methods

delta :: Delta -> Delta Source #

HasBytes Delta Source # 
Instance details

Defined in Text.Trifecta.Delta

Methods

bytes :: Delta -> Int64 Source #

Measured Delta Rope Source # 
Instance details

Defined in Text.Trifecta.Rope

Methods

measure :: Rope -> Delta #

Measured Delta Strand Source # 
Instance details

Defined in Text.Trifecta.Rope

Methods

measure :: Strand -> Delta #

MarkParsing Delta Parser Source # 
Instance details

Defined in Text.Trifecta.Parser

type Rep Delta Source # 
Instance details

Defined in Text.Trifecta.Delta

type Rep Delta = D1 (MetaData "Delta" "Text.Trifecta.Delta" "trifecta-2.1-1VM4tpPDimvdvWAJyZ5f0" False) ((C1 (MetaCons "Columns" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) SourceUnpack SourceStrict DecidedStrict) (Rec0 Int64) :*: S1 (MetaSel (Nothing :: Maybe Symbol) SourceUnpack SourceStrict DecidedStrict) (Rec0 Int64)) :+: C1 (MetaCons "Tab" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) SourceUnpack SourceStrict DecidedStrict) (Rec0 Int64) :*: (S1 (MetaSel (Nothing :: Maybe Symbol) SourceUnpack SourceStrict DecidedStrict) (Rec0 Int64) :*: S1 (MetaSel (Nothing :: Maybe Symbol) SourceUnpack SourceStrict DecidedStrict) (Rec0 Int64)))) :+: (C1 (MetaCons "Lines" PrefixI False) ((S1 (MetaSel (Nothing :: Maybe Symbol) SourceUnpack SourceStrict DecidedStrict) (Rec0 Int64) :*: S1 (MetaSel (Nothing :: Maybe Symbol) SourceUnpack SourceStrict DecidedStrict) (Rec0 Int64)) :*: (S1 (MetaSel (Nothing :: Maybe Symbol) SourceUnpack SourceStrict DecidedStrict) (Rec0 Int64) :*: S1 (MetaSel (Nothing :: Maybe Symbol) SourceUnpack SourceStrict DecidedStrict) (Rec0 Int64))) :+: C1 (MetaCons "Directed" PrefixI False) ((S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 ByteString) :*: S1 (MetaSel (Nothing :: Maybe Symbol) SourceUnpack SourceStrict DecidedStrict) (Rec0 Int64)) :*: (S1 (MetaSel (Nothing :: Maybe Symbol) SourceUnpack SourceStrict DecidedStrict) (Rec0 Int64) :*: (S1 (MetaSel (Nothing :: Maybe Symbol) SourceUnpack SourceStrict DecidedStrict) (Rec0 Int64) :*: S1 (MetaSel (Nothing :: Maybe Symbol) SourceUnpack SourceStrict DecidedStrict) (Rec0 Int64))))))

class HasDelta t where Source #

Methods

delta :: t -> Delta Source #

Instances
HasDelta Char Source # 
Instance details

Defined in Text.Trifecta.Delta

Methods

delta :: Char -> Delta Source #

HasDelta Word8 Source # 
Instance details

Defined in Text.Trifecta.Delta

Methods

delta :: Word8 -> Delta Source #

HasDelta ByteString Source # 
Instance details

Defined in Text.Trifecta.Delta

HasDelta Delta Source # 
Instance details

Defined in Text.Trifecta.Delta

Methods

delta :: Delta -> Delta Source #

HasDelta Rope Source # 
Instance details

Defined in Text.Trifecta.Rope

Methods

delta :: Rope -> Delta Source #

HasDelta Strand Source # 
Instance details

Defined in Text.Trifecta.Rope

Methods

delta :: Strand -> Delta Source #

HasDelta Rendering Source # 
Instance details

Defined in Text.Trifecta.Rendering

HasDelta Caret Source # 
Instance details

Defined in Text.Trifecta.Rendering

Methods

delta :: Caret -> Delta Source #

HasDelta HighlightedRope Source # 
Instance details

Defined in Text.Trifecta.Highlight

HasDelta (Careted a) Source # 
Instance details

Defined in Text.Trifecta.Rendering

Methods

delta :: Careted a -> Delta Source #

HasDelta (Rendered a) Source # 
Instance details

Defined in Text.Trifecta.Rendering

Methods

delta :: Rendered a -> Delta Source #

(HasDelta l, HasDelta r) => HasDelta (Either l r) Source # 
Instance details

Defined in Text.Trifecta.Delta

Methods

delta :: Either l r -> Delta Source #

(Measured v a, HasDelta v) => HasDelta (FingerTree v a) Source # 
Instance details

Defined in Text.Trifecta.Delta

Methods

delta :: FingerTree v a -> Delta Source #

class HasBytes t where Source #

Methods

bytes :: t -> Int64 Source #

Instances
HasBytes ByteString Source # 
Instance details

Defined in Text.Trifecta.Delta

HasBytes Delta Source # 
Instance details

Defined in Text.Trifecta.Delta

Methods

bytes :: Delta -> Int64 Source #

HasBytes Rope Source # 
Instance details

Defined in Text.Trifecta.Rope

Methods

bytes :: Rope -> Int64 Source #

HasBytes Strand Source # 
Instance details

Defined in Text.Trifecta.Rope

Methods

bytes :: Strand -> Int64 Source #

HasBytes Caret Source # 
Instance details

Defined in Text.Trifecta.Rendering

Methods

bytes :: Caret -> Int64 Source #

HasBytes HighlightedRope Source # 
Instance details

Defined in Text.Trifecta.Highlight

HasBytes (Careted a) Source # 
Instance details

Defined in Text.Trifecta.Rendering

Methods

bytes :: Careted a -> Int64 Source #

HasBytes (Rendered a) Source # 
Instance details

Defined in Text.Trifecta.Rendering

Methods

bytes :: Rendered a -> Int64 Source #

(Measured v a, HasBytes v) => HasBytes (FingerTree v a) Source # 
Instance details

Defined in Text.Trifecta.Delta

Methods

bytes :: FingerTree v a -> Int64 Source #

prettyDelta :: Delta -> Doc AnsiStyle Source #

Example: file.txt:12:34

nextTab :: Int64 -> Int64 Source #

Increment a column number to the next tabstop.

rewind :: Delta -> Delta Source #

Rewind a Delta to the beginning of the line.

near :: (HasDelta s, HasDelta t) => s -> t -> Bool Source #

Should we show two things with a Delta on the same line?

>>> near (Columns 0 0) (Columns 5 5)
True
>>> near (Lines 1 0 1 0) (Lines 2 4 4 2)
False

column :: HasDelta t => t -> Int64 Source #

Retrieve the character offset within the current line from this Delta.

columnByte :: Delta -> Int64 Source #

Retrieve the byte offset within the current line from this Delta.