language-c-0.8.3: Analysis and generation of C code

Copyright(c) [1995..2000] Manuel M. T. Chakravarty
[2008..2009] Benedikt Huber
LicenseBSD-style
Maintainerbenedikt.huber@gmail.com
Stabilityexperimental
Portabilityghc
Safe HaskellNone
LanguageHaskell98

Language.C.Data.Position

Description

Source code position

Synopsis

Documentation

data Position Source #

uniform representation of source file positions

Instances
Eq Position Source # 
Instance details

Defined in Language.C.Data.Position

Data Position Source # 
Instance details

Defined in Language.C.Data.Position

Methods

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

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

toConstr :: Position -> Constr #

dataTypeOf :: Position -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord Position Source # 
Instance details

Defined in Language.C.Data.Position

Show Position Source # 
Instance details

Defined in Language.C.Data.Position

Generic Position Source # 
Instance details

Defined in Language.C.Data.Position

Associated Types

type Rep Position :: Type -> Type #

Methods

from :: Position -> Rep Position x #

to :: Rep Position x -> Position #

NFData Position Source # 
Instance details

Defined in Language.C.Data.Position

Methods

rnf :: Position -> () #

type Rep Position Source # 
Instance details

Defined in Language.C.Data.Position

position :: Int -> String -> Int -> Int -> Maybe Position -> Position Source #

position absoluteOffset fileName lineNumber columnNumber initializes a Position using the given arguments

type PosLength = (Position, Int) Source #

Position and length of a token

posRow :: Position -> Int Source #

row (line) in the original file. Affected by #LINE pragmas.

posColumn :: Position -> Int Source #

column in the preprocessed file. Inaccurate w.r.t. to the original file in the presence of preprocessor macros.

posOffset :: Position -> Int Source #

absolute offset in the preprocessed file

initPos :: FilePath -> Position Source #

initialize a Position to the start of the translation unit starting in the given file

isSourcePos :: Position -> Bool Source #

returns True if the given position refers to an actual source file

nopos :: Position Source #

no position (for unknown position information)

isNoPos :: Position -> Bool Source #

returns True if the there is no position information available

builtinPos :: Position Source #

position attached to built-in objects

isBuiltinPos :: Position -> Bool Source #

returns True if the given position refers to a builtin definition

internalPos :: Position Source #

position used for internal errors

isInternalPos :: Position -> Bool Source #

returns True if the given position is internal

incPos :: Position -> Int -> Position Source #

advance column

retPos :: Position -> Position Source #

advance to next line

incOffset :: Position -> Int -> Position Source #

advance just the offset

class Pos a where Source #

class of type which aggregate a source code location

Methods

posOf :: a -> Position Source #

Instances
Pos NodeInfo Source # 
Instance details

Defined in Language.C.Data.Node

Pos Ident Source # 
Instance details

Defined in Language.C.Data.Ident

Methods

posOf :: Ident -> Position Source #

Pos Attr Source # 
Instance details

Defined in Language.C.Analysis.SemRep

Methods

posOf :: Attr -> Position Source #

Pos Enumerator Source # 
Instance details

Defined in Language.C.Analysis.SemRep

Pos EnumType Source # 
Instance details

Defined in Language.C.Analysis.SemRep

Pos CompType Source # 
Instance details

Defined in Language.C.Analysis.SemRep

Pos EnumTypeRef Source # 
Instance details

Defined in Language.C.Analysis.SemRep

Pos CompTypeRef Source # 
Instance details

Defined in Language.C.Analysis.SemRep

Pos TypeDefRef Source # 
Instance details

Defined in Language.C.Analysis.SemRep

Pos TypeDef Source # 
Instance details

Defined in Language.C.Analysis.SemRep

Pos MemberDecl Source # 
Instance details

Defined in Language.C.Analysis.SemRep

Pos ParamDecl Source # 
Instance details

Defined in Language.C.Analysis.SemRep

