language-objc-0.4.2.0: Analysis and generation of Objcective C code

Portabilityghc
Stabilityexperimental
Maintainerjwlato@gmail.com
Safe HaskellNone

Language.ObjC.Data

Contents

Description

Common data types for Language.ObjC: 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).

isAnonymousRef :: SUERef -> BoolSource

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

mkIdent :: Position -> String -> Name -> IdentSource

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 -> StringSource

string of an identifier

internalIdent :: String -> IdentSource

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

isInternalIdent :: Ident -> BoolSource

return True if the given identifier is internal

builtinIdent :: String -> IdentSource

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

Unqiue names

newtype Name Source

Name is a unique identifier

Constructors

Name 

Fields

nameId :: 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

Constructors

Position 

Fields

posOffset' :: !Int

absolute offset in the preprocessed file

posFile' :: String

source file

posRow' :: !Int

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

posColumn' :: !Int

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

NoPosition 
BuiltinPosition 
InternalPosition 

class Pos a whereSource

class of type which aggregate a source code location

Methods

posOf :: a -> PositionSource

Instances

Pos NodeInfo 
Pos Ident 
Pos CToken 
Pos CDeclrR 
Pos Attr 
Pos Enumerator 
Pos EnumType 
Pos CompType 
Pos EnumTypeRef 
Pos CompTypeRef 
Pos TypeDefRef 
Pos TypeDef 
Pos MemberDecl 
Pos ParamDecl 
Pos FunDef 
Pos ObjDef 
Pos Decl 
Pos DeclEvent 
Pos IdentDecl 
Pos TagDef 
Pos a => Pos [a] 
Pos a => Pos (Reversed a) 
CNode t1 => Pos (CStringLiteral t1) 
CNode t1 => Pos (CConstant t1) 
CNode t1 => Pos (ObjCConstant t1) 
CNode t1 => Pos (CBuiltinThing t1) 
CNode t1 => Pos (ObjCKeywordArg t1) 
CNode t1 => Pos (ObjCMessageSelector t1) 
CNode t1 => Pos (ObjCMessageExpression t1) 
CNode t1 => Pos (ObjCSelector t1) 
CNode t1 => Pos (ObjCSelectorKeyName t1) 
CNode t1 => Pos (ObjCSelectorName t1) 
CNode t1 => Pos (CExpression t1) 
CNode t1 => Pos (CAttribute t1) 
CNode t1 => Pos (CPartDesignator t1) 
CNode t1 => Pos (CInitializer t1) 
CNode t1 => Pos (CEnumeration t1) 
CNode t1 => Pos (CStructureUnion t1) 
CNode t1 => Pos (ObjCProtoQualifier t1) 
CNode t1 => Pos (CTypeQualifier t1) 
CNode t1 => Pos (CTypeSpecifier t1) 
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) 
CNode t1 => Pos (CDerivedDeclarator t1) 
CNode t1 => Pos (CDeclarator t1) 
CNode t1 => Pos (CDeclaration t1) 
CNode t1 => Pos (ObjCPropertyModifier t1) 
CNode t1 => Pos (ObjCPropertyDeclaration t1) 
CNode t1 => Pos (ObjCKeywordDeclarator t1) 
CNode t1 => Pos (ObjCMethodSelector t1) 
CNode t1 => Pos (ObjCMethodDefinition t1) 
CNode t1 => Pos (ObjCMethodDeclaration t1) 
CNode t1 => Pos (ObjCImplementationDefinition t1) 
CNode t1 => Pos (ObjCInterfaceDeclaration t1) 
CNode t1 => Pos (ObjCVisibilitySpec t1) 
CNode t1 => Pos (ObjCInstanceVariableBlock t1) 
CNode t1 => Pos (ObjCProtocolName t1) 
CNode t1 => Pos (ObjCClassName t1) 
CNode t1 => Pos (ObjCClassDeclarator t1) 
CNode t1 => Pos (ObjCImplementation t1) 
CNode t1 => Pos (ObjCInterface t1) 
CNode t1 => Pos (ObjCProtocolDeclBlock t1) 
CNode t1 => Pos (ObjCProtocolDec t1) 
CNode t1 => Pos (ObjCClassListDef t1) 
CNode t1 => Pos (ObjCCategoryImplementation t1) 
CNode t1 => Pos (ObjCCategoryDec t1) 
CNode t1 => Pos (CFunctionDef t1) 
CNode t1 => Pos (CExternalDeclaration t1) 
CNode t1 => Pos (CTranslationUnit t1) 
Pos (Located a) 

