megaparsec-6.2.0: Monadic parser combinators

Copyright© 2015–2017 Megaparsec contributors
LicenseFreeBSD
MaintainerMark Karpov <markkarpov92@gmail.com>
Stabilityexperimental
Portabilityportable
Safe HaskellNone
LanguageHaskell2010

Text.Megaparsec.Pos

Contents

Description

Textual source position. The position includes name of file, line number, and column number. List of such positions can be used to model a stack of include files.

You probably do not want to import this module directly because Text.Megaparsec re-exports it anyway.

Synopsis

Abstract position

data Pos Source #

Pos is the type for positive integers. This is used to represent line number, column number, and similar things like indentation level. Semigroup instance can be used to safely and efficiently add Poses together.

Since: 5.0.0

Instances

Eq Pos Source # 

Methods

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

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

Data Pos Source # 

Methods

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

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

toConstr :: Pos -> Constr #

dataTypeOf :: Pos -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord Pos Source # 

Methods

compare :: Pos -> Pos -> Ordering #

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

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

(>) :: Pos -> Pos -> Bool #

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

max :: Pos -> Pos -> Pos #

min :: Pos -> Pos -> Pos #

Read Pos Source # 
Show Pos Source # 

Methods

showsPrec :: Int -> Pos -> ShowS #

show :: Pos -> String #

showList :: [Pos] -> ShowS #

Semigroup Pos Source # 

Methods

(<>) :: Pos -> Pos -> Pos #

sconcat :: NonEmpty Pos -> Pos #

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

NFData Pos Source # 

Methods

rnf :: Pos -> () #

mkPos :: Int -> Pos Source #

Construction of Pos from Int. The function throws InvalidPosException when given a non-positive argument.

Since: 6.0.0

unPos :: Pos -> Int Source #

Extract Int from Pos.

Since: 6.0.0

pos1 :: Pos Source #

Position with value 1.

Since: 6.0.0

defaultTabWidth :: Pos Source #

Value of tab width used by default. Always prefer this constant when you want to refer to the default tab width because actual value may change in future.

Since: 5.0.0

data InvalidPosException Source #

The exception is thrown by mkPos when its argument is not a positive number.

Since: 5.0.0

Constructors

InvalidPosException Int

The first value is the minimal allowed value, the second value is the actual value that was passed to mkPos.

Instances

Eq InvalidPosException Source # 
Data InvalidPosException Source # 

Methods

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

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

toConstr :: InvalidPosException -> Constr #

dataTypeOf :: InvalidPosException -> DataType #

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

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

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

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

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

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

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

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

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

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

Show InvalidPosException Source # 
Generic InvalidPosException Source # 
Exception InvalidPosException Source # 
NFData InvalidPosException Source # 

Methods

rnf :: InvalidPosException -> () #

type Rep InvalidPosException Source # 
type Rep InvalidPosException = D1 (MetaData "InvalidPosException" "Text.Megaparsec.Pos" "megaparsec-6.2.0-pWtGle4bFH9yv4IfTZKBA" False) (C1 (MetaCons "InvalidPosException" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Int)))

Source position

data SourcePos Source #

The data type SourcePos represents source positions. It contains the name of the source file, a line number, and a column number. Source line and column positions change intensively during parsing, so we need to make them strict to avoid memory leaks.

Constructors

SourcePos 

Fields

Instances

Eq SourcePos Source # 
Data SourcePos Source # 

Methods

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

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

toConstr :: SourcePos -> Constr #

dataTypeOf :: SourcePos -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord SourcePos Source # 
Read SourcePos Source # 
Show SourcePos Source # 
Generic SourcePos Source # 

Associated Types

type Rep SourcePos :: * -> * #

NFData SourcePos Source # 

Methods

rnf :: SourcePos -> () #

type Rep SourcePos Source # 
type Rep SourcePos = D1 (MetaData "SourcePos" "Text.Megaparsec.Pos" "megaparsec-6.2.0-pWtGle4bFH9yv4IfTZKBA" False) (C1 (MetaCons "SourcePos" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "sourceName") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 FilePath)) ((:*:) (S1 (MetaSel (Just Symbol "sourceLine") NoSourceUnpackedness SourceStrict DecidedUnpack) (Rec0 Pos)) (S1 (MetaSel (Just Symbol "sourceColumn") NoSourceUnpackedness SourceStrict DecidedUnpack) (Rec0 Pos)))))

initialPos :: FilePath -> SourcePos Source #

Construct initial position (line 1, column 1) given name of source file.

sourcePosPretty :: SourcePos -> String Source #

Pretty-print a SourcePos.

Since: 5.0.0