| Copyright | (c) Abhinav Gupta 2016 |
|---|---|
| License | BSD3 |
| Maintainer | Abhinav Gupta <mail@abhinavg.net> |
| Stability | experimental |
| Safe Haskell | Safe |
| Language | Haskell2010 |
Language.Thrift.AST
Contents
Description
This module defines types that compose a Thrift IDL file.
Most of the types have an optional srcAnnot parameter that represents a
source annotation. The parser produces types annotated with their position
in the Thrift file (SourcePos). When constructing the AST
by hand, you can use (). The types are Functors so you can use fmap
to change the annotation on all objects in a tree.
Lenses for attributes of most types are provided for use with the lens
library.
Types representing the AST all have Pretty
instances to go with them.
- data Program srcAnnot = Program {
- programHeaders :: [Header srcAnnot]
- programDefinitions :: [Definition srcAnnot]
- headers :: Lens (Program a) [Header a]
- definitions :: Lens (Program a) [Definition a]
- data Header srcAnnot
- = HeaderInclude (Include srcAnnot)
- | HeaderNamespace (Namespace srcAnnot)
- data Include srcAnnot = Include {
- includePath :: Text
- includeSrcAnnot :: srcAnnot
- path :: Lens (Include a) Text
- data Namespace srcAnnot = Namespace {
- namespaceLanguage :: Text
- namespaceName :: Text
- namespaceSrcAnnot :: srcAnnot
- language :: Lens (Namespace a) Text
- data Definition srcAnnot
- = ConstDefinition (Const srcAnnot)
- | TypeDefinition (Type srcAnnot)
- | ServiceDefinition (Service srcAnnot)
- data Const srcAnnot = Const {
- constValueType :: TypeReference srcAnnot
- constName :: Text
- constValue :: ConstValue srcAnnot
- constDocstring :: Docstring
- constSrcAnnot :: srcAnnot
- data Service srcAnnot = Service {
- serviceName :: Text
- serviceExtends :: Maybe Text
- serviceFunctions :: [Function srcAnnot]
- serviceAnnotations :: [TypeAnnotation]
- serviceDocstring :: Docstring
- serviceSrcAnnot :: srcAnnot
- functions :: Lens (Service a) [Function a]
- extends :: Lens (Service a) (Maybe Text)
- data Type srcAnnot
- = TypedefType (Typedef srcAnnot)
- | EnumType (Enum srcAnnot)
- | StructType (Struct srcAnnot)
- | SenumType (Senum srcAnnot)
- data Typedef srcAnnot = Typedef {
- typedefTargetType :: TypeReference srcAnnot
- typedefName :: Text
- typedefAnnotations :: [TypeAnnotation]
- typedefDocstring :: Docstring
- typedefSrcAnnot :: srcAnnot
- targetType :: Lens (Typedef a) (TypeReference a)
- data Enum srcAnnot = Enum {
- enumName :: Text
- enumValues :: [EnumDef srcAnnot]
- enumAnnotations :: [TypeAnnotation]
- enumDocstring :: Docstring
- enumSrcAnnot :: srcAnnot
- data StructKind
- data Struct srcAnnot = Struct {
- structKind :: StructKind
- structName :: Text
- structFields :: [Field srcAnnot]
- structAnnotations :: [TypeAnnotation]
- structDocstring :: Docstring
- structSrcAnnot :: srcAnnot
- kind :: Lens (Struct a) StructKind
- type Union = Struct
- unionName :: Union a -> Text
- unionFields :: Union a -> [Field a]
- unionAnnotations :: Union a -> [TypeAnnotation]
- unionDocstring :: Union a -> Docstring
- unionSrcAnnot :: Union a -> a
- type Exception = Struct
- exceptionName :: Exception a -> Text
- exceptionFields :: Exception a -> [Field a]
- exceptionAnnotations :: Exception a -> [TypeAnnotation]
- exceptionDocstring :: Exception a -> Docstring
- exceptionSrcAnnot :: Exception a -> a
- data Senum srcAnnot = Senum {
- senumName :: Text
- senumValues :: [Text]
- senumAnnotations :: [TypeAnnotation]
- senumDocstring :: Docstring
- senumSrcAnnot :: srcAnnot
- data FieldRequiredness
- data Field srcAnnot = Field {
- fieldIdentifier :: Maybe Integer
- fieldRequiredness :: Maybe FieldRequiredness
- fieldValueType :: TypeReference srcAnnot
- fieldName :: Text
- fieldDefaultValue :: Maybe (ConstValue srcAnnot)
- fieldAnnotations :: [TypeAnnotation]
- fieldDocstring :: Docstring
- fieldSrcAnnot :: srcAnnot
- identifier :: Lens (Field a) (Maybe Integer)
- requiredness :: Lens (Field a) (Maybe FieldRequiredness)
- defaultValue :: Lens (Field a) (Maybe (ConstValue a))
- data EnumDef srcAnnot = EnumDef {
- enumDefName :: Text
- enumDefValue :: Maybe Integer
- enumDefAnnotations :: [TypeAnnotation]
- enumDefDocstring :: Docstring
- enumDefSrcAnnot :: srcAnnot
- data ConstValue srcAnnot
- = ConstInt Integer srcAnnot
- | ConstFloat Double srcAnnot
- | ConstLiteral Text srcAnnot
- | ConstIdentifier Text srcAnnot
- | ConstList [ConstValue srcAnnot] srcAnnot
- | ConstMap [(ConstValue srcAnnot, ConstValue srcAnnot)] srcAnnot
- data TypeReference srcAnnot
- = DefinedType Text srcAnnot
- | StringType [TypeAnnotation] srcAnnot
- | BinaryType [TypeAnnotation] srcAnnot
- | SListType [TypeAnnotation] srcAnnot
- | BoolType [TypeAnnotation] srcAnnot
- | ByteType [TypeAnnotation] srcAnnot
- | I16Type [TypeAnnotation] srcAnnot
- | I32Type [TypeAnnotation] srcAnnot
- | I64Type [TypeAnnotation] srcAnnot
- | DoubleType [TypeAnnotation] srcAnnot
- | MapType (TypeReference srcAnnot) (TypeReference srcAnnot) [TypeAnnotation] srcAnnot
- | SetType (TypeReference srcAnnot) [TypeAnnotation] srcAnnot
- | ListType (TypeReference srcAnnot) [TypeAnnotation] srcAnnot
- data Function srcAnnot = Function {
- functionOneWay :: Bool
- functionReturnType :: Maybe (TypeReference srcAnnot)
- functionName :: Text
- functionParameters :: [Field srcAnnot]
- functionExceptions :: Maybe [Field srcAnnot]
- functionAnnotations :: [TypeAnnotation]
- functionDocstring :: Docstring
- functionSrcAnnot :: srcAnnot
- oneWay :: Lens (Function a) Bool
- returnType :: Lens (Function a) (Maybe (TypeReference a))
- parameters :: Lens (Function a) [Field a]
- exceptions :: Lens (Function a) (Maybe [Field a])
- data TypeAnnotation = TypeAnnotation {}
- type Docstring = Maybe Text
- class HasAnnotations t where
- class HasDocstring t where
- class HasFields t where
- class HasName t where
- class HasSrcAnnot t where
- class HasValue s a | s -> a where
- class HasValues s a | s -> a where
- class HasValueType t where
AST
data Program srcAnnot Source #
A program represents a single Thrift document.
Constructors
| Program | |
Fields
| |
Instances
definitions :: Lens (Program a) [Definition a] Source #
Headers for a program.
Constructors
| HeaderInclude (Include srcAnnot) | Request to include another Thrift file. |
| HeaderNamespace (Namespace srcAnnot) | A |
data Include srcAnnot Source #
The IDL includes another Thrift file.
include "common.thrift" typedef common.Foo Bar
Constructors
| Include | |
Fields
| |
Instances
| Functor Include Source # | |
| HasSrcAnnot Include Source # | |
| Eq srcAnnot => Eq (Include srcAnnot) Source # | |
| Data srcAnnot => Data (Include srcAnnot) Source # | |
| Ord srcAnnot => Ord (Include srcAnnot) Source # | |
| Show srcAnnot => Show (Include srcAnnot) Source # | |
| Generic (Include srcAnnot) Source # | |
| type Rep (Include srcAnnot) Source # | |
data Namespace srcAnnot Source #
Namespace directives allows control of the namespace or package name used by the generated code for certain languages.
namespace py my_service.generated
Constructors
| Namespace | |
Fields
| |
Instances
| Functor Namespace Source # | |
| HasSrcAnnot Namespace Source # | |
| Eq srcAnnot => Eq (Namespace srcAnnot) Source # | |
| Data srcAnnot => Data (Namespace srcAnnot) Source # | |
| Ord srcAnnot => Ord (Namespace srcAnnot) Source # | |
| Show srcAnnot => Show (Namespace srcAnnot) Source # | |
| Generic (Namespace srcAnnot) Source # | |
| HasName (Namespace a) Source # | |
| type Rep (Namespace srcAnnot) Source # | |
data Definition srcAnnot Source #
A definition either consists of new constants, new types, or new services.
Constructors
| ConstDefinition (Const srcAnnot) | A declared constant. |
| TypeDefinition (Type srcAnnot) | A custom type. |
| ServiceDefinition (Service srcAnnot) | A service definition. |
Instances
| Functor Definition Source # | |
| HasSrcAnnot Definition Source # | |
| Eq srcAnnot => Eq (Definition srcAnnot) Source # | |
| Data srcAnnot => Data (Definition srcAnnot) Source # | |
| Ord srcAnnot => Ord (Definition srcAnnot) Source # | |
| Show srcAnnot => Show (Definition srcAnnot) Source # | |
| Generic (Definition srcAnnot) Source # | |
| HasName (Definition a) Source # | |
| type Rep (Definition srcAnnot) Source # | |
A declared constant.
const i32 code = 1;
Constructors
| Const | |
Fields
| |
Instances
| Functor Const Source # | |
| HasValueType Const Source # | |
| HasSrcAnnot Const Source # | |
| Eq srcAnnot => Eq (Const srcAnnot) Source # | |
| Data srcAnnot => Data (Const srcAnnot) Source # | |
| Ord srcAnnot => Ord (Const srcAnnot) Source # | |
| Show srcAnnot => Show (Const srcAnnot) Source # | |
| Generic (Const srcAnnot) Source # | |
| HasDocstring (Const a) Source # | |
| HasName (Const a) Source # | |
| HasValue (Const a) (ConstValue a) Source # | |
| type Rep (Const srcAnnot) Source # | |
data Service srcAnnot Source #
A service definition.
service MyService {
// ...
}Constructors
| Service | |
Fields
| |
Instances
| Functor Service Source # | |
| HasSrcAnnot Service Source # | |
| Eq srcAnnot => Eq (Service srcAnnot) Source # | |
| Data srcAnnot => Data (Service srcAnnot) Source # | |
| Ord srcAnnot => Ord (Service srcAnnot) Source # | |
| Show srcAnnot => Show (Service srcAnnot) Source # | |
| Generic (Service srcAnnot) Source # | |
| HasDocstring (Service a) Source # | |
| HasAnnotations (Service a) Source # | |
| HasName (Service a) Source # | |
| type Rep (Service srcAnnot) Source # | |
Defines the various types that can be declared in Thrift.
Constructors
| TypedefType (Typedef srcAnnot) | typedef |
| EnumType (Enum srcAnnot) | enum |
| StructType (Struct srcAnnot) |
|
| SenumType (Senum srcAnnot) | senum |
Instances
| Functor Type Source # | |
| HasSrcAnnot Type Source # | |
| Eq srcAnnot => Eq (Type srcAnnot) Source # | |
| Data srcAnnot => Data (Type srcAnnot) Source # | |
| Ord srcAnnot => Ord (Type srcAnnot) Source # | |
| Show srcAnnot => Show (Type srcAnnot) Source # | |
| Generic (Type srcAnnot) Source # | |
| HasName (Type a) Source # | |
| type Rep (Type srcAnnot) Source # | |
data Typedef srcAnnot Source #
A typedef is just an alias for another type.
typedef common.Foo Bar
Constructors
| Typedef | |
Fields
| |
Instances
| Functor Typedef Source # | |
| HasSrcAnnot Typedef Source # | |
| Eq srcAnnot => Eq (Typedef srcAnnot) Source # | |
| Data srcAnnot => Data (Typedef srcAnnot) Source # | |
| Ord srcAnnot => Ord (Typedef srcAnnot) Source # | |
| Show srcAnnot => Show (Typedef srcAnnot) Source # | |
| Generic (Typedef srcAnnot) Source # | |
| HasDocstring (Typedef a) Source # | |
| HasAnnotations (Typedef a) Source # | |
| HasName (Typedef a) Source # | |
| type Rep (Typedef srcAnnot) Source # | |
targetType :: Lens (Typedef a) (TypeReference a) Source #
Enums are sets of named integer values.
enum Role {
User = 1, Admin = 2
}Constructors
| Enum | |
Fields
| |
Instances
| Functor Enum Source # | |
| HasSrcAnnot Enum Source # | |
| Eq srcAnnot => Eq (Enum srcAnnot) Source # | |
| Data srcAnnot => Data (Enum srcAnnot) Source # | |
| Ord srcAnnot => Ord (Enum srcAnnot) Source # | |
| Show srcAnnot => Show (Enum srcAnnot) Source # | |
| Generic (Enum srcAnnot) Source # | |
| HasDocstring (Enum a) Source # | |
| HasAnnotations (Enum a) Source # | |
| HasName (Enum a) Source # | |
| HasValues (Enum a) [EnumDef a] Source # | |
| type Rep (Enum srcAnnot) Source # | |
data StructKind Source #
The kind of the struct.
Constructors
| StructKind | struct |
| UnionKind | union |
| ExceptionKind | exception |
Instances
A struct, union, or exception definition.
struct User {
1: Role role = Role.User;
}union Value {
1: string stringValue;
2: i32 intValue;
}exception UserDoesNotExist {
1: optional string message
2: required string username
}Constructors
| Struct | |
Fields
| |
Instances
| Functor Struct Source # | |
| HasFields Struct Source # | |
| HasSrcAnnot Struct Source # | |
| Eq srcAnnot => Eq (Struct srcAnnot) Source # | |
| Data srcAnnot => Data (Struct srcAnnot) Source # | |
| Ord srcAnnot => Ord (Struct srcAnnot) Source # | |
| Show srcAnnot => Show (Struct srcAnnot) Source # | |
| Generic (Struct srcAnnot) Source # | |
| HasDocstring (Struct a) Source # | |
| HasAnnotations (Struct a) Source # | |
| HasName (Struct a) Source # | |
| type Rep (Struct srcAnnot) Source # | |
kind :: Lens (Struct a) StructKind Source #
Deprecated: The type has been consolidated into Struct.
A union of other types.
unionFields :: Union a -> [Field a] Source #
Deprecated: Use structFields.
unionAnnotations :: Union a -> [TypeAnnotation] Source #
Deprecated: Use structAnnotations.
unionDocstring :: Union a -> Docstring Source #
Deprecated: Use structDocstring.
unionSrcAnnot :: Union a -> a Source #
Deprecated: Use structSrcAnnot.
type Exception = Struct Source #
Deprecated: The type has been consolidated into Struct.
Exception types.
exceptionName :: Exception a -> Text Source #
Deprecated: Use structName.
exceptionFields :: Exception a -> [Field a] Source #
Deprecated: Use structFields.
exceptionAnnotations :: Exception a -> [TypeAnnotation] Source #
Deprecated: Use structAnnotations.
exceptionDocstring :: Exception a -> Docstring Source #
Deprecated: Use structDocstring.
exceptionSrcAnnot :: Exception a -> a Source #
Deprecated: Use structSrcAnnot.
An string-only enum. These are a deprecated feature of Thrift and shouldn't be used.
Constructors
| Senum | |
Fields
| |
Instances
| Functor Senum Source # | |
| HasSrcAnnot Senum Source # | |
| Eq srcAnnot => Eq (Senum srcAnnot) Source # | |
| Data srcAnnot => Data (Senum srcAnnot) Source # | |
| Ord srcAnnot => Ord (Senum srcAnnot) Source # | |
| Show srcAnnot => Show (Senum srcAnnot) Source # | |
| Generic (Senum srcAnnot) Source # | |
| HasDocstring (Senum a) Source # | |
| HasAnnotations (Senum a) Source # | |
| HasName (Senum a) Source # | |
| HasValues (Senum a) [Text] Source # | |
| type Rep (Senum srcAnnot) Source # | |
data FieldRequiredness Source #
Whether a field is required or optional.
A field inside a struct, exception, or function parameters list.
Constructors
| Field | |
Fields
| |
Instances
| Functor Field Source # | |
| HasValueType Field Source # | |
| HasSrcAnnot Field Source # | |
| Eq srcAnnot => Eq (Field srcAnnot) Source # | |
| Data srcAnnot => Data (Field srcAnnot) Source # | |
| Ord srcAnnot => Ord (Field srcAnnot) Source # | |
| Show srcAnnot => Show (Field srcAnnot) Source # | |
| Generic (Field srcAnnot) Source # | |
| HasDocstring (Field a) Source # | |
| HasAnnotations (Field a) Source # | |
| HasName (Field a) Source # | |
| type Rep (Field srcAnnot) Source # | |
requiredness :: Lens (Field a) (Maybe FieldRequiredness) Source #
defaultValue :: Lens (Field a) (Maybe (ConstValue a)) Source #
data EnumDef srcAnnot Source #
A named value inside an enum.
Constructors
| EnumDef | |
Fields
| |
Instances
| Functor EnumDef Source # | |
| HasSrcAnnot EnumDef Source # | |
| Eq srcAnnot => Eq (EnumDef srcAnnot) Source # | |
| Data srcAnnot => Data (EnumDef srcAnnot) Source # | |
| Ord srcAnnot => Ord (EnumDef srcAnnot) Source # | |
| Show srcAnnot => Show (EnumDef srcAnnot) Source # | |
| Generic (EnumDef srcAnnot) Source # | |
| HasDocstring (EnumDef a) Source # | |
| HasAnnotations (EnumDef a) Source # | |
| HasName (EnumDef a) Source # | |
| HasValues (Enum a) [EnumDef a] Source # | |
| HasValue (EnumDef a) (Maybe Integer) Source # | |
| type Rep (EnumDef srcAnnot) Source # | |
data ConstValue srcAnnot Source #
A constant literal value in the IDL. Only a few basic types, lists, and maps can be presented in Thrift files as literals.
Constants are used for IDL-level constants and default values for fields.
Constructors
| ConstInt Integer srcAnnot | An integer. |
| ConstFloat Double srcAnnot | A float. |
| ConstLiteral Text srcAnnot | A literal string. |
| ConstIdentifier Text srcAnnot | A reference to another constant. |
| ConstList [ConstValue srcAnnot] srcAnnot | A literal list containing other constant values. |
| ConstMap [(ConstValue srcAnnot, ConstValue srcAnnot)] srcAnnot | A literal list containing other constant values.
|
Instances
| Functor ConstValue Source # | |
| HasSrcAnnot ConstValue Source # | |
| Eq srcAnnot => Eq (ConstValue srcAnnot) Source # | |
| Data srcAnnot => Data (ConstValue srcAnnot) Source # | |
| Ord srcAnnot => Ord (ConstValue srcAnnot) Source # | |
| Show srcAnnot => Show (ConstValue srcAnnot) Source # | |
| Generic (ConstValue srcAnnot) Source # | |
| HasValue (Const a) (ConstValue a) Source # | |
| type Rep (ConstValue srcAnnot) Source # | |
data TypeReference srcAnnot Source #
A reference to a type.
Constructors
| DefinedType Text srcAnnot | A custom defined type referred to by name. |
| StringType [TypeAnnotation] srcAnnot |
|
| BinaryType [TypeAnnotation] srcAnnot |
|
| SListType [TypeAnnotation] srcAnnot |
|
| BoolType [TypeAnnotation] srcAnnot |
|
| ByteType [TypeAnnotation] srcAnnot |
|
| I16Type [TypeAnnotation] srcAnnot |
|
| I32Type [TypeAnnotation] srcAnnot |
|
| I64Type [TypeAnnotation] srcAnnot |
|
| DoubleType [TypeAnnotation] srcAnnot |
|
| MapType (TypeReference srcAnnot) (TypeReference srcAnnot) [TypeAnnotation] srcAnnot |
|
| SetType (TypeReference srcAnnot) [TypeAnnotation] srcAnnot |
|
| ListType (TypeReference srcAnnot) [TypeAnnotation] srcAnnot |
|
Instances
| Functor TypeReference Source # | |
| HasSrcAnnot TypeReference Source # | |
| Eq srcAnnot => Eq (TypeReference srcAnnot) Source # | |
| Data srcAnnot => Data (TypeReference srcAnnot) Source # | |
| Ord srcAnnot => Ord (TypeReference srcAnnot) Source # | |
| Show srcAnnot => Show (TypeReference srcAnnot) Source # | |
| Generic (TypeReference srcAnnot) Source # | |
| type Rep (TypeReference srcAnnot) Source # | |
data Function srcAnnot Source #
A function defined inside a service.
Constructors
| Function | |
Fields
| |
Instances
| Functor Function Source # | |
| HasSrcAnnot Function Source # | |
| Eq srcAnnot => Eq (Function srcAnnot) Source # | |
| Data srcAnnot => Data (Function srcAnnot) Source # | |
| Ord srcAnnot => Ord (Function srcAnnot) Source # | |
| Show srcAnnot => Show (Function srcAnnot) Source # | |
| Generic (Function srcAnnot) Source # | |
| HasDocstring (Function a) Source # | |
| HasAnnotations (Function a) Source # | |
| HasName (Function a) Source # | |
| type Rep (Function srcAnnot) Source # | |
returnType :: Lens (Function a) (Maybe (TypeReference a)) Source #
parameters :: Lens (Function a) [Field a] Source #
data TypeAnnotation Source #
Type annoations may be added in various places in the form,
(foo = "bar", baz, qux = "quux")
These do not usually affect code generation but allow for custom logic if writing your own code generator.
Constructors
| TypeAnnotation | |
Fields
| |
type Docstring = Maybe Text Source #
Docstrings are Javadoc-style comments attached various defined objects.
/** * Fetches an item. */ Item getItem()
Typeclasses
class HasAnnotations t where Source #
Minimal complete definition
Methods
annotations :: Lens t [TypeAnnotation] Source #
Instances
| HasAnnotations (Senum a) Source # | |
| HasAnnotations (Struct a) Source # | |
| HasAnnotations (Enum a) Source # | |
| HasAnnotations (EnumDef a) Source # | |
| HasAnnotations (Typedef a) Source # | |
| HasAnnotations (Service a) Source # | |
| HasAnnotations (Function a) Source # | |
| HasAnnotations (Field a) Source # | |
class HasDocstring t where Source #
Minimal complete definition
Instances
| HasDocstring (Senum a) Source # | |
| HasDocstring (Struct a) Source # | |
| HasDocstring (Enum a) Source # | |
| HasDocstring (EnumDef a) Source # | |
| HasDocstring (Typedef a) Source # | |
| HasDocstring (Const a) Source # | |
| HasDocstring (Service a) Source # | |
| HasDocstring (Function a) Source # | |
| HasDocstring (Field a) Source # | |
class HasName t where Source #
Minimal complete definition
Instances
| HasName TypeAnnotation Source # | |
| HasName (Namespace a) Source # | |
| HasName (Definition a) Source # | |
| HasName (Type a) Source # | |
| HasName (Senum a) Source # | |
| HasName (Struct a) Source # | |
| HasName (Enum a) Source # | |
| HasName (EnumDef a) Source # | |
| HasName (Typedef a) Source # | |
| HasName (Const a) Source # | |
| HasName (Service a) Source # | |
| HasName (Function a) Source # | |
| HasName (Field a) Source # | |
class HasSrcAnnot t where Source #
Minimal complete definition
Instances
class HasValueType t where Source #
Minimal complete definition
Methods
valueType :: Lens (t a) (TypeReference a) Source #
Instances