initPos :: FilePath -> PositionSource

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

nopos :: PositionSource

no position (for unknown position information)

builtinPos :: PositionSource

position attached to built-in objects

internalPos :: PositionSource

position used for internal errors

isSourcePos :: Position -> BoolSource

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

isBuiltinPos :: Position -> BoolSource

returns True if the given position refers to a builtin definition

isInternalPos :: Position -> BoolSource

returns True if the given position is internal

Syntax tree nodes

class CNode a whereSource

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

Methods

nodeInfo :: a -> NodeInfoSource

Instances

CNode NodeInfo 
CNode Ident 
CNode CDeclrR 
CNode Attr 
CNode Enumerator 
CNode EnumType 
CNode CompType 
CNode EnumTypeRef 
CNode CompTypeRef 
CNode TypeDefRef 
CNode TypeDef 
CNode MemberDecl 
CNode ParamDecl 
CNode FunDef 
CNode ObjDef 
CNode Decl 
CNode DeclEvent 
CNode IdentDecl 
CNode TagDef 
CNode TagFwdDecl 
CNode t1 => CNode (CStringLiteral t1) 
CNode t1 => CNode (CConstant t1) 
CNode t1 => CNode (ObjCConstant t1) 
CNode t1 => CNode (CBuiltinThing t1) 
CNode t1 => CNode (ObjCKeywordArg t1) 
CNode t1 => CNode (ObjCMessageSelector t1) 
CNode t1 => CNode (ObjCMessageExpression t1) 
CNode t1 => CNode (ObjCSelector t1) 
CNode t1 => CNode (ObjCSelectorKeyName t1) 
CNode t1 => CNode (ObjCSelectorName t1) 
CNode t1 => CNode (CExpression t1) 
CNode t1 => CNode (CAttribute t1) 
CNode t1 => CNode (CPartDesignator t1) 
CNode t1 => CNode (CInitializer t1) 
CNode t1 => CNode (CEnumeration t1) 
CNode t1 => CNode (CStructureUnion t1) 
CNode t1 => CNode (ObjCProtoQualifier 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) 
CNode t1 => CNode (CDerivedDeclarator t1) 
CNode t1 => CNode (CDeclarator t1) 
CNode t1 => CNode (CDeclaration t1) 
CNode t1 => CNode (ObjCPropertyModifier t1) 
CNode t1 => CNode (ObjCPropertyDeclaration t1) 
CNode t1 => CNode (ObjCKeywordDeclarator t1) 
CNode t1 => CNode (ObjCMethodSelector t1) 
CNode t1 => CNode (ObjCMethodDefinition t1) 
CNode t1 => CNode (ObjCMethodDeclaration t1) 
CNode t1 => CNode (ObjCImplementationDefinition t1) 
CNode t1 => CNode (ObjCInterfaceDeclaration t1) 
CNode t1 => CNode (ObjCVisibilitySpec t1) 
CNode t1 => CNode (ObjCInstanceVariableBlock t1) 
CNode t1 => CNode (ObjCProtocolName t1) 
CNode t1 => CNode (ObjCClassName t1) 
CNode t1 => CNode (ObjCClassDeclarator t1) 
CNode t1 => CNode (ObjCImplementation t1) 
CNode t1 => CNode (ObjCInterface t1) 
CNode t1 => CNode (ObjCProtocolDeclBlock t1) 
CNode t1 => CNode (ObjCProtocolDec t1) 
CNode t1 => CNode (ObjCClassListDef t1) 
CNode t1 => CNode (ObjCCategoryImplementation t1) 
CNode t1 => CNode (ObjCCategoryDec t1) 
CNode t1 => CNode (CFunctionDef t1) 
CNode t1 => CNode (CExternalDeclaration t1) 
CNode t1 => CNode (CTranslationUnit t1) 
(CNode a, CNode b) => CNode (Either a b) 

undefNode :: NodeInfoSource

create a node with neither name nor positional information

mkNodeInfoOnlyPos :: Position -> NodeInfoSource

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

mkNodeInfo :: Position -> Name -> NodeInfoSource

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

Extensible errors