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

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

Language.C.Data.Ident

Description

This module provides the notion of identifiers in C, speed up using hashing. Identifiers are associated optionally associated with a NodeInfo, i.e. with a unique Name and a source location (Position). The ordering relation on identifiers is based on the hash and does not follow the lexical order.

Synopsis

Documentation

data Ident Source #

C identifiers

Constructors

Ident String !Int NodeInfo 

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 #

Generic Ident Source # 

Associated Types

type Rep Ident :: * -> * #

Methods

from :: Ident -> Rep Ident x #

to :: Rep Ident x -> Ident #

NFData Ident Source # 

Methods

rnf :: Ident -> () #

Pos Ident Source # 

Methods

posOf :: Ident -> Position Source #

CNode Ident Source # 
type Rep Ident Source # 

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 # 
Generic SUERef Source # 

Associated Types

type Rep SUERef :: * -> * #

Methods

from :: SUERef -> Rep SUERef x #

to :: Rep SUERef x -> SUERef #

NFData SUERef Source # 

Methods

rnf :: SUERef -> () #

type Rep SUERef Source # 
type Rep SUERef = D1 * (MetaData "SUERef" "Language.C.Data.Ident" "language-c-0.8.1-63uQcSi2uwlB9tO1wYroDu" False) ((:+:) * (C1 * (MetaCons "AnonymousRef" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Name))) (C1 * (MetaCons "NamedRef" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Ident))))

isAnonymousRef :: SUERef -> Bool Source #

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

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.

builtinIdent :: String -> Ident Source #

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

internalIdent :: String -> Ident Source #

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

internalIdentAt :: Position -> String -> Ident Source #

return an internal identifier with position info

isInternalIdent :: Ident -> Bool Source #

return True if the given identifier is internal

identToString :: Ident -> String Source #

string of an identifier

sueRefToString :: SUERef -> String Source #

string of a SUE ref (empty if anonymous)

dumpIdent :: Ident -> String Source #

dump the identifier string and its positions for debugging purposes