godot-haskell-0.1.0.0: Haskell bindings for the Godot game engine API

Safe HaskellNone
LanguageHaskell2010

Types.Internal

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

runCParser Source #

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 forall m. CParser m => m a is a valid argument.

-> Either ParseError a 

Runs a CParser using parsec.

quickCParser Source #

Arguments

:: IsTypeName

Function determining if an identifier is a type name.

-> String

String to parse.

-> ReaderT IsTypeName (Parsec String ()) a

Parser. Anything with type forall m. CParser 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 IsTypeName (Parsec String ()) a

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

-> a 

Like quickCParser, but uses const False as IsTypeName.

Types and parsing

newtype Identifier Source #

Constructors

Identifier 

Fields

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 Pointer Source #

Constructors

Pointer [TypeQualifier] 
Instances
Eq Pointer Source # 
Instance details

Defined in Types.Internal

Methods

(==) :: Pointer -> Pointer -> Bool #

(/=) :: Pointer -> Pointer -> Bool #

Ord Pointer Source # 
Instance details

Defined in Types.Internal

Show Pointer Source # 
Instance details

Defined in Types.Internal

Pretty Pointer Source # 
Instance details

Defined in Types.Internal

Methods

pretty :: Pointer -> Doc #

prettyList :: [Pointer] -> Doc #

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