Pos FunDef Source # 
Instance details

Defined in Language.C.Analysis.SemRep

Pos ObjDef Source # 
Instance details

Defined in Language.C.Analysis.SemRep

Pos Decl Source # 
Instance details

Defined in Language.C.Analysis.SemRep

Methods

posOf :: Decl -> Position Source #

Pos DeclEvent Source # 
Instance details

Defined in Language.C.Analysis.SemRep

Pos IdentDecl Source # 
Instance details

Defined in Language.C.Analysis.SemRep

Pos TagDef Source # 
Instance details

Defined in Language.C.Analysis.SemRep

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

Defined in Language.C.Parser.Parser

Methods

posOf :: [a] -> Position Source #

CNode t1 => Pos (CStringLiteral t1) Source # 
Instance details

Defined in Language.C.Syntax.AST

CNode t1 => Pos (CConstant t1) Source # 
Instance details

Defined in Language.C.Syntax.AST

Methods

posOf :: CConstant t1 -> Position Source #

CNode t1 => Pos (CBuiltinThing t1) Source # 
Instance details

Defined in Language.C.Syntax.AST

CNode t1 => Pos (CExpression t1) Source # 
Instance details

Defined in Language.C.Syntax.AST

CNode t1 => Pos (CAttribute t1) Source # 
Instance details

Defined in Language.C.Syntax.AST

Methods

posOf :: CAttribute t1 -> Position Source #

CNode t1 => Pos (CPartDesignator t1) Source # 
Instance details

Defined in Language.C.Syntax.AST

CNode t1 => Pos (CInitializer t1) Source # 
Instance details

Defined in Language.C.Syntax.AST

CNode t1 => Pos (CEnumeration t1) Source # 
Instance details

Defined in Language.C.Syntax.AST

CNode t1 => Pos (CStructureUnion t1) Source # 
Instance details

Defined in Language.C.Syntax.AST

CNode t1 => Pos (CAlignmentSpecifier t1) Source # 
Instance details

Defined in Language.C.Syntax.AST

CNode t1 => Pos (CFunctionSpecifier t1) Source # 
Instance details

Defined in Language.C.Syntax.AST

CNode t1 => Pos (CTypeQualifier t1) Source # 
Instance details

Defined in Language.C.Syntax.AST

CNode t1 => Pos (CTypeSpecifier t1) Source # 
Instance details

Defined in Language.C.Syntax.AST

CNode t1 => Pos (CStorageSpecifier t1) Source # 
Instance details

Defined in Language.C.Syntax.AST

CNode t1 => Pos (CDeclarationSpecifier t1) Source # 
Instance details

Defined in Language.C.Syntax.AST

CNode t1 => Pos (CCompoundBlockItem t1) Source # 
Instance details

Defined in Language.C.Syntax.AST

CNode t1 => Pos (CAssemblyOperand t1) Source # 
Instance details

Defined in Language.C.Syntax.AST

CNode t1 => Pos (CAssemblyStatement t1) Source # 
Instance details

Defined in Language.C.Syntax.AST

CNode t1 => Pos (CStatement t1) Source # 
Instance details

Defined in Language.C.Syntax.AST

Methods

posOf :: CStatement t1 -> Position Source #

CNode t1 => Pos (CDerivedDeclarator t1) Source # 
Instance details

Defined in Language.C.Syntax.AST

CNode t1 => Pos (CDeclarator t1) Source # 
Instance details

Defined in Language.C.Syntax.AST

CNode t1 => Pos (CDeclaration t1) Source # 
Instance details

Defined in Language.C.Syntax.AST

CNode t1 => Pos (CFunctionDef t1) Source # 
Instance details

Defined in Language.C.Syntax.AST

CNode t1 => Pos (CExternalDeclaration t1) Source # 
Instance details

Defined in Language.C.Syntax.AST

CNode t1 => Pos (CTranslationUnit t1) Source # 
Instance details

Defined in Language.C.Syntax.AST