------------------------------------------------------------------ -- | -- Module : Language.WebIDL.Syntax -- Copyright : (c) Dmitry Golubovsky, 2009 -- License : BSD-style -- -- Maintainer : golubovsky@gmail.com -- Stability : experimental -- Portability : portable -- -- -- -- Web IDL syntax representation. It is built based on the original -- yacc/bison parser found in the es-operating-system project. -- The source of the original parser (written in C++) is located here: -- -- -------------------------------------------------------------------- module Language.WebIDL.Syntax where import Data.Maybe import Text.ParserCombinators.Parsec.Pos -- specification : | definition_list type IDLSpecification = [IDLDefinition] newtype JavaDoc = JavaDoc String deriving (Show) data IDLDefinition = IDLDefinition SourcePos JavaDoc IDLDef deriving (Show) -- definition : -- module ';' -- | interface ';' -- | except_dcl ';' -- | type_dcl ';' -- | value ';' -- | const_dcl ';' -- | preprocessor data IDLDef = -- module : -- extended_attribute_opt MODULE IDENTIFIER -- '{' definition_list '}' IDLDefModule String [IDLExtAttr] [IDLDefinition] -- interface : -- interface_dcl -- | forward_dcl -- interface_dcl : -- interface_header '{' interface_body '}' -- interface_header : -- INTERFACE IDENTIFIER interface_inheritance_spec -- | INTERFACE IDENTIFIER -- | extended_attribute_list INTERFACE IDENTIFIER interface_inheritance_spec -- | extended_attribute_list INTERFACE IDENTIFIER -- value : -- value_box_dcl -- | value_forward_dcl -- value_forward_dcl : -- VALUETYPE IDENTIFIER -- value_box_dcl : -- VALUETYPE IDENTIFIER type_spec | IDLDefInterface String [IDLExtAttr] [IDLScopedName] (Maybe IDLInterfaceBody) | IDLDefExcept IDLExceptDcl | IDLDefType IDLTypeDcl | IDLDefConst IDLConstDcl | IDLDefValue String (Maybe IDLTypeSpec) | IDLDefPP deriving (Show) -- scoped_name : -- IDENTIFIER -- | OP_SCOPE IDENTIFIER -- | scoped_name OP_SCOPE IDENTIFIER data IDLScopedName = IDLScopedName [String] deriving (Show) -- extended_attribute_opt : -- | extended_attribute_list -- extended_attribute_list : -- '[' extended_attributes ']' -- extended_attributes : -- extended_attribute -- | extended_attributes ',' extended_attribute -- extended_attribute : -- javadoc IDENTIFIER extended_attribute_details data IDLExtAttr = IDLExtAttr JavaDoc String (Maybe IDLExtAttrDetails) deriving (Show) -- extended_attribute_details : -- | '=' scoped_name -- | '=' IDENTIFIER parameter_dcls -- | parameter_dcls data IDLExtAttrDetails = IDLDetailSN IDLScopedName | IDLDetailID String [IDLParamDcl] | IDLDetailPD [IDLParamDcl] deriving (Show) -- simple_declarator : -- IDENTIFIER -- param_attribute : -- IN -- | OUT -- | INOUT data IDLParamAttr = IDLParamIn | IDLParamOut | IDLParamInOut deriving (Show) -- param_type_spec : -- base_type_spec -- | string_type -- | scoped_name data IDLParamTypeSpec = IDLParamBaseSpec IDLBaseTypeSpec | IDLParamStringSpec IDLStringType | IDLParamScopedSpec IDLScopedName | IDLParamVoid -- to be also used with op_type_spec deriving (Show) -- base_type_spec : -- floating_pt_type -- | integer_type -- | char_type -- | boolean_type -- | octet_type -- | any_type data IDLBaseTypeSpec = IDLBaseTypeFloat IDLFloatingType | IDLBaseTypeInt IDLIntegerType | IDLBaseTypeChar | IDLBaseTypeBool | IDLBaseTypeOctet | IDLBaseTypeAny deriving (Show) -- floating_pt_type : -- FLOAT -- | DOUBLE -- | LONG DOUBLE data IDLFloatingType = IDLFloat | IDLDouble | IDLLongDouble deriving (Show) -- integer_type : -- signed_int -- | unsigned_int -- signed_int : -- signed_short_int -- | signed_long_int -- | signed_longlong_int -- signed_short_int : -- SHORT -- signed_long_int : -- LONG -- signed_longlong_int : -- LONG LONG -- unsigned_int : -- unsigned_short_int -- | unsigned_long_int -- | unsigned_longlong_int -- unsigned_short_int : -- UNSIGNED SHORT -- unsigned_long_int : -- UNSIGNED LONG -- unsigned_longlong_int : -- UNSIGNED LONG LONG data IDLIntegerType = IDLSigned IDLInteger | IDLUnsigned IDLInteger deriving (Show) data IDLInteger = IDLShortInt | IDLLongInt | IDLLongLongInt deriving (Show) -- interface_body : -- export_list_opt -- export_list_opt : -- /* empty */ -- | export_list data IDLInterfaceBody = IDLInterfaceBody [IDLExport] deriving (Show) -- export_list : -- javadoc export -- | export_list javadoc export data IDLExport = IDLExport SourcePos JavaDoc IDLExp deriving (Show) -- export : -- type_dcl ';' -- | const_dcl ';' -- | except_dcl ';' -- | attr_dcl ';' -- | op_dcl ';' -- | preprocessor data IDLExp = IDLExpType IDLTypeDcl | IDLExpConst IDLConstDcl | IDLExpExcept IDLExceptDcl | IDLExpAttr IDLAttrDcl | IDLExpOp IDLOpDcl | IDLExpPP deriving (Show) -- type_dcl : -- TYPEDEF type_declarator -- | struct_type -- | NATIVE simple_declarator -- | constr_forward_decl data IDLTypeDcl = IDLTypeDef IDLTypeSpec [IDLDeclarator] | IDLNative String | IDLStruct IDLStructType | IDLConstrFwd String deriving (Show) -- type_spec : -- simple_type_spec -- | struct_type data IDLTypeSpec = IDLSimpleSpec IDLSimpleTypeSpec | IDLStructSpec IDLStructType deriving (Show) -- simple_type_spec : -- base_type_spec -- | template_type_spec -- | scoped_name data IDLSimpleTypeSpec = IDLSimpleBase IDLBaseTypeSpec | IDLSimpleTmpl IDLTemplateTypeSpec | IDLSimpleScoped IDLScopedName deriving (Show) -- template_type_spec : -- sequence_type -- | string_type -- | fixed_pt_type data IDLTemplateTypeSpec = IDLTmplSequence IDLSequenceType | IDLTmplString IDLStringType | IDLTmplFixed IDLFixedType deriving (Show) -- sequence_type : -- SEQUENCE '<' simple_type_spec ',' positive_int_const '>' -- | SEQUENCE '<' simple_type_spec '>' data IDLSequenceType = IDLSequenceType IDLSimpleTypeSpec (Maybe IDLConstExp) deriving (Show) -- string_type : -- STRING '<' positive_int_const '>' -- | STRING data IDLStringType = IDLStringType (Maybe IDLConstExp) deriving (Show) -- fixed_pt_type : -- FIXED '<' positive_int_const ',' positive_int_const '>' data IDLFixedType = IDLFixedType IDLConstExp IDLConstExp deriving (Show) -- struct_type : -- STRUCT IDENTIFIER -- '{' member_list '}' -- member_list_opt : -- /* empty */ -- | member_list -- member_list : -- member -- | member_list member -- member : -- type_spec declarators ';' data IDLStructType = IDLStructType String [IDLMember] deriving (Show) data IDLMember = IDLMember IDLTypeSpec [IDLDeclarator] deriving (Show) -- const_dcl : -- CONST const_type IDENTIFIER '=' const_exp data IDLConstDcl = IDLConstDcl IDLConstType String IDLConstExp deriving (Show) -- const_type : -- integer_type -- | char_type -- | boolean_type -- | floating_pt_type -- | string_type -- | fixed_pt_const_type -- | scoped_name -- | octet_type data IDLConstType = IDLConstTypeFloat IDLFloatingType | IDLConstTypeInt IDLIntegerType | IDLConstTypeString IDLStringType | IDLConstTypeChar | IDLConstTypeBool | IDLConstTypeFixed | IDLConstTypeOctet | IDLConstTypeScoped IDLScopedName deriving (Show) -- except_dcl : -- EXCEPTION IDENTIFIER -- '{' member_list_opt '}' data IDLExceptDcl = IDLExceptDcl String [IDLMember] deriving (Show) -- attr_dcl : -- readonly_attr_spec -- | attr_spec -- readonly_attr_spec : -- extended_attribute_opt READONLY ATTRIBUTE param_type_spec -- simple_declarator get_excep_expr set_excep_expr -- attr_spec : -- extended_attribute_opt ATTRIBUTE param_type_spec -- simple_declarator get_excep_expr set_excep_expr data IDLAttrDcl = IDLAttrDcl [IDLExtAttr] Bool IDLParamTypeSpec String [IDLScopedName] [IDLScopedName] deriving (Show) -- op_dcl : -- op_attribute_opt op_type_spec IDENTIFIER -- parameter_dcls raises_expr_opt -- | extended_attribute_list op_attribute_opt op_type_spec IDENTIFIER -- parameter_dcls raises_expr_opt -- op_attribute_opt : -- /* empty */ -- | ONEWAY -- op_type_spec : -- param_type_spec -- | VOID data IDLOpDcl = IDLOpDcl [IDLExtAttr] (Maybe IDLOpAttr) IDLParamTypeSpec String [IDLParamDcl] [IDLScopedName] deriving (Show) data IDLOpAttr = IDLOneWay deriving (Show) -- parameter_dcls : -- '(' param_dcl_list ')' -- | '(' ')' -- param_dcl_list : -- param_dcl -- | param_dcl_list ',' param_dcl -- param_dcl : -- extended_attribute_opt param_attribute param_type_spec simple_declarator data IDLParamDcl = IDLParamDcl [IDLExtAttr] IDLParamAttr IDLParamTypeSpec String deriving (Show) -- declarator : -- simple_declarator -- | complex_declarator data IDLDeclarator = IDLSimpleDecl String | IDLComplexDecl IDLArrayDeclarator deriving (Show) -- array_declarator : -- IDENTIFIER fixed_array_size_list -- fixed_array_size_list : -- fixed_array_size -- | fixed_array_size_list fixed_array_size -- fixed_array_size : -- '[' positive_int_const ']' data IDLArrayDeclarator = IDLArrayDeclarator String [IDLConstExp] deriving (Show) -- The following combines multiple BNFs for constant expressions. data IDLConstExp = IDLBinExp IDLBinaryOp IDLConstExp IDLConstExp | IDLUnaryExp IDLUnaryOp IDLConstExp | IDLPrimScoped IDLScopedName | IDLPrimLit IDLLiteral | IDLParenExp IDLConstExp deriving (Show) data IDLBinaryOp = IDLOr | IDLXor | IDLAnd | IDLShiftL | IDLShiftR | IDLAdd | IDLSub | IDLMult | IDLDiv | IDLRem deriving (Show) data IDLUnaryOp = IDLPos | IDLNeg | IDLNot deriving (Show) data IDLLiteral = IDLIntLit String | IDLStringLit String | IDLCharLit String | IDLFixedLit String | IDLFloatLit String | IDLBoolLit String deriving (Show)