Safe Haskell | Safe |
---|---|
Language | Haskell2010 |
Language.WebIDL.AST
Description
- data Definition a
- = DefInterface (Interface a)
- | DefPartial (Partial a)
- | DefDictionary (Dictionary a)
- | DefEnum (Enum a)
- | DefTypedef (Typedef a)
- | DefCallback (Callback a)
- | DefImplementsStatement (ImplementsStatement a)
- data ExtendedAttribute a
- data Interface a = Interface a [ExtendedAttribute a] Ident (Maybe Ident) [InterfaceMember a]
- data Partial a
- = PartialInterface a Ident [InterfaceMember a]
- | PartialDictionary a Ident [DictionaryMember a]
- data Callback a = Callback a Ident ReturnType [Argument a]
- data Dictionary a = Dictionary a Ident (Maybe Ident) [DictionaryMember a]
- data Exception a = Exception a Ident (Maybe Ident) [ExceptionMember a]
- data Enum a = Enum a Ident [EnumValue]
- data Typedef a = Typedef a Type Ident
- data ImplementsStatement a = ImplementsStatement a Ident Ident
- data InterfaceMember a
- = IMemConst (Const a)
- | IMemAttribute (Attribute a)
- | IMemOperation (Operation a)
- data DictionaryMember a = DictionaryMember a Type Ident (Maybe Default)
- data ExceptionMember a
- data Attribute a = Attribute a (Maybe Inherit) (Maybe ReadOnly) Type Ident
- data Operation a = Operation a [ExtendedAttribute a] (Maybe Qualifier) ReturnType (Maybe Ident) [Argument a]
- data Argument a
- newtype EnumValue = EnumValue String
- data ArgumentName
- data Const a = Const a ConstType Ident ConstValue
- data Default
- data ConstValue
- data Qualifier
- data Special
- = Getter
- | Setter
- | Deleter
- | LegacyCaller
- data ArgumentNameKeyword
- data Type
- data SingleType
- = STyNonAny NonAnyType
- | STyAny (Maybe Null)
- data NonAnyType
- data PrimitiveType
- data IntegerType = IntegerType (Maybe Unsigned) IntegerWidth
- data IntegerWidth
- data Unsigned = Unsigned
- data FloatType
- type UnionType = [UnionMemberType]
- data UnionMemberType
- data ReturnType
- data ConstType
- = ConstPrim PrimitiveType (Maybe Null)
- | ConstIdent Ident (Maybe Null)
- data Null = Null
- data Ellipsis = Ellipsis
- data ReadOnly = ReadOnly
- data Inherit = Inherit
- data Unrestricted = Unrestricted
- newtype Ident = Ident String
Documentation
data Definition a Source #
Definition
Constructors
DefInterface (Interface a) | |
DefPartial (Partial a) | |
DefDictionary (Dictionary a) | |
DefEnum (Enum a) | |
DefTypedef (Typedef a) | |
DefCallback (Callback a) | |
DefImplementsStatement (ImplementsStatement a) |
Instances
Functor Definition Source # | |
Eq a => Eq (Definition a) Source # | |
Show a => Show (Definition a) Source # | |
data ExtendedAttribute a Source #
Extended attribute
Constructors
ExtendedAttributeNoArgs a Ident | identifier |
ExtendedAttributeArgList a Ident [Argument a] | identifier "(" ArgumentList ")" |
ExtendedAttributeIdent a Ident Ident | identifier "=" identifier |
ExtendedAttributeIdentList a Ident [Ident] | identifier "=" "(" IdentifierList ")" |
ExtendedAttributeNamedArgList a Ident Ident [Argument a] | identifier "=" identifier "(" ArgumentList ")" |
Instances
Functor ExtendedAttribute Source # | |
Eq a => Eq (ExtendedAttribute a) Source # | |
Show a => Show (ExtendedAttribute a) Source # | |
interface
Constructors
Interface a [ExtendedAttribute a] Ident (Maybe Ident) [InterfaceMember a] |
Partial Definition
Constructors
PartialInterface a Ident [InterfaceMember a] | |
PartialDictionary a Ident [DictionaryMember a] |
Callback functions
Constructors
Callback a Ident ReturnType [Argument a] |
data Dictionary a Source #
dictionary
Constructors
Dictionary a Ident (Maybe Ident) [DictionaryMember a] |
Instances
Functor Dictionary Source # | |
Eq a => Eq (Dictionary a) Source # | |
Show a => Show (Dictionary a) Source # | |
exception
Constructors
Exception a Ident (Maybe Ident) [ExceptionMember a] |
enum
typedef
data ImplementsStatement a Source #
implements
statement
Constructors
ImplementsStatement a Ident Ident |
Instances
Functor ImplementsStatement Source # | |
Eq a => Eq (ImplementsStatement a) Source # | |
Show a => Show (ImplementsStatement a) Source # | |
data InterfaceMember a Source #
Member of interface definition
Constructors
IMemConst (Const a) | |
IMemAttribute (Attribute a) | |
IMemOperation (Operation a) |
Instances
Functor InterfaceMember Source # | |
Eq a => Eq (InterfaceMember a) Source # | |
Show a => Show (InterfaceMember a) Source # | |
data DictionaryMember a Source #
Member of dictionary
Constructors
DictionaryMember a Type Ident (Maybe Default) |
Instances
Functor DictionaryMember Source # | |
Eq a => Eq (DictionaryMember a) Source # | |
Show a => Show (DictionaryMember a) Source # | |
data ExceptionMember a Source #
Member of exception definition
Instances
Functor ExceptionMember Source # | |
Eq a => Eq (ExceptionMember a) Source # | |
Show a => Show (ExceptionMember a) Source # | |
Attribute member of interface
Operation member of interface
Constructors
Operation a [ExtendedAttribute a] (Maybe Qualifier) ReturnType (Maybe Ident) [Argument a] |
Argument of operation signature
Constructors
ArgOptional [ExtendedAttribute a] Type ArgumentName (Maybe Default) | |
ArgNonOpt [ExtendedAttribute a] Type (Maybe Ellipsis) ArgumentName |
Value of a enum
data ArgumentName Source #
Name of argument
Constructors
ArgKey ArgumentNameKeyword | |
ArgIdent Ident |
Instances
const
Constructors
Const a ConstType Ident ConstValue |
default
specification
Constructors
DefaultValue ConstValue | |
DefaultString String |
Qualifers
Special qualifier
Constructors
Getter | |
Setter | |
Deleter | |
LegacyCaller |
data ArgumentNameKeyword Source #
Argument name keyword
Constructors
Instances
Types
Constructors
TySingleType SingleType | |
TyUnionType UnionType (Maybe Null) |
data NonAnyType Source #
Types that is not any
Constructors
TyPrim PrimitiveType (Maybe Null) | |
TyDOMString (Maybe Null) | |
TyIdent Ident (Maybe Null) | |
TySequence Type (Maybe Null) | |
TyObject (Maybe Null) | |
TyDate (Maybe Null) |
Instances
data PrimitiveType Source #
Primitive type
Constructors
PrimIntegerType IntegerType | |
PrimFloatType FloatType | |
Boolean | |
Byte | |
Octet |
Instances
data IntegerType Source #
Integer type
Constructors
IntegerType (Maybe Unsigned) IntegerWidth |
Instances
unsigned
modifier
Constructors
Unsigned |
Float type
Constructors
TyFloat (Maybe Unrestricted) | |
TyDouble (Maybe Unrestricted) |
type UnionType = [UnionMemberType] Source #
Union of several types
data UnionMemberType Source #
Union member type
Constructors
UnionTy UnionType (Maybe Null) | |
UnionTyNonAny NonAnyType |
Instances
Constant's type
Constructors
ConstPrim PrimitiveType (Maybe Null) | |
ConstIdent Ident (Maybe Null) |
ellipsis
marker
Constructors
Ellipsis |
readonly
marker
Constructors
ReadOnly |
inherit
marker
Constructors
Inherit |