language-python-0.5.8: Parsing and pretty printing of Python code.

Copyright(c) 2009 Bernie Pope
LicenseBSD-style
Maintainerbjpop@csse.unimelb.edu.au
Stabilityexperimental
Portabilityghc
Safe HaskellSafe
LanguageHaskell2010

Language.Python.Common.SrcLocation

Contents

Description

Source location information for the Python lexer and parser. This module provides single-point locations and spans, and conversions between them.

Synopsis

Construction

data SrcLocation Source #

A location for a syntactic entity from the source code. The location is specified by its filename, and starting row and column.

Constructors

Sloc 
NoLocation 
Instances
Eq SrcLocation Source # 
Instance details

Defined in Language.Python.Common.SrcLocation

Data SrcLocation Source # 
Instance details

Defined in Language.Python.Common.SrcLocation

Methods

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

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

toConstr :: SrcLocation -> Constr #

dataTypeOf :: SrcLocation -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord SrcLocation Source # 
Instance details

Defined in Language.Python.Common.SrcLocation

Show SrcLocation Source # 
Instance details

Defined in Language.Python.Common.SrcLocation

Pretty SrcLocation Source # 
Instance details

Defined in Language.Python.Common.SrcLocation

Span SrcLocation Source # 
Instance details

Defined in Language.Python.Common.SrcLocation

data SrcSpan Source #

Source location spanning a contiguous section of a file.

Constructors

SpanCoLinear

A span which starts and ends on the same line.

SpanMultiLine

A span which starts and ends on different lines.

SpanPoint

A span which is actually just one point in the file.

SpanEmpty

No span information.

Instances
Eq SrcSpan Source # 
Instance details

Defined in Language.Python.Common.SrcLocation

Methods

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

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

Data SrcSpan Source # 
Instance details

Defined in Language.Python.Common.SrcLocation

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 # 
Instance details

Defined in Language.Python.Common.SrcLocation

Show SrcSpan Source # 
Instance details

Defined in Language.Python.Common.SrcLocation

Pretty SrcSpan Source # 
Instance details

Defined in Language.Python.Common.SrcLocation

Methods

pretty :: SrcSpan -> Doc Source #

Span SrcSpan Source # 
Instance details

Defined in Language.Python.Common.SrcLocation

Span AssignOpSpan Source # 
Instance details

Defined in Language.Python.Common.AST

Span OpSpan Source # 
Instance details

Defined in Language.Python.Common.AST

Span SliceSpan Source # 
Instance details

Defined in Language.Python.Common.AST

Span DictKeyDatumListSpan Source # 
Instance details

Defined in Language.Python.Common.AST

Span YieldArgSpan Source # 
Instance details

Defined in Language.Python.Common.AST

Span ExprSpan Source # 
Instance details

Defined in Language.Python.Common.AST

Span CompIterSpan Source # 
Instance details

Defined in Language.Python.Common.AST

Span CompIfSpan Source # 
Instance details

Defined in Language.Python.Common.AST

Span CompForSpan Source # 
Instance details

Defined in Language.Python.Common.AST

Span ComprehensionExprSpan Source # 
Instance details

Defined in Language.Python.Common.AST

Span ComprehensionSpan Source # 
Instance details

Defined in Language.Python.Common.AST

Span ExceptClauseSpan Source # 
Instance details

Defined in Language.Python.Common.AST

Span HandlerSpan Source # 
Instance details

Defined in Language.Python.Common.AST

Span ArgumentSpan Source # 
Instance details

Defined in Language.Python.Common.AST

Span ParamTupleSpan Source # 
Instance details

Defined in Language.Python.Common.AST

Span ParameterSpan Source # 
Instance details

Defined in Language.Python.Common.AST

Span DecoratorSpan Source # 
Instance details

Defined in Language.Python.Common.AST

Span StatementSpan Source # 
Instance details

Defined in Language.Python.Common.AST

Span ImportRelativeSpan Source # 
Instance details

Defined in Language.Python.Common.AST

Span FromItemsSpan Source # 
Instance details

Defined in Language.Python.Common.AST

Span FromItemSpan Source # 
Instance details

Defined in Language.Python.Common.AST

Span ImportItemSpan Source # 
Instance details

Defined in Language.Python.Common.AST

Span IdentSpan Source # 
Instance details

Defined in Language.Python.Common.AST

class Span a where Source #

Types which have a span.

Minimal complete definition

Nothing

Methods

getSpan :: a -> SrcSpan Source #

