| Copyright | © 2015–2018 Megaparsec contributors | 
|---|---|
| License | FreeBSD | 
| Maintainer | Mark Karpov <markkarpov92@gmail.com> | 
| Stability | experimental | 
| Portability | portable | 
| Safe Haskell | None | 
| Language | Haskell2010 | 
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
- data Pos
 - mkPos :: Int -> Pos
 - unPos :: Pos -> Int
 - pos1 :: Pos
 - defaultTabWidth :: Pos
 - data InvalidPosException = InvalidPosException Int
 - data SourcePos = SourcePos {
- sourceName :: FilePath
 - sourceLine :: !Pos
 - sourceColumn :: !Pos
 
 - initialPos :: FilePath -> SourcePos
 - sourcePosPretty :: SourcePos -> String
 
Abstract position
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: megaparsec-5.0.0
Instances
| Eq Pos Source # | |
| Data Pos Source # | |
Defined in Text.Megaparsec.Pos 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 # 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 # | |
| Read Pos Source # | |
| Show Pos Source # | |
| Semigroup Pos Source # | |
| NFData Pos Source # | |
Defined in Text.Megaparsec.Pos  | |
Construction of Pos from Int. The function throws
 InvalidPosException when given a non-positive argument.
Since: megaparsec-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: megaparsec-5.0.0
data InvalidPosException Source #
The exception is thrown by mkPos when its argument is not a positive
 number.
Since: megaparsec-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   | 
Instances
Source position
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 # | |
Defined in Text.Megaparsec.Pos 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 # | |
| NFData SourcePos Source # | |
Defined in Text.Megaparsec.Pos  | |
| type Rep SourcePos Source # | |
Defined in Text.Megaparsec.Pos type Rep SourcePos = D1 (MetaData "SourcePos" "Text.Megaparsec.Pos" "megaparsec-6.5.0-4VKBtSFJhna3iLscGKIZAP" False) (C1 (MetaCons "SourcePos" PrefixI True) (S1 (MetaSel (Just "sourceName") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 FilePath) :*: (S1 (MetaSel (Just "sourceLine") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Pos) :*: S1 (MetaSel (Just "sourceColumn") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Pos))))  | |
initialPos :: FilePath -> SourcePos Source #
Construct initial position (line 1, column 1) given name of source file.