Safe Haskell | None |
---|---|
Language | Haskell2010 |
Types.Internal
Description
A parser for C99 declarations. Currently, the parser has the following limitations:
- Array sizes can only be
*
,n
(where n is a positive integer),x
(wherex
is a C identifier). In C99 they can be arbitrary expressions. See the
data type.ArrayType
_Bool
,_Complex
, and_Imaginary
are not present.- Untyped parameter lists (pre-K&R C) are not allowed.
The parser is incremental and generic (see CParser
). Pretty
and Arbitrary
instances are provided for all the data types.
The entry point if you want to parse C declarations is
.parameter_declaration
Synopsis
- type CParser m = (Monad m, Functor m, Applicative m, MonadPlus m, Parsing m, CharParsing m, TokenParsing m, LookAheadParsing m, MonadReader IsTypeName m)
- type IsTypeName = Identifier -> Bool
- runCParser :: Stream s Identity Char => IsTypeName -> String -> s -> ReaderT IsTypeName (Parsec s ()) a -> Either ParseError a
- quickCParser :: IsTypeName -> String -> ReaderT IsTypeName (Parsec String ()) a -> a
- quickCParser_ :: String -> ReaderT IsTypeName (Parsec String ()) a -> a
- newtype Identifier = Identifier {}
- identifier :: CParser m => m Identifier
- identifier_no_lex :: CParser m => m Identifier
- data DeclarationSpecifier
- declaration_specifiers :: forall m. CParser m => m [DeclarationSpecifier]
- data StorageClassSpecifier
- storage_class_specifier :: CParser m => m StorageClassSpecifier
- data TypeSpecifier
- = VOID
- | CHAR
- | SHORT
- | INT
- | LONG
- | FLOAT
- | DOUBLE
- | SIGNED
- | UNSIGNED
- | Struct Identifier
- | Enum Identifier
- | TypeName Identifier
- type_specifier :: CParser m => m TypeSpecifier
- data TypeQualifier
- type_qualifier :: CParser m => m TypeQualifier
- data FunctionSpecifier = INLINE
- function_specifier :: CParser m => m FunctionSpecifier
- data Declarator = Declarator {}
- declarator :: CParser m => m Declarator
- data DirectDeclarator
- direct_declarator :: CParser m => m DirectDeclarator
- data ArrayOrProto
- array_or_proto :: CParser m => m ArrayOrProto
- data ArrayType
- array_type :: CParser m => m ArrayType
- data Pointer = Pointer [TypeQualifier]
- pointer :: CParser m => m Pointer
- data ParameterDeclaration = ParameterDeclaration {}
- parameter_declaration :: CParser m => m ParameterDeclaration
- parameter_list :: CParser m => m [ParameterDeclaration]
- data AbstractDeclarator = AbstractDeclarator {}
- abstract_declarator :: CParser m => m AbstractDeclarator
- data DirectAbstractDeclarator
- direct_abstract_declarator :: CParser m => m DirectAbstractDeclarator
Parser type
type CParser m = (Monad m, Functor m, Applicative m, MonadPlus m, Parsing m, CharParsing m, TokenParsing m, LookAheadParsing m, MonadReader IsTypeName m) Source #
All the parsing is done using the type classes provided by the
parsers
package. You can use the parsing routines with any of the parsers
that implement the classes, such as parsec
or trifecta
.
The MonadReader
with IsTypeName
is required for parsing C, see
http://en.wikipedia.org/wiki/The_lexer_hack.
type IsTypeName = Identifier -> Bool Source #
Function used to determine whether an Id
is a type name.
Arguments
:: Stream s Identity Char | |
=> IsTypeName | Function determining if an identifier is a type name. |
-> String | Source name. |
-> s | String to parse. |
-> ReaderT IsTypeName (Parsec s ()) a | Parser. Anything with type |
-> Either ParseError a |
Runs a
using CParser
parsec
.
Arguments
:: IsTypeName | Function determining if an identifier is a type name. |
-> String | String to parse. |
-> ReaderT IsTypeName (Parsec String ()) a | Parser. Anything with type |
-> a |
Useful for quick testing. Uses "quickCParser"
as source name, and throws
an error
if parsing fails.
Arguments
:: String | String to parse. |
-> ReaderT IsTypeName (Parsec String ()) a | Parser. Anything with type |
-> a |
Like quickCParser
, but uses
as const
False
IsTypeName
.
Types and parsing
newtype Identifier Source #
Constructors
Identifier | |
Fields |
Instances
Eq Identifier Source # | |
Defined in Types.Internal | |
Ord Identifier Source # | |
Defined in Types.Internal Methods compare :: Identifier -> Identifier -> Ordering # (<) :: Identifier -> Identifier -> Bool # (<=) :: Identifier -> Identifier -> Bool # (>) :: Identifier -> Identifier -> Bool # (>=) :: Identifier -> Identifier -> Bool # max :: Identifier -> Identifier -> Identifier # min :: Identifier -> Identifier -> Identifier # | |
Show Identifier Source # | |
Defined in Types.Internal Methods showsPrec :: Int -> Identifier -> ShowS # show :: Identifier -> String # showList :: [Identifier] -> ShowS # | |
IsString Identifier Source # | |
Defined in Types.Internal Methods fromString :: String -> Identifier # | |
Pretty Identifier Source # | |
Defined in Types.Internal |
identifier :: CParser m => m Identifier Source #
identifier_no_lex :: CParser m => m Identifier Source #
This parser parses an Id
and nothing else -- it does not consume
trailing spaces and the like.
data DeclarationSpecifier Source #
Constructors
StorageClassSpecifier StorageClassSpecifier | |
TypeSpecifier TypeSpecifier | |
TypeQualifier TypeQualifier | |
FunctionSpecifier FunctionSpecifier |
Instances
Eq DeclarationSpecifier Source # | |
Defined in Types.Internal Methods (==) :: DeclarationSpecifier -> DeclarationSpecifier -> Bool # (/=) :: DeclarationSpecifier -> DeclarationSpecifier -> Bool # | |
Ord DeclarationSpecifier Source # | |
Defined in Types.Internal Methods compare :: DeclarationSpecifier -> DeclarationSpecifier -> Ordering # (<) :: DeclarationSpecifier -> DeclarationSpecifier -> Bool # (<=) :: DeclarationSpecifier -> DeclarationSpecifier -> Bool # (>) :: DeclarationSpecifier -> DeclarationSpecifier -> Bool # (>=) :: DeclarationSpecifier -> DeclarationSpecifier -> Bool # max :: DeclarationSpecifier -> DeclarationSpecifier -> DeclarationSpecifier # min :: DeclarationSpecifier -> DeclarationSpecifier -> DeclarationSpecifier # | |
Show DeclarationSpecifier Source # | |
Defined in Types.Internal Methods showsPrec :: Int -> DeclarationSpecifier -> ShowS # show :: DeclarationSpecifier -> String # showList :: [DeclarationSpecifier] -> ShowS # | |
Pretty DeclarationSpecifier Source # | |
Defined in Types.Internal |
declaration_specifiers :: forall m. CParser m => m [DeclarationSpecifier] Source #
data StorageClassSpecifier Source #
Instances
data TypeSpecifier Source #
Constructors
VOID | |
CHAR | |
SHORT | |
INT | |
LONG | |
FLOAT | |
DOUBLE | |
SIGNED | |
UNSIGNED | |
Struct Identifier | |
Enum Identifier | |
TypeName Identifier |
Instances
Eq TypeSpecifier Source # | |
Defined in Types.Internal Methods (==) :: TypeSpecifier -> TypeSpecifier -> Bool # (/=) :: TypeSpecifier -> TypeSpecifier -> Bool # | |
Ord TypeSpecifier Source # | |
Defined in Types.Internal Methods compare :: TypeSpecifier -> TypeSpecifier -> Ordering # (<) :: TypeSpecifier -> TypeSpecifier -> Bool # (<=) :: TypeSpecifier -> TypeSpecifier -> Bool # (>) :: TypeSpecifier -> TypeSpecifier -> Bool # (>=) :: TypeSpecifier -> TypeSpecifier -> Bool # max :: TypeSpecifier -> TypeSpecifier -> TypeSpecifier # min :: TypeSpecifier -> TypeSpecifier -> TypeSpecifier # | |
Show TypeSpecifier Source # | |
Defined in Types.Internal Methods showsPrec :: Int -> TypeSpecifier -> ShowS # show :: TypeSpecifier -> String # showList :: [TypeSpecifier] -> ShowS # | |
Pretty TypeSpecifier Source # | |
Defined in Types.Internal |
type_specifier :: CParser m => m TypeSpecifier Source #
data TypeQualifier Source #
Instances
Eq TypeQualifier Source # | |
Defined in Types.Internal Methods (==) :: TypeQualifier -> TypeQualifier -> Bool # (/=) :: TypeQualifier -> TypeQualifier -> Bool # | |
Ord TypeQualifier Source # | |
Defined in Types.Internal Methods compare :: TypeQualifier -> TypeQualifier -> Ordering # (<) :: TypeQualifier -> TypeQualifier -> Bool # (<=) :: TypeQualifier -> TypeQualifier -> Bool # (>) :: TypeQualifier -> TypeQualifier -> Bool # (>=) :: TypeQualifier -> TypeQualifier -> Bool # max :: TypeQualifier -> TypeQualifier -> TypeQualifier # min :: TypeQualifier -> TypeQualifier -> TypeQualifier # | |
Show TypeQualifier Source # | |
Defined in Types.Internal Methods showsPrec :: Int -> TypeQualifier -> ShowS # show :: TypeQualifier -> String # showList :: [TypeQualifier] -> ShowS # | |
Pretty TypeQualifier Source # | |
Defined in Types.Internal |
type_qualifier :: CParser m => m TypeQualifier Source #
data FunctionSpecifier Source #
Constructors
INLINE |
Instances
Eq FunctionSpecifier Source # | |
Defined in Types.Internal Methods (==) :: FunctionSpecifier -> FunctionSpecifier -> Bool # (/=) :: FunctionSpecifier -> FunctionSpecifier -> Bool # | |
Ord FunctionSpecifier Source # | |
Defined in Types.Internal Methods compare :: FunctionSpecifier -> FunctionSpecifier -> Ordering # (<) :: FunctionSpecifier -> FunctionSpecifier -> Bool # (<=) :: FunctionSpecifier -> FunctionSpecifier -> Bool # (>) :: FunctionSpecifier -> FunctionSpecifier -> Bool # (>=) :: FunctionSpecifier -> FunctionSpecifier -> Bool # max :: FunctionSpecifier -> FunctionSpecifier -> FunctionSpecifier # min :: FunctionSpecifier -> FunctionSpecifier -> FunctionSpecifier # | |
Show FunctionSpecifier Source # | |
Defined in Types.Internal Methods showsPrec :: Int -> FunctionSpecifier -> ShowS # show :: FunctionSpecifier -> String # showList :: [FunctionSpecifier] -> ShowS # | |
Pretty FunctionSpecifier Source # | |
Defined in Types.Internal |
function_specifier :: CParser m => m FunctionSpecifier Source #
data Declarator Source #
Constructors
Declarator | |
Fields |
Instances
Eq Declarator Source # | |
Defined in Types.Internal | |
Ord Declarator Source # | |
Defined in Types.Internal Methods compare :: Declarator -> Declarator -> Ordering # (<) :: Declarator -> Declarator -> Bool # (<=) :: Declarator -> Declarator -> Bool # (>) :: Declarator -> Declarator -> Bool # (>=) :: Declarator -> Declarator -> Bool # max :: Declarator -> Declarator -> Declarator # min :: Declarator -> Declarator -> Declarator # | |
Show Declarator Source # | |
Defined in Types.Internal Methods showsPrec :: Int -> Declarator -> ShowS # show :: Declarator -> String # showList :: [Declarator] -> ShowS # | |
Pretty Declarator Source # | |
Defined in Types.Internal |
declarator :: CParser m => m Declarator Source #
data DirectDeclarator Source #
Constructors
DeclaratorRoot Identifier | |
ArrayOrProto DirectDeclarator ArrayOrProto | |
DeclaratorParens Declarator |
Instances
Eq DirectDeclarator Source # | |
Defined in Types.Internal Methods (==) :: DirectDeclarator -> DirectDeclarator -> Bool # (/=) :: DirectDeclarator -> DirectDeclarator -> Bool # | |
Ord DirectDeclarator Source # | |
Defined in Types.Internal Methods compare :: DirectDeclarator -> DirectDeclarator -> Ordering # (<) :: DirectDeclarator -> DirectDeclarator -> Bool # (<=) :: DirectDeclarator -> DirectDeclarator -> Bool # (>) :: DirectDeclarator -> DirectDeclarator -> Bool # (>=) :: DirectDeclarator -> DirectDeclarator -> Bool # max :: DirectDeclarator -> DirectDeclarator -> DirectDeclarator # min :: DirectDeclarator -> DirectDeclarator -> DirectDeclarator # | |
Show DirectDeclarator Source # | |
Defined in Types.Internal Methods showsPrec :: Int -> DirectDeclarator -> ShowS # show :: DirectDeclarator -> String # showList :: [DirectDeclarator] -> ShowS # | |
Pretty DirectDeclarator Source # | |
Defined in Types.Internal |
direct_declarator :: CParser m => m DirectDeclarator Source #
data ArrayOrProto Source #
Constructors
Array ArrayType | |
Proto [ParameterDeclaration] |
Instances
Eq ArrayOrProto Source # | |
Defined in Types.Internal | |
Ord ArrayOrProto Source # | |
Defined in Types.Internal Methods compare :: ArrayOrProto -> ArrayOrProto -> Ordering # (<) :: ArrayOrProto -> ArrayOrProto -> Bool # (<=) :: ArrayOrProto -> ArrayOrProto -> Bool # (>) :: ArrayOrProto -> ArrayOrProto -> Bool # (>=) :: ArrayOrProto -> ArrayOrProto -> Bool # max :: ArrayOrProto -> ArrayOrProto -> ArrayOrProto # min :: ArrayOrProto -> ArrayOrProto -> ArrayOrProto # | |
Show ArrayOrProto Source # | |
Defined in Types.Internal Methods showsPrec :: Int -> ArrayOrProto -> ShowS # show :: ArrayOrProto -> String # showList :: [ArrayOrProto] -> ShowS # | |
Pretty ArrayOrProto Source # | |
Defined in Types.Internal |
array_or_proto :: CParser m => m ArrayOrProto Source #
Constructors
VariablySized | |
Unsized | |
SizedByInteger Integer | |
SizedByIdentifier Identifier |
Instances
Eq ArrayType Source # | |
Ord ArrayType Source # | |
Show ArrayType Source # | |
Pretty ArrayType Source # | |
Defined in Types.Internal |
array_type :: CParser m => m ArrayType Source #
Constructors
Pointer [TypeQualifier] |
data ParameterDeclaration Source #
Constructors
ParameterDeclaration | |
Instances
Eq ParameterDeclaration Source # | |
Defined in Types.Internal Methods (==) :: ParameterDeclaration -> ParameterDeclaration -> Bool # (/=) :: ParameterDeclaration -> ParameterDeclaration -> Bool # | |
Ord ParameterDeclaration Source # | |
Defined in Types.Internal Methods compare :: ParameterDeclaration -> ParameterDeclaration -> Ordering # (<) :: ParameterDeclaration -> ParameterDeclaration -> Bool # (<=) :: ParameterDeclaration -> ParameterDeclaration -> Bool # (>) :: ParameterDeclaration -> ParameterDeclaration -> Bool # (>=) :: ParameterDeclaration -> ParameterDeclaration -> Bool # max :: ParameterDeclaration -> ParameterDeclaration -> ParameterDeclaration # min :: ParameterDeclaration -> ParameterDeclaration -> ParameterDeclaration # | |
Show ParameterDeclaration Source # | |
Defined in Types.Internal Methods showsPrec :: Int -> ParameterDeclaration -> ShowS # show :: ParameterDeclaration -> String # showList :: [ParameterDeclaration] -> ShowS # | |
Pretty ParameterDeclaration Source # | |
Defined in Types.Internal |
parameter_declaration :: CParser m => m ParameterDeclaration Source #
parameter_list :: CParser m => m [ParameterDeclaration] Source #
data AbstractDeclarator Source #
Constructors
AbstractDeclarator | |
Instances
Eq AbstractDeclarator Source # | |
Defined in Types.Internal Methods (==) :: AbstractDeclarator -> AbstractDeclarator -> Bool # (/=) :: AbstractDeclarator -> AbstractDeclarator -> Bool # | |
Ord AbstractDeclarator Source # | |
Defined in Types.Internal Methods compare :: AbstractDeclarator -> AbstractDeclarator -> Ordering # (<) :: AbstractDeclarator -> AbstractDeclarator -> Bool # (<=) :: AbstractDeclarator -> AbstractDeclarator -> Bool # (>) :: AbstractDeclarator -> AbstractDeclarator -> Bool # (>=) :: AbstractDeclarator -> AbstractDeclarator -> Bool # max :: AbstractDeclarator -> AbstractDeclarator -> AbstractDeclarator # min :: AbstractDeclarator -> AbstractDeclarator -> AbstractDeclarator # | |
Show AbstractDeclarator Source # | |
Defined in Types.Internal Methods showsPrec :: Int -> AbstractDeclarator -> ShowS # show :: AbstractDeclarator -> String # showList :: [AbstractDeclarator] -> ShowS # | |
Pretty AbstractDeclarator Source # | |
Defined in Types.Internal |
abstract_declarator :: CParser m => m AbstractDeclarator Source #
data DirectAbstractDeclarator Source #
Constructors
ArrayOrProtoHere ArrayOrProto | |
ArrayOrProtoThere DirectAbstractDeclarator ArrayOrProto | |
AbstractDeclaratorParens AbstractDeclarator |
Instances
YACC grammar
The parser above is derived from a modification of the YACC grammar for C99 found at http://www.quut.com/c/ANSI-C-grammar-y-1999.html, reproduced below.
%token IDENTIFIER TYPE_NAME INTEGER %token TYPEDEF EXTERN STATIC AUTO REGISTER INLINE RESTRICT %token CHAR SHORT INT LONG SIGNED UNSIGNED FLOAT DOUBLE CONST VOLATILE VOID %token BOOL COMPLEX IMAGINARY %token STRUCT UNION ENUM %start parameter_list %% declaration_specifiers : storage_class_specifier | storage_class_specifier declaration_specifiers | type_specifier | type_specifier declaration_specifiers | type_qualifier | type_qualifier declaration_specifiers | function_specifier | function_specifier declaration_specifiers ; storage_class_specifier : TYPEDEF | EXTERN | STATIC | AUTO | REGISTER ; type_specifier : VOID | CHAR | SHORT | INT | LONG | FLOAT | DOUBLE | SIGNED | UNSIGNED | BOOL | COMPLEX | IMAGINARY | STRUCT IDENTIFIER | UNION IDENTIFIER | ENUM IDENTIFIER | TYPE_NAME ; type_qualifier : CONST | RESTRICT | VOLATILE ; function_specifier : INLINE ; declarator : pointer direct_declarator | direct_declarator ; direct_declarator : IDENTIFIER | '(' declarator ')' | direct_declarator '[' type_qualifier_list ']' | direct_declarator '[' type_qualifier_list*
']' | direct_declarator '['*
']' | direct_declarator '[' IDENTIFIER ']' | direct_declarator '[' INTEGER ']' | direct_declarator '[' ']' | direct_declarator '(' parameter_list ')' | direct_declarator '(' ')' ; pointer :*
|*
type_qualifier_list |*
pointer |*
type_qualifier_list pointer ; type_qualifier_list : type_qualifier | type_qualifier_list type_qualifier ; parameter_list : parameter_declaration | parameter_list ',' parameter_declaration ; parameter_declaration : declaration_specifiers declarator | declaration_specifiers abstract_declarator | declaration_specifiers ; abstract_declarator : pointer | direct_abstract_declarator | pointer direct_abstract_declarator ; direct_abstract_declarator : '(' abstract_declarator ')' | '[' ']' | direct_abstract_declarator '[' ']' | '['*
']' | direct_abstract_declarator '['*
']' | '[' IDENTIFIER ']' | direct_abstract_declarator '[' IDENTIFIER ']' | '[' INTEGER ']' | direct_abstract_declarator '[' INTEGER ']' | '(' ')' | '(' parameter_list ')' | direct_abstract_declarator '(' ')' | direct_abstract_declarator '(' parameter_list ')' ; %% #include <stdio.h> extern char yytext[]; extern int column; void yyerror(char const *s) { fflush(stdout); printf("n%*sn%*sn", column, "^", column, s); }