Instances
Span SrcSpan Source # 
Instance details

Defined in Language.Python.Common.SrcLocation

Span SrcLocation Source # 
Instance details

Defined in Language.Python.Common.SrcLocation

Span AssignOpSpan Source # 
Instance details

Defined in Language.Python.Common.AST

Span OpSpan Source # 
Instance details

Defined in Language.Python.Common.AST

Span SliceSpan Source # 
Instance details

Defined in Language.Python.Common.AST

Span DictKeyDatumListSpan Source # 
Instance details

Defined in Language.Python.Common.AST

Span YieldArgSpan Source # 
Instance details

Defined in Language.Python.Common.AST

Span ExprSpan Source # 
Instance details

Defined in Language.Python.Common.AST

Span CompIterSpan Source # 
Instance details

Defined in Language.Python.Common.AST

Span CompIfSpan Source # 
Instance details

Defined in Language.Python.Common.AST

Span CompForSpan Source # 
Instance details

Defined in Language.Python.Common.AST

Span ComprehensionExprSpan Source # 
Instance details

Defined in Language.Python.Common.AST

Span ComprehensionSpan Source # 
Instance details

Defined in Language.Python.Common.AST

Span ExceptClauseSpan Source # 
Instance details

Defined in Language.Python.Common.AST

Span HandlerSpan Source # 
Instance details

Defined in Language.Python.Common.AST

Span ArgumentSpan Source # 
Instance details

Defined in Language.Python.Common.AST

Span ParamTupleSpan Source # 
Instance details

Defined in Language.Python.Common.AST

Span ParameterSpan Source # 
Instance details

Defined in Language.Python.Common.AST

Span DecoratorSpan Source # 
Instance details

Defined in Language.Python.Common.AST

Span StatementSpan Source # 
Instance details

Defined in Language.Python.Common.AST

Span ImportRelativeSpan Source # 
Instance details

Defined in Language.Python.Common.AST

Span FromItemsSpan Source # 
Instance details

Defined in Language.Python.Common.AST

Span FromItemSpan Source # 
Instance details

Defined in Language.Python.Common.AST

Span ImportItemSpan Source # 
Instance details

Defined in Language.Python.Common.AST

Span IdentSpan Source # 
Instance details

Defined in Language.Python.Common.AST

Span Token Source # 
Instance details

Defined in Language.Python.Common.Token

Span a => Span [a] Source # 
Instance details

Defined in Language.Python.Common.SrcLocation

Methods

getSpan :: [a] -> SrcSpan Source #

Span a => Span (Maybe a) Source # 
Instance details

Defined in Language.Python.Common.SrcLocation

Methods

getSpan :: Maybe a -> SrcSpan Source #

(Span a, Span b) => Span (Either a b) Source # 
Instance details

Defined in Language.Python.Common.SrcLocation

Methods

getSpan :: Either a b -> SrcSpan Source #

(Span a, Span b) => Span (a, b) Source # 
Instance details

Defined in Language.Python.Common.SrcLocation

Methods

getSpan :: (a, b) -> SrcSpan Source #

spanning :: (Span a, Span b) => a -> b -> SrcSpan Source #

Create a new span which encloses two spanned things.

mkSrcSpan :: SrcLocation -> SrcLocation -> SrcSpan Source #

Make a span from two locations. Assumption: either the arguments are the same, or the left one preceeds the right one.

combineSrcSpans :: SrcSpan -> SrcSpan -> SrcSpan Source #

Combines two SrcSpan into one that spans at least all the characters within both spans. Assumes the "file" part is the same in both inputs

initialSrcLocation :: String -> SrcLocation Source #

Construct the initial source location for a file.

spanStartPoint :: SrcSpan -> SrcSpan Source #

Make a point span from the start of a span

Modification

incColumn :: Int -> SrcLocation -> SrcLocation Source #

Increment the column of a location.

decColumn :: Int -> SrcLocation -> SrcLocation Source #

Decrement the column of a location, only if they are on the same row.

incLine :: Int -> SrcLocation -> SrcLocation Source #

Increment the line number (row) of a location by one.

incTab :: SrcLocation -> SrcLocation Source #

Increment the column of a location by one tab stop.

endCol :: SrcSpan -> Int Source #

Get the column of the end of a span.

Projection of components of a span

endRow :: SrcSpan -> Int Source #

Get the row of the end of a span.

startCol :: SrcSpan -> Int Source #

Get the column of the start of a span.

startRow :: SrcSpan -> Int Source #

Get the row of the start of a span.