language-thrift-0.9.0.0: Parser and pretty printer for the Thrift IDL format.

Copyright(c) Abhinav Gupta 2016
LicenseBSD3
MaintainerAbhinav Gupta <mail@abhinavg.net>
Stabilityexperimental
Safe HaskellSafe
LanguageHaskell2010

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.

Synopsis

AST

data Program srcAnnot Source

A program represents a single Thrift document.

Constructors

Program 

Fields

programHeaders :: [Header srcAnnot]

Headers in a document define includes and namespaces.

programDefinitions :: [Definition srcAnnot]

Types and services defined in the document.

Instances

Functor Program Source 
Eq srcAnnot => Eq (Program srcAnnot) Source 
Data srcAnnot => Data (Program srcAnnot) Source 
Ord srcAnnot => Ord (Program srcAnnot) Source 
Show srcAnnot => Show (Program srcAnnot) Source 
Generic (Program srcAnnot) Source 
type Rep (Program srcAnnot) Source 

headers :: Lens (Program a) [Header a] Source

data Header srcAnnot Source

Headers for a program.

Constructors

HeaderInclude (Include srcAnnot)

Request to include another Thrift file.

HeaderNamespace (Namespace srcAnnot)

A namespace specifier.

Instances

Functor Header Source 
Eq srcAnnot => Eq (Header srcAnnot) Source 
Data srcAnnot => Data (Header srcAnnot) Source 
Ord srcAnnot => Ord (Header srcAnnot) Source 
Show srcAnnot => Show (Header srcAnnot) Source 
Generic (Header srcAnnot) Source 
type Rep (Header srcAnnot) Source 

data Include srcAnnot Source

The IDL includes another Thrift file.

include "common.thrift"

typedef common.Foo Bar

Constructors

Include 

Fields

includePath :: Text

Path to the included file.

includeSrcAnnot :: srcAnnot
 

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 

path :: Lens (Include a) Text 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

namespaceLanguage :: Text

The language for which the namespace is being specified. This may be * to refer to all languages.

namespaceName :: Text

Namespace or package path to use in the generated code for that language.

namespaceSrcAnnot :: srcAnnot
 

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 

data Const srcAnnot Source

A declared constant.

const i32 code = 1;

Constructors

Const 

Fields

constValueType :: TypeReference srcAnnot

Type of the constant.

constName :: Text

Name of the constant.

constValue :: ConstValue srcAnnot

Value of the constant.

constDocstring :: Docstring

Documentation.

constSrcAnnot :: srcAnnot
 

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

serviceName :: Text

Name of the service.

serviceExtends :: Maybe Text

Name of the service this service extends.

serviceFunctions :: [Function srcAnnot]

All the functions defined for the service.

serviceAnnotations :: [TypeAnnotation]

Annotations added to the service.

serviceDocstring :: Docstring

Documentation.

serviceSrcAnnot :: srcAnnot
 

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 

data Type srcAnnot Source

Defines the various types that can be declared in Thrift.

Constructors

TypedefType (Typedef srcAnnot)
typedef
EnumType (Enum srcAnnot)
enum
StructType (Struct srcAnnot)
struct
UnionType (Union srcAnnot)
union
ExceptionType (Exception srcAnnot)
exception
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

typedefTargetType :: TypeReference srcAnnot

The aliased type.

typedefName :: Text

Name of the new type.

typedefAnnotations :: [TypeAnnotation]

Annotations added to the typedef.

typedefDocstring :: Docstring

Documentation.

typedefSrcAnnot :: srcAnnot
 

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 

data Enum srcAnnot Source

Enums are sets of named integer values.

enum Role {
    User = 1, Admin = 2
}

Constructors

Enum 

Fields

enumName :: Text

Name of the enum type.

enumValues :: [EnumDef srcAnnot]

Values defined in the enum.

enumAnnotations :: [TypeAnnotation]

Annotations added to the enum.

enumDocstring :: Docstring

Documentation.

enumSrcAnnot :: srcAnnot
 

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 Struct srcAnnot Source

A struct definition

struct User {
    1: Role role = Role.User;
}

Constructors

Struct 

Fields

structName :: Text

Name of the struct.

structFields :: [Field srcAnnot]

Fields defined in the struct.

structAnnotations :: [TypeAnnotation]

Annotations added to the struct.

structDocstring :: Docstring

Documentation.

structSrcAnnot :: srcAnnot
 

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 

data Union srcAnnot Source

A union of other types.

union Value {
    1: string stringValue;
    2: i32 intValue;
}

Constructors

Union 

Fields

unionName :: Text

Name of the union.

unionFields :: [Field srcAnnot]

Fields defined in the union.

unionAnnotations :: [TypeAnnotation]

Annotations added to the union.

unionDocstring :: Docstring

Documentation.

unionSrcAnnot :: srcAnnot
 

Instances

