Copyright | (c) 2008 Benedikt Huber |
---|---|
License | BSD-style |
Maintainer | benedikt.huber@gmail.com |
Stability | experimental |
Portability | ghc |
Safe Haskell | Safe-Inferred |
Language | Haskell2010 |
Common data types for Language.C: Identifiers, unique names, source code locations, ast node attributes and extensible errors.
Synopsis
- module Language.C.Data.InputStream
- data SUERef
- isAnonymousRef :: SUERef -> Bool
- sueRefToString :: SUERef -> String
- data Ident
- mkIdent :: Position -> String -> Name -> Ident
- identToString :: Ident -> String
- internalIdent :: String -> Ident
- isInternalIdent :: Ident -> Bool
- builtinIdent :: String -> Ident
- newtype Name = Name {}
- newNameSupply :: [Name]
- data Position
- posFile :: Position -> String
- posParent :: Position -> Maybe Position
- class Pos a where
- initPos :: FilePath -> Position
- nopos :: Position
- builtinPos :: Position
- internalPos :: Position
- isSourcePos :: Position -> Bool
- isBuiltinPos :: Position -> Bool
- isInternalPos :: Position -> Bool
- data NodeInfo
- class CNode a where
- fileOfNode :: CNode a => a -> Maybe FilePath
- posOfNode :: NodeInfo -> Position
- nameOfNode :: NodeInfo -> Maybe Name
- undefNode :: NodeInfo
- mkNodeInfoOnlyPos :: Position -> NodeInfo
- mkNodeInfo :: Position -> Name -> NodeInfo
- internalNode :: NodeInfo
- module Language.C.Data.Error
Input stream
module Language.C.Data.InputStream
Identifiers
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
Data SUERef Source # | |
Defined in Language.C.Data.Ident 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 :: forall r r'. (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 # | |
Generic SUERef Source # | |
Show SUERef Source # | |
NFData SUERef Source # | |
Defined in Language.C.Data.Ident | |
Eq SUERef Source # | |
Ord SUERef Source # | |
Pretty SUERef Source # | |
type Rep SUERef Source # | |
Defined in Language.C.Data.Ident type Rep SUERef = D1 ('MetaData "SUERef" "Language.C.Data.Ident" "language-c-0.9.4-9yWFXod72jo4EfM9VWrwhH" 'False) (C1 ('MetaCons "AnonymousRef" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Name)) :+: C1 ('MetaCons "NamedRef" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Ident))) |
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)
C identifiers
Instances
Data Ident Source # | |
Defined in Language.C.Data.Ident 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 # 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 :: forall r r'. (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 # | |
Generic Ident Source # | |
Show Ident Source # | |
NFData Ident Source # | |
Defined in Language.C.Data.Ident | |
Eq Ident Source # | |
Ord Ident Source # | |
CNode Ident Source # | |
Pos Ident Source # | |
Pretty Ident Source # | |
type Rep Ident Source # | |
Defined in Language.C.Data.Ident type Rep Ident = D1 ('MetaData "Ident" "Language.C.Data.Ident" "language-c-0.9.4-9yWFXod72jo4EfM9VWrwhH" 'False) (C1 ('MetaCons "Ident" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'SourceUnpack 'SourceStrict 'DecidedStrict) (Rec0 Int) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 NodeInfo)))) |
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
Name is a unique identifier
Instances
Data Name Source # | |
Defined in Language.C.Data.Name 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 # 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 :: forall r r'. (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 # | |
Enum Name Source # | |
Generic Name Source # | |
Ix Name Source # | |
Read Name Source # | |
Show Name Source # | |
NFData Name Source # | |
Defined in Language.C.Data.Name | |
Eq Name Source # | |
Ord Name Source # | |
type Rep Name Source # | |
Defined in Language.C.Data.Name |
newNameSupply :: [Name] Source #
return an infinite stream of Name
s starting with nameId
0
Source code positions
uniform representation of source file positions
Instances
Data Position Source # | |
Defined in Language.C.Data.Position 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 :: forall r r'. (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 # | |
Generic Position Source # | |
Show Position Source # | |
NFData Position Source # | |
Defined in Language.C.Data.Position | |
Eq Position Source # | |
Ord Position Source # | |
Defined in Language.C.Data.Position | |
type Rep Position Source # | |
Defined in Language.C.Data.Position |
class of type which aggregate a source code location
Instances
initPos :: FilePath -> Position Source #
initialize a Position to the start of the translation unit starting in the given file
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
Parsed entity attribute
Instances
a class for convenient access to the attributes of an attributed object
Instances
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
module Language.C.Data.Error