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

Copyright(c) 2008 Benedikt Huber
LicenseBSD-style
Maintainerbenedikt.huber@gmail.com
Stabilityexperimental
Portabilityghc
Safe HaskellNone
LanguageHaskell98

Language.C.Data

Contents

Description

Common data types for Language.C: Identifiers, unique names, source code locations, ast node attributes and extensible errors.

Synopsis

Input stream

Identifiers

data SUERef Source #

References uniquely determining a struct, union or enum type. Those are either identified by an string identifier, or by a unique name (anonymous types).

Instances

Eq SUERef Source # 

Methods

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

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

Data SUERef Source # 

Methods

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

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

toConstr :: SUERef -> Constr #

dataTypeOf :: SUERef -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord SUERef Source # 
Show SUERef Source # 

isAnonymousRef :: SUERef -> Bool Source #

Return true if the struct/union/enum reference is anonymous.

sueRefToString :: SUERef -> String Source #

string of a SUE ref (empty if anonymous)

data Ident Source #

C identifiers

Instances

Eq Ident Source # 

Methods

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

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

Data Ident Source # 

Methods

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

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

toConstr :: Ident -> Constr #

dataTypeOf :: Ident -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord Ident Source # 

Methods

compare :: Ident -> Ident -> Ordering #

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

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

(>) :: Ident -> Ident -> Bool #

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

max :: Ident -> Ident -> Ident #

min :: Ident -> Ident -> Ident #

Show Ident Source # 

Methods

showsPrec :: Int -> Ident -> ShowS #

show :: Ident -> String #

showList :: [Ident] -> ShowS #

Pos Ident Source # 

Methods

posOf :: Ident -> Position Source #

CNode Ident Source # 

mkIdent :: Position -> String -> Name -> Ident Source #

build an identifier from a string.

  • only minimal error checking, e.g., the characters of the identifier are not checked for being alphanumerical only; the correct lexis of the identifier should be ensured by the caller, e.g., the scanner.
  • for reasons of simplicity the complete lexeme is hashed.

identToString :: Ident -> String Source #

string of an identifier

internalIdent :: String -> Ident Source #

returns an internal identifier (has internal position and no unique name)

isInternalIdent :: Ident -> Bool Source #

return True if the given identifier is internal

builtinIdent :: String -> Ident Source #

returns a builtin identifier (has builtin position and no unique name)

Unqiue names

newtype Name Source #

Name is a unique identifier

Constructors

Name 

Fields

Instances

Enum Name Source # 

Methods

succ :: Name -> Name #

pred :: Name -> Name #

toEnum :: Int -> Name #

fromEnum :: Name -> Int #

enumFrom :: Name -> [Name] #

enumFromThen :: Name -> Name -> [Name] #

enumFromTo :: Name -> Name -> [Name] #

enumFromThenTo :: Name -> Name -> Name -> [Name] #

Eq Name Source # 

Methods

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

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

Data Name Source # 

Methods

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

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

toConstr :: Name -> Constr #

dataTypeOf :: Name -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord Name Source # 

Methods

compare :: Name -> Name -> Ordering #

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

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

(>) :: Name -> Name -> Bool #

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

max :: Name -> Name -> Name #

min :: Name -> Name -> Name #

Read Name Source # 
Show Name Source # 

Methods

showsPrec :: Int -> Name -> ShowS #

show :: Name -> String #

showList :: [Name] -> ShowS #

Ix Name Source # 

Methods

range :: (Name, Name) -> [Name] #

index :: (Name, Name) -> Name -> Int #

unsafeIndex :: (Name, Name) -> Name -> Int

inRange :: (Name, Name) -> Name -> Bool #

rangeSize :: (Name, Name) -> Int #

unsafeRangeSize :: (Name, Name) -> Int

newNameSupply :: [Name] Source #

return an infinite stream of Names starting with nameId 0

Source code positions

data Position Source #

uniform representation of source file positions

Instances

Eq Position Source # 
Data Position Source # 

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 # 
Show Position Source # 

class Pos a where Source #

class of type which aggregate a source code location

Minimal complete definition

posOf

Methods

posOf :: a -> Position Source #

Instances

Pos NodeInfo Source # 
Pos Ident Source # 

Methods

posOf :: Ident -> Position Source #

Pos Attr Source # 

Methods

posOf :: Attr -> Position Source #

Pos Enumerator Source # 
Pos EnumType Source # 
Pos CompType Source # 
Pos EnumTypeRef Source # 
Pos CompTypeRef Source # 
Pos TypeDefRef Source # 
Pos TypeDef Source # 
Pos MemberDecl Source # 
Pos ParamDecl Source # 
Pos FunDef Source # 
Pos ObjDef Source # 
Pos Decl Source # 

Methods

posOf :: Decl -> Position Source #

Pos DeclEvent Source # 
Pos IdentDecl Source # 
Pos TagDef Source # 
CNode t1 => Pos (CStringLiteral t1) Source # 
CNode t1 => Pos (CConstant t1) Source # 

Methods

posOf :: CConstant t1 -> Position Source #

CNode t1 => Pos (CBuiltinThing t1) Source # 
CNode t1 => Pos (CExpression t1) Source # 
CNode t1 => Pos (CAttribute t1) Source # 

Methods

posOf :: CAttribute t1 -> Position Source #

