haskell-src-exts-1.17.0: Manipulating Haskell source: abstract syntax, lexer, parser, and pretty-printer

Copyright(c) Niklas Broberg 2009
LicenseBSD-style (see the file LICENSE.txt)
MaintainerNiklas Broberg, d00nibro@chalmers.se
Stabilitystable
Portabilityportable
Safe HaskellSafe
LanguageHaskell98

Language.Haskell.Exts.SrcLoc

Description

This module defines various data types representing source location information, of varying degree of preciseness.

Synopsis

Documentation

data SrcLoc Source

A single position in the source.

Constructors

SrcLoc 

Instances

Eq SrcLoc Source 

Methods

(==) :: SrcLoc -> SrcLoc -> Bool

(/=) :: SrcLoc -> SrcLoc -> Bool

Data SrcLoc Source 

Methods

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

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

toConstr :: SrcLoc -> Constr

dataTypeOf :: SrcLoc -> DataType

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

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

gmapT :: (forall b. Data b => b -> b) -> SrcLoc -> SrcLoc

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

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

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

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

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

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

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

Ord SrcLoc Source 
Show SrcLoc Source 
Generic SrcLoc Source 

Associated Types

type Rep SrcLoc :: * -> *

Methods

from :: SrcLoc -> Rep SrcLoc x

to :: Rep SrcLoc x -> SrcLoc

SrcInfo SrcLoc Source 
Pretty SrcLoc Source 

Methods

pretty :: SrcLoc -> Doc

prettyPrec :: Int -> SrcLoc -> Doc

type Rep SrcLoc Source 

data SrcSpan Source

A portion of the source, spanning one or more lines and zero or more columns.

Instances

Eq SrcSpan Source 

Methods

(==) :: SrcSpan -> SrcSpan -> Bool

(/=) :: SrcSpan -> SrcSpan -> Bool

Data SrcSpan Source 

Methods

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

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

toConstr :: SrcSpan -> Constr

dataTypeOf :: SrcSpan -> DataType

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

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

gmapT :: (forall b. Data b => b -> b) -> SrcSpan -> SrcSpan

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

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

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

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

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

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

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

Ord SrcSpan Source 
Show SrcSpan Source 
SrcInfo SrcSpan Source 
Pretty SrcSpan Source 

Methods

pretty :: SrcSpan -> Doc

prettyPrec :: Int -> SrcSpan -> Doc

mkSrcSpan :: SrcLoc -> SrcLoc -> SrcSpan Source

Combine two locations in the source to denote a span.

mergeSrcSpan :: SrcSpan -> SrcSpan -> SrcSpan Source

Merge two source spans into a single span from the start of the first to the end of the second. Assumes that the two spans relate to the same source file.

isNullSpan :: SrcSpan -> Bool Source

Test if a given span starts and ends at the same location.

data Loc a Source

An entity located in the source.

Constructors

Loc 

Fields

Instances

Eq a => Eq (Loc a) Source 

Methods

(==) :: Loc a -> Loc a -> Bool

(/=) :: Loc a -> Loc a -> Bool

Ord a => Ord (Loc a) Source 

Methods

compare :: Loc a -> Loc a -> Ordering

(<) :: Loc a -> Loc a -> Bool

(<=) :: Loc a -> Loc a -> Bool

(>) :: Loc a -> Loc a -> Bool

(>=) :: Loc a -> Loc a -> Bool

max :: Loc a -> Loc a -> Loc a

min :: Loc a -> Loc a -> Loc a

Show a => Show (Loc a) Source 

Methods

showsPrec :: Int -> Loc a -> ShowS

show :: Loc a -> String

showList :: [Loc a] -> ShowS

data SrcSpanInfo Source

A portion of the source, extended with information on the position of entities within the span.

Constructors

SrcSpanInfo 

Instances

Eq SrcSpanInfo Source 
Data SrcSpanInfo Source 

Methods

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

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

toConstr :: SrcSpanInfo -> Constr

dataTypeOf :: SrcSpanInfo -> DataType

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

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

gmapT :: (forall b. Data b => b -> b) -> SrcSpanInfo -> SrcSpanInfo

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

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

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

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

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

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

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

Ord SrcSpanInfo Source 
Show SrcSpanInfo Source 
SrcInfo SrcSpanInfo Source 
Parseable (NonGreedy (ListOf (ModulePragma SrcSpanInfo))) Source 
Parseable (NonGreedy (ModuleHeadAndImports SrcSpanInfo)) Source 
Parseable (NonGreedy (PragmasAndModuleHead SrcSpanInfo)) Source 
Parseable (NonGreedy (PragmasAndModuleName SrcSpanInfo)) Source 

noInfoSpan :: SrcSpan -> SrcSpanInfo Source

Generate a SrcSpanInfo with no positional information for entities.

infoSpan :: SrcSpan -> [SrcSpan] -> SrcSpanInfo Source

Generate a SrcSpanInfo with the supplied positional information for entities.

combSpanInfo :: SrcSpanInfo -> SrcSpanInfo -> SrcSpanInfo Source

Combine two SrcSpanInfos into one that spans the combined source area of the two arguments, leaving positional information blank.

combSpanMaybe :: SrcSpanInfo -> Maybe SrcSpanInfo -> SrcSpanInfo Source

Like '(+?)', but it also concatenates the srcInfoPoints.

(<+?>) :: SrcSpanInfo -> Maybe SrcSpanInfo -> SrcSpanInfo infixl 4 Source

Optionally combine the first argument with the second, or return it unchanged if the second argument is Nothing.

(<?+>) :: Maybe SrcSpanInfo -> SrcSpanInfo -> SrcSpanInfo infixl 4 Source

Optionally combine the second argument with the first, or return it unchanged if the first argument is Nothing.

(<**) :: SrcSpanInfo -> [SrcSpan] -> SrcSpanInfo infixl 4 Source

Add more positional information for entities of a span.

(<^^>) :: SrcSpan -> SrcSpan -> SrcSpanInfo infixl 6 Source

Merge two SrcSpans and lift them to a SrcInfoSpan with no positional information for entities.