inline-c-0.5.4.1: Write Haskell source files including C code inline. No FFI required.

Safe HaskellNone
LanguageHaskell2010

Language.C.Types.Parse

Contents

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 (where x is a C identifier). In C99 they can be arbitrary expressions. See the ArrayType data type.
  • _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

Parser configuration

type TypeNames = HashSet CIdentifier Source

A collection of named types (typedefs)

data CParserContext i Source

Constructors

CParserContext 

Fields

cpcIdentName :: String
 
cpcTypeNames :: TypeNames

Function used to determine whether an identifier is a type name.

cpcParseIdent :: forall m. CParser i m => m i

Parses an identifier, *without consuming whitespace afterwards*.

cpcIdentToString :: i -> String
 

Default configuration

Parser type

type CParser i m = (Monad m, Functor m, Applicative m, MonadPlus m, Parsing m, CharParsing m, TokenParsing m, LookAheadParsing m, MonadReader (CParserContext i) m, Hashable i) 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.

We parametrize the parsing by the type of the variable identifiers, i. We do so because we use this parser to implement anti-quoters referring to Haskell variables, and thus we need to parse Haskell identifiers in certain positions.

runCParser Source

Arguments

:: Stream s Identity Char 
=> CParserContext i 
-> String

Source name.

-> s

String to parse.

-> ReaderT (CParserContext i) (Parsec s ()) a

Parser. Anything with type forall m. CParser i m => m a is a valid argument.

-> Either ParseError a 

Runs a CParser using parsec.

quickCParser Source

Arguments

:: CParserContext i 
-> String

String to parse.

-> ReaderT (CParserContext i) (Parsec String ()) a

Parser. Anything with type forall m. CParser i m => m a is a valid argument.

-> a 

Useful for quick testing. Uses "quickCParser" as source name, and throws an error if parsing fails.

quickCParser_ Source

Arguments

:: String

String to parse.

-> ReaderT (CParserContext CIdentifier) (Parsec String ()) a

Parser. Anything with type forall m. CParser i m => m a is a valid argument.

-> a 

Types and parsing

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);
}

Testing utilities