CNode t1 => Pos (CPartDesignator t1) Source # 
CNode t1 => Pos (CInitializer t1) Source # 
CNode t1 => Pos (CEnumeration t1) Source # 
CNode t1 => Pos (CStructureUnion t1) Source # 
CNode t1 => Pos (CAlignmentSpecifier t1) Source # 
CNode t1 => Pos (CFunctionSpecifier t1) Source # 
CNode t1 => Pos (CTypeQualifier t1) Source # 
CNode t1 => Pos (CTypeSpecifier t1) Source # 
CNode t1 => Pos (CStorageSpecifier t1) Source # 
CNode t1 => Pos (CDeclarationSpecifier t1) Source # 
CNode t1 => Pos (CCompoundBlockItem t1) Source # 
CNode t1 => Pos (CAssemblyOperand t1) Source # 
CNode t1 => Pos (CAssemblyStatement t1) Source # 
CNode t1 => Pos (CStatement t1) Source # 

Methods

posOf :: CStatement t1 -> Position Source #

CNode t1 => Pos (CDerivedDeclarator t1) Source # 
CNode t1 => Pos (CDeclarator t1) Source # 
CNode t1 => Pos (CDeclaration t1) Source # 
CNode t1 => Pos (CFunctionDef t1) Source # 
CNode t1 => Pos (CExternalDeclaration t1) Source # 
CNode t1 => Pos (CTranslationUnit t1) Source # 

initPos :: FilePath -> Position Source #

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

nopos :: Position Source #

no position (for unknown position information)

builtinPos :: Position Source #

position attached to built-in objects

internalPos :: Position Source #

position used for internal errors

isSourcePos :: Position -> Bool Source #

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

isBuiltinPos :: Position -> Bool Source #

returns True if the given position refers to a builtin definition

isInternalPos :: Position -> Bool Source #

returns True if the given position is internal

Syntax tree nodes

data NodeInfo Source #

Parsed entity attribute

Instances

Eq NodeInfo Source # 
Data NodeInfo Source # 

Methods

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

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

toConstr :: NodeInfo -> Constr #

dataTypeOf :: NodeInfo -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord NodeInfo Source # 
Show NodeInfo Source # 
Pos NodeInfo Source # 
CNode NodeInfo Source # 
Pretty CStrLit Source # 
Pretty CConst Source # 
Pretty CBuiltin Source # 
Pretty CExpr Source # 
Pretty CAttr Source # 
Pretty CDesignator Source # 
Pretty CInit Source # 
Pretty CEnum Source # 
Pretty CStructUnion Source # 
Pretty CAlignSpec Source # 
Pretty CFunSpec Source # 
Pretty CTypeQual Source # 
Pretty CTypeSpec Source # 
Pretty CStorageSpec Source # 
Pretty CDeclSpec Source # 
Pretty CBlockItem Source # 
Pretty CAsmOperand Source # 
Pretty CAsmStmt Source # 
Pretty CStat Source # 
Pretty CArrSize Source # 
Pretty CDeclr Source # 
Pretty CDecl Source # 
Pretty CFunDef Source # 
Pretty CExtDecl Source # 
Pretty CTranslUnit Source # 

class CNode a where Source #

a class for convenient access to the attributes of an attributed object

Minimal complete definition

nodeInfo

Methods

nodeInfo :: a -> NodeInfo Source #

Instances

CNode NodeInfo Source # 
CNode Ident Source # 
CNode Attr Source # 
CNode Enumerator Source # 
CNode EnumType Source # 
CNode CompType Source # 
CNode EnumTypeRef Source # 
CNode CompTypeRef Source # 
CNode TypeDefRef Source # 
CNode TypeDef Source # 
CNode MemberDecl Source # 
CNode ParamDecl Source # 
CNode FunDef Source # 
CNode ObjDef Source # 
CNode Decl Source # 
CNode DeclEvent Source # 
CNode IdentDecl Source # 
CNode TagDef Source # 
CNode TagFwdDecl Source # 
CNode t1 => CNode (CStringLiteral t1) Source # 
CNode t1 => CNode (CConstant t1) Source # 
CNode t1 => CNode (CBuiltinThing t1) Source # 
CNode t1 => CNode (CExpression t1) Source # 
CNode t1 => CNode (CAttribute t1) Source # 
CNode t1 => CNode (CPartDesignator t1) Source # 
CNode t1 => CNode (CInitializer t1) Source # 
CNode t1 => CNode (CEnumeration t1) Source # 
CNode t1 => CNode (CStructureUnion t1) Source # 
CNode t1 => CNode (CAlignmentSpecifier t1) Source # 
CNode t1 => CNode (CFunctionSpecifier t1) Source # 
CNode t1 => CNode (CTypeQualifier t1) Source # 
CNode t1 => CNode (CTypeSpecifier t1) Source # 
CNode t1 => CNode (CStorageSpecifier t1) Source # 
CNode t1 => CNode (CDeclarationSpecifier t1) Source # 
CNode t1 => CNode (CCompoundBlockItem t1) Source # 
CNode t1 => CNode (CAssemblyOperand t1) Source # 
CNode t1 => CNode (CAssemblyStatement t1) Source # 
CNode t1 => CNode (CStatement t1) Source # 
CNode t1 => CNode (CDerivedDeclarator t1) Source # 
CNode t1 => CNode (CDeclarator t1) Source # 
CNode t1 => CNode (CDeclaration t1) Source # 
CNode t1 => CNode (CFunctionDef t1) Source # 
CNode t1 => CNode (CExternalDeclaration t1) Source # 
CNode t1 => CNode (CTranslationUnit t1) Source # 
(CNode a, CNode b) => CNode (Either a b) Source # 

Methods

nodeInfo :: Either a b -> NodeInfo Source #

undefNode :: NodeInfo Source #

create a node with neither name nor positional information

mkNodeInfoOnlyPos :: Position -> NodeInfo Source #

| Given only a source position, create a new node attribute

mkNodeInfo :: Position -> Name -> NodeInfo Source #

Given a source position and a unique name, create a new attribute identifier

internalNode :: NodeInfo Source #

Deprecated: use undefNode instead

Extensible errors