language-c-0.6.1: 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 #

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 # 

Methods

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

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

Data SUERef # 

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 # 
Show SUERef # 

isAnonymousRef :: SUERef -> Bool #

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

sueRefToString :: SUERef -> String #

string of a SUE ref (empty if anonymous)

data Ident #

C identifiers

Instances

Eq Ident # 

Methods

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

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

Data Ident # 

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 # 

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 # 

Methods

showsPrec :: Int -> Ident -> ShowS #

show :: Ident -> String #

showList :: [Ident] -> ShowS #

Pos Ident # 

Methods

posOf :: Ident -> Position #

CNode Ident # 

Methods

nodeInfo :: Ident -> NodeInfo #

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

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 #

string of an identifier

internalIdent :: String -> Ident #

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

isInternalIdent :: Ident -> Bool #

return True if the given identifier is internal

builtinIdent :: String -> Ident #

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

Unqiue names

newtype Name #

Name is a unique identifier

Constructors

Name 

Fields

Instances

Enum Name # 

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 # 

Methods

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

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

Data Name # 

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 # 

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 # 
Show Name # 

Methods

showsPrec :: Int -> Name -> ShowS #

show :: Name -> String #

showList :: [Name] -> ShowS #

Ix Name # 

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] #

return an infinite stream of Names starting with nameId 0

Source code positions

data Position #

uniform representation of source file positions

Instances

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

class Pos a where #

class of type which aggregate a source code location

Minimal complete definition

posOf

Methods

posOf :: a -> Position #

Instances

Pos NodeInfo # 

Methods

posOf :: NodeInfo -> Position #

Pos Ident # 

Methods

posOf :: Ident -> Position #

Pos Attr # 

Methods

posOf :: Attr -> Position #

Pos Enumerator # 

Methods

posOf :: Enumerator -> Position #

Pos EnumType # 

Methods

posOf :: EnumType -> Position #

Pos CompType # 

Methods

posOf :: CompType -> Position #

Pos EnumTypeRef # 
Pos CompTypeRef # 
Pos TypeDefRef # 

Methods

posOf :: TypeDefRef -> Position #

Pos TypeDef # 

Methods

posOf :: TypeDef -> Position #

Pos MemberDecl # 

Methods

posOf :: MemberDecl -> Position #

Pos ParamDecl # 

Methods

posOf :: ParamDecl -> Position #

Pos FunDef # 

Methods

posOf :: FunDef -> Position #

Pos ObjDef # 

Methods

posOf :: ObjDef -> Position #

Pos Decl # 

Methods

posOf :: Decl -> Position #

Pos DeclEvent # 

Methods

posOf :: DeclEvent -> Position #

Pos IdentDecl # 

Methods

posOf :: IdentDecl -> Position #

Pos TagDef # 

Methods

posOf :: TagDef -> Position #

CNode t1 => Pos (CStringLiteral t1) # 

Methods

posOf :: CStringLiteral t1 -> Position #

CNode t1 => Pos (CConstant t1) # 

Methods

posOf :: CConstant t1 -> Position #

CNode t1 => Pos (CBuiltinThing t1) # 

Methods

posOf :: CBuiltinThing t1 -> Position #

CNode t1 => Pos (CExpression t1) # 

Methods

posOf :: CExpression t1 -> Position #

CNode t1 => Pos (CAttribute t1) # 

Methods

posOf :: CAttribute t1 -> Position #

CNode t1 => Pos (CPartDesignator t1) # 
CNode t1 => Pos (CInitializer t1) # 

Methods

posOf :: CInitializer t1 -> Position #

CNode t1 => Pos (CEnumeration t1) # 

Methods

posOf :: CEnumeration t1 -> Position #

CNode t1 => Pos (CStructureUnion t1) # 
CNode t1 => Pos (CAlignmentSpecifier t1) # 
CNode t1 => Pos (CFunctionSpecifier t1) # 
CNode t1 => Pos (CTypeQualifier t1) # 

Methods

posOf :: CTypeQualifier t1 -> Position #

CNode t1 => Pos (CTypeSpecifier t1) # 

Methods

posOf :: CTypeSpecifier t1 -> Position #

CNode t1 => Pos (CStorageSpecifier t1) # 
CNode t1 => Pos (CDeclarationSpecifier t1) # 
CNode t1 => Pos (CCompoundBlockItem t1) # 
CNode t1 => Pos (CAssemblyOperand t1) # 
CNode t1 => Pos (CAssemblyStatement t1) # 
CNode t1 => Pos (CStatement t1) # 

Methods

posOf :: CStatement t1 -> Position #

CNode t1 => Pos (CDerivedDeclarator t1) # 
CNode t1 => Pos (CDeclarator t1) # 

Methods

posOf :: CDeclarator t1 -> Position #

CNode t1 => Pos (CDeclaration t1) # 

Methods

posOf :: CDeclaration t1 -> Position #

CNode t1 => Pos (CFunctionDef t1) # 

Methods

posOf :: CFunctionDef t1 -> Position #

CNode t1 => Pos (CExternalDeclaration t1) # 
CNode t1 => Pos (CTranslationUnit t1) # 

initPos :: FilePath -> Position #

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

nopos :: Position #

no position (for unknown position information)

builtinPos :: Position #

position attached to built-in objects

internalPos :: Position #

position used for internal errors

isSourcePos :: Position -> Bool #

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

isBuiltinPos :: Position -> Bool #

returns True if the given position refers to a builtin definition

isInternalPos :: Position -> Bool #

returns True if the given position is internal

Syntax tree nodes

data NodeInfo #

Parsed entity attribute

Instances

Eq NodeInfo # 
Data NodeInfo # 

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 # 
Show NodeInfo # 
Pos NodeInfo # 

Methods

posOf :: NodeInfo -> Position #

CNode NodeInfo # 
Pretty CStrLit # 

Methods

pretty :: CStrLit -> Doc #

prettyPrec :: Int -> CStrLit -> Doc #

Pretty CConst # 

Methods

pretty :: CConst -> Doc #

prettyPrec :: Int -> CConst -> Doc #

Pretty CBuiltin # 

Methods

pretty :: CBuiltin -> Doc #

prettyPrec :: Int -> CBuiltin -> Doc #

Pretty CExpr # 

Methods

pretty :: CExpr -> Doc #

prettyPrec :: Int -> CExpr -> Doc #

Pretty CAttr # 

Methods

pretty :: CAttr -> Doc #

prettyPrec :: Int -> CAttr -> Doc #

Pretty CDesignator # 
Pretty CInit # 

Methods

pretty :: CInit -> Doc #

prettyPrec :: Int -> CInit -> Doc #

Pretty CEnum # 

Methods

pretty :: CEnum -> Doc #

prettyPrec :: Int -> CEnum -> Doc #

Pretty CStructUnion # 
Pretty CAlignSpec # 
Pretty CFunSpec # 

Methods

pretty :: CFunSpec -> Doc #

prettyPrec :: Int -> CFunSpec -> Doc #

Pretty CTypeQual # 
Pretty CTypeSpec # 
Pretty CStorageSpec # 
Pretty CDeclSpec # 
Pretty CBlockItem # 
Pretty CAsmOperand # 
Pretty CAsmStmt # 

Methods

pretty :: CAsmStmt -> Doc #

prettyPrec :: Int -> CAsmStmt -> Doc #

Pretty CStat # 

Methods

pretty :: CStat -> Doc #

prettyPrec :: Int -> CStat -> Doc #

Pretty CArrSize # 

Methods

pretty :: CArrSize -> Doc #

prettyPrec :: Int -> CArrSize -> Doc #

Pretty CDeclr # 

Methods

pretty :: CDeclr -> Doc #

prettyPrec :: Int -> CDeclr -> Doc #

Pretty CDecl # 

Methods

pretty :: CDecl -> Doc #

prettyPrec :: Int -> CDecl -> Doc #

Pretty CFunDef # 

Methods

pretty :: CFunDef -> Doc #

prettyPrec :: Int -> CFunDef -> Doc #

Pretty CExtDecl # 

Methods

pretty :: CExtDecl -> Doc #

prettyPrec :: Int -> CExtDecl -> Doc #

Pretty CTranslUnit # 

class CNode a where #

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

Minimal complete definition

nodeInfo

Methods

nodeInfo :: a -> NodeInfo #

Instances

CNode NodeInfo # 
CNode Ident # 

Methods

nodeInfo :: Ident -> NodeInfo #

CNode Attr # 

Methods

nodeInfo :: Attr -> NodeInfo #

CNode Enumerator # 
CNode EnumType # 
CNode CompType # 
CNode EnumTypeRef # 
CNode CompTypeRef # 
CNode TypeDefRef # 
CNode TypeDef # 

Methods

nodeInfo :: TypeDef -> NodeInfo #

CNode MemberDecl # 
CNode ParamDecl # 
CNode FunDef # 

Methods

nodeInfo :: FunDef -> NodeInfo #

CNode ObjDef # 

Methods

nodeInfo :: ObjDef -> NodeInfo #

CNode Decl # 

Methods

nodeInfo :: Decl -> NodeInfo #

CNode DeclEvent # 
CNode IdentDecl # 
CNode TagDef # 

Methods

nodeInfo :: TagDef -> NodeInfo #

CNode TagFwdDecl # 
CNode t1 => CNode (CStringLiteral t1) # 
CNode t1 => CNode (CConstant t1) # 

Methods

nodeInfo :: CConstant t1 -> NodeInfo #

CNode t1 => CNode (CBuiltinThing t1) # 
CNode t1 => CNode (CExpression t1) # 

Methods

nodeInfo :: CExpression t1 -> NodeInfo #

CNode t1 => CNode (CAttribute t1) # 

Methods

nodeInfo :: CAttribute t1 -> NodeInfo #

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

Methods

nodeInfo :: CStatement t1 -> NodeInfo #

CNode t1 => CNode (CDerivedDeclarator t1) # 
CNode t1 => CNode (CDeclarator t1) # 

Methods

nodeInfo :: CDeclarator t1 -> NodeInfo #

CNode t1 => CNode (CDeclaration t1) # 
CNode t1 => CNode (CFunctionDef t1) # 
CNode t1 => CNode (CExternalDeclaration t1) # 
CNode t1 => CNode (CTranslationUnit t1) # 
(CNode a, CNode b) => CNode (Either a b) # 

Methods

nodeInfo :: Either a b -> NodeInfo #

undefNode :: NodeInfo #

create a node with neither name nor positional information

mkNodeInfoOnlyPos :: Position -> NodeInfo #

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

mkNodeInfo :: Position -> Name -> NodeInfo #

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

internalNode :: NodeInfo #

Deprecated: use undefNode instead

Extensible errors