Functor Union Source 
HasFields Union Source 
HasSrcAnnot Union Source 
Eq srcAnnot => Eq (Union srcAnnot) Source 
Data srcAnnot => Data (Union srcAnnot) Source 
Ord srcAnnot => Ord (Union srcAnnot) Source 
Show srcAnnot => Show (Union srcAnnot) Source 
Generic (Union srcAnnot) Source 
HasDocstring (Union a) Source 
HasAnnotations (Union a) Source 
HasName (Union a) Source 
type Rep (Union srcAnnot) Source 

data Exception srcAnnot Source

Exception types.

exception UserDoesNotExist {
    1: optional string message
    2: required string username
}

Constructors

Exception 

Fields

exceptionName :: Text

Name of the exception.

exceptionFields :: [Field srcAnnot]

Fields defined in the exception.

exceptionAnnotations :: [TypeAnnotation]

Annotations added to the exception.

exceptionDocstring :: Docstring

Documentation.

exceptionSrcAnnot :: srcAnnot
 

Instances

data Senum srcAnnot Source

An string-only enum. These are a deprecated feature of Thrift and shouldn't be used.

Constructors

Senum 

Fields

senumName :: Text
 
senumValues :: [Text]
 
senumAnnotations :: [TypeAnnotation]

Annotations added to the senum.

senumDocstring :: Docstring

Documentation.

senumSrcAnnot :: srcAnnot
 

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.

Constructors

Required

The field is required.

Optional

The field is optional.

data Field srcAnnot Source

A field inside a struct, exception, or function parameters list.

Constructors

Field 

Fields

fieldIdentifier :: Maybe Integer

Position of the field.

While this is optional, it is recommended that Thrift files always contain specific field IDs.

fieldRequiredness :: Maybe FieldRequiredness

Whether this field is required or not.

Behavior may differ between languages if requiredness is not specified. Therefore it's recommended that requiredness for a field is always specified.

fieldValueType :: TypeReference srcAnnot

Type of value the field holds.

fieldName :: Text

Name of the field.

fieldDefaultValue :: Maybe (ConstValue srcAnnot)

Default value of the field, if any.

fieldAnnotations :: [TypeAnnotation]

Field annotations.

fieldDocstring :: Docstring

Documentation.

fieldSrcAnnot :: srcAnnot
 

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 

data EnumDef srcAnnot Source

A named value inside an enum.

Constructors

EnumDef 

Fields

enumDefName :: Text

Name of the value.

enumDefValue :: Maybe Integer

Value attached to the enum for that name.

enumDefAnnotations :: [TypeAnnotation]

Annotations added to this enum field.

enumDefDocstring :: Docstring

Documentation

enumDefSrcAnnot :: srcAnnot
 

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

ConstFloat Double srcAnnot

A float. 4.2

ConstLiteral Text srcAnnot

A literal string. "hello"

ConstIdentifier Text srcAnnot

A reference to another constant. Foo.bar

ConstList [ConstValue srcAnnot] srcAnnot

A literal list containing other constant values. [42]

ConstMap [(ConstValue srcAnnot, ConstValue srcAnnot)] srcAnnot

A literal list containing other constant values. {"hellO": 1, "world": 2}

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

string and annotations.

BinaryType [TypeAnnotation] srcAnnot

binary and annotations.

SListType [TypeAnnotation] srcAnnot

slist and annotations.

BoolType [TypeAnnotation] srcAnnot

bool and annotations.

ByteType [TypeAnnotation] srcAnnot

byte and annotations.

I16Type [TypeAnnotation] srcAnnot

i16 and annotations.

I32Type [TypeAnnotation] srcAnnot

i32 and annotations.

I64Type [TypeAnnotation] srcAnnot

i64 and annotations.

DoubleType [TypeAnnotation] srcAnnot

double and annotations.

MapType (TypeReference srcAnnot) (TypeReference srcAnnot) [TypeAnnotation] srcAnnot

map<foo, bar> and annotations.

SetType (TypeReference srcAnnot) [TypeAnnotation] srcAnnot

set<baz> and annotations.

ListType (TypeReference srcAnnot) [TypeAnnotation] srcAnnot

list<qux> and annotations.

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

functionOneWay :: Bool

Whether the function is oneway. If it's one way, it cannot receive repsonses.

functionReturnType :: Maybe (TypeReference srcAnnot)

Return type of the function, or Nothing if it's void or oneway.

functionName :: Text

Name of the function.

functionParameters :: [Field srcAnnot]

Parameters accepted by the function.

functionExceptions :: Maybe [Field srcAnnot]

Exceptions raised by the function, if any.

functionAnnotations :: [TypeAnnotation]

Annotations added to the function.

functionDocstring :: Docstring

Documentation.

functionSrcAnnot :: srcAnnot
 

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 

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

typeAnnotationName :: Text

Name of the annotation.

typeAnnotationValue :: Maybe Text

Value for the annotation.

type Docstring = Maybe Text Source

Docstrings are Javadoc-style comments attached various defined objects.

/**
 * Fetches an item.
 */
Item getItem()

Typeclasses

class HasValue s a | s -> a where Source

Methods

value :: Lens s a Source

class HasValues s a | s -> a where Source

Methods

values :: Lens s a Source