language-thrift-0.8.0.1: 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.Types

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

Instances

Functor Program Source # 

Methods

fmap :: (a -> b) -> Program a -> Program b #

(<$) :: a -> Program b -> Program a #

Eq srcAnnot => Eq (Program srcAnnot) Source # 

Methods

(==) :: Program srcAnnot -> Program srcAnnot -> Bool #

(/=) :: Program srcAnnot -> Program srcAnnot -> Bool #

Data srcAnnot => Data (Program srcAnnot) Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Program srcAnnot -> c (Program srcAnnot) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Program srcAnnot) #

toConstr :: Program srcAnnot -> Constr #

dataTypeOf :: Program srcAnnot -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c (Program srcAnnot)) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Program srcAnnot)) #

gmapT :: (forall b. Data b => b -> b) -> Program srcAnnot -> Program srcAnnot #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Program srcAnnot -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Program srcAnnot -> r #

gmapQ :: (forall d. Data d => d -> u) -> Program srcAnnot -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Program srcAnnot -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Program srcAnnot -> m (Program srcAnnot) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Program srcAnnot -> m (Program srcAnnot) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Program srcAnnot -> m (Program srcAnnot) #

Ord srcAnnot => Ord (Program srcAnnot) Source # 

Methods

compare :: Program srcAnnot -> Program srcAnnot -> Ordering #

(<) :: Program srcAnnot -> Program srcAnnot -> Bool #

(<=) :: Program srcAnnot -> Program srcAnnot -> Bool #

(>) :: Program srcAnnot -> Program srcAnnot -> Bool #

(>=) :: Program srcAnnot -> Program srcAnnot -> Bool #

max :: Program srcAnnot -> Program srcAnnot -> Program srcAnnot #

min :: Program srcAnnot -> Program srcAnnot -> Program srcAnnot #

Show srcAnnot => Show (Program srcAnnot) Source # 

Methods

showsPrec :: Int -> Program srcAnnot -> ShowS #

show :: Program srcAnnot -> String #

showList :: [Program srcAnnot] -> ShowS #

Generic (Program srcAnnot) Source # 

Associated Types

type Rep (Program srcAnnot) :: * -> * #

Methods

from :: Program srcAnnot -> Rep (Program srcAnnot) x #

to :: Rep (Program srcAnnot) x -> Program srcAnnot #

type Rep (Program srcAnnot) Source # 
type Rep (Program srcAnnot) = D1 (MetaData "Program" "Language.Thrift.Internal.Types" "language-thrift-0.8.0.1-74ptPlTr1sU1XwSnsHlCew" False) (C1 (MetaCons "Program" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "programHeaders") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Header srcAnnot])) (S1 (MetaSel (Just Symbol "programDefinitions") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Definition srcAnnot]))))

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 # 

Methods

fmap :: (a -> b) -> Header a -> Header b #

(<$) :: a -> Header b -> Header a #

Eq srcAnnot => Eq (Header srcAnnot) Source # 

Methods

(==) :: Header srcAnnot -> Header srcAnnot -> Bool #

(/=) :: Header srcAnnot -> Header srcAnnot -> Bool #

Data srcAnnot => Data (Header srcAnnot) Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Header srcAnnot -> c (Header srcAnnot) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Header srcAnnot) #

toConstr :: Header srcAnnot -> Constr #

dataTypeOf :: Header srcAnnot -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c (Header srcAnnot)) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Header srcAnnot)) #

gmapT :: (forall b. Data b => b -> b) -> Header srcAnnot -> Header srcAnnot #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Header srcAnnot -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Header srcAnnot -> r #

gmapQ :: (forall d. Data d => d -> u) -> Header srcAnnot -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Header srcAnnot -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Header srcAnnot -> m (Header srcAnnot) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Header srcAnnot -> m (Header srcAnnot) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Header srcAnnot -> m (Header srcAnnot) #

Ord srcAnnot => Ord (Header srcAnnot) Source # 

Methods

compare :: Header srcAnnot -> Header srcAnnot -> Ordering #

(<) :: Header srcAnnot -> Header srcAnnot -> Bool #

(<=) :: Header srcAnnot -> Header srcAnnot -> Bool #

(>) :: Header srcAnnot -> Header srcAnnot -> Bool #

(>=) :: Header srcAnnot -> Header srcAnnot -> Bool #

max :: Header srcAnnot -> Header srcAnnot -> Header srcAnnot #

min :: Header srcAnnot -> Header srcAnnot -> Header srcAnnot #

Show srcAnnot => Show (Header srcAnnot) Source # 

Methods

showsPrec :: Int -> Header srcAnnot -> ShowS #

show :: Header srcAnnot -> String #

showList :: [Header srcAnnot] -> ShowS #

Generic (Header srcAnnot) Source # 

Associated Types

type Rep (Header srcAnnot) :: * -> * #

Methods

from :: Header srcAnnot -> Rep (Header srcAnnot) x #

to :: Rep (Header srcAnnot) x -> Header srcAnnot #

type Rep (Header srcAnnot) Source # 
type Rep (Header srcAnnot) = D1 (MetaData "Header" "Language.Thrift.Internal.Types" "language-thrift-0.8.0.1-74ptPlTr1sU1XwSnsHlCew" False) ((:+:) (C1 (MetaCons "HeaderInclude" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Include srcAnnot)))) (C1 (MetaCons "HeaderNamespace" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Namespace srcAnnot)))))

data Include srcAnnot Source #

The IDL includes another Thrift file.

include "common.thrift"

typedef common.Foo Bar

Constructors

Include 

Fields

Instances

Functor Include Source # 

Methods

fmap :: (a -> b) -> Include a -> Include b #

(<$) :: a -> Include b -> Include a #

HasSrcAnnot Include Source # 

Methods

srcAnnot :: Functor f => (a -> f a) -> Include a -> f (Include a) Source #

Eq srcAnnot => Eq (Include srcAnnot) Source # 

Methods

(==) :: Include srcAnnot -> Include srcAnnot -> Bool #

(/=) :: Include srcAnnot -> Include srcAnnot -> Bool #

Data srcAnnot => Data (Include srcAnnot) Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Include srcAnnot -> c (Include srcAnnot) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Include srcAnnot) #

toConstr :: Include srcAnnot -> Constr #

dataTypeOf :: Include srcAnnot -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c (Include srcAnnot)) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Include srcAnnot)) #

gmapT :: (forall b. Data b => b -> b) -> Include srcAnnot -> Include srcAnnot #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Include srcAnnot -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Include srcAnnot -> r #

gmapQ :: (forall d. Data d => d -> u) -> Include srcAnnot -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Include srcAnnot -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Include srcAnnot -> m (Include srcAnnot) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Include srcAnnot -> m (Include srcAnnot) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Include srcAnnot -> m (Include srcAnnot) #

Ord srcAnnot => Ord (Include srcAnnot) Source # 

Methods

compare :: Include srcAnnot -> Include srcAnnot -> Ordering #

(<) :: Include srcAnnot -> Include srcAnnot -> Bool #

(<=) :: Include srcAnnot -> Include srcAnnot -> Bool #

(>) :: Include srcAnnot -> Include srcAnnot -> Bool #

(>=) :: Include srcAnnot -> Include srcAnnot -> Bool #

max :: Include srcAnnot -> Include srcAnnot -> Include srcAnnot #

min :: Include srcAnnot -> Include srcAnnot -> Include srcAnnot #

Show srcAnnot => Show (Include srcAnnot) Source # 

Methods

showsPrec :: Int -> Include srcAnnot -> ShowS #

show :: Include srcAnnot -> String #

showList :: [Include srcAnnot] -> ShowS #

Generic (Include srcAnnot) Source # 

Associated Types

type Rep (Include srcAnnot) :: * -> * #

Methods

from :: Include srcAnnot -> Rep (Include srcAnnot) x #

to :: Rep (Include srcAnnot) x -> Include srcAnnot #

type Rep (Include srcAnnot) Source # 
type Rep (Include srcAnnot) = D1 (MetaData "Include" "Language.Thrift.Internal.Types" "language-thrift-0.8.0.1-74ptPlTr1sU1XwSnsHlCew" False) (C1 (MetaCons "Include" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "includePath") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Text)) (S1 (MetaSel (Just Symbol "includeSrcAnnot") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 srcAnnot))))

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

Instances

Functor Namespace Source # 

Methods

fmap :: (a -> b) -> Namespace a -> Namespace b #

(<$) :: a -> Namespace b -> Namespace a #

HasSrcAnnot Namespace Source # 

Methods

srcAnnot :: Functor f => (a -> f a) -> Namespace a -> f (Namespace a) Source #

Eq srcAnnot => Eq (Namespace srcAnnot) Source # 

Methods

(==) :: Namespace srcAnnot -> Namespace srcAnnot -> Bool #

(/=) :: Namespace srcAnnot -> Namespace srcAnnot -> Bool #

Data srcAnnot => Data (Namespace srcAnnot) Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Namespace srcAnnot -> c (Namespace srcAnnot) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Namespace srcAnnot) #

toConstr :: Namespace srcAnnot -> Constr #

dataTypeOf :: Namespace srcAnnot -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c (Namespace srcAnnot)) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Namespace srcAnnot)) #

gmapT :: (forall b. Data b => b -> b) -> Namespace srcAnnot -> Namespace srcAnnot #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Namespace srcAnnot -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Namespace srcAnnot -> r #

gmapQ :: (forall d. Data d => d -> u) -> Namespace srcAnnot -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Namespace srcAnnot -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Namespace srcAnnot -> m (Namespace srcAnnot) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Namespace srcAnnot -> m (Namespace srcAnnot) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Namespace srcAnnot -> m (Namespace srcAnnot) #

Ord srcAnnot => Ord (Namespace srcAnnot) Source # 

Methods

compare :: Namespace srcAnnot -> Namespace srcAnnot -> Ordering #

(<) :: Namespace srcAnnot -> Namespace srcAnnot -> Bool #

(<=) :: Namespace srcAnnot -> Namespace srcAnnot -> Bool #

(>) :: Namespace srcAnnot -> Namespace srcAnnot -> Bool #

(>=) :: Namespace srcAnnot -> Namespace srcAnnot -> Bool #

max :: Namespace srcAnnot -> Namespace srcAnnot -> Namespace srcAnnot #

min :: Namespace srcAnnot -> Namespace srcAnnot -> Namespace srcAnnot #

Show srcAnnot => Show (Namespace srcAnnot) Source # 

Methods

showsPrec :: Int -> Namespace srcAnnot -> ShowS #

show :: Namespace srcAnnot -> String #

showList :: [Namespace srcAnnot] -> ShowS #

Generic (Namespace srcAnnot) Source # 

Associated Types

type Rep (Namespace srcAnnot) :: * -> * #

Methods

from :: Namespace srcAnnot -> Rep (Namespace srcAnnot) x #

to :: Rep (Namespace srcAnnot) x -> Namespace srcAnnot #

HasName (Namespace a) Source # 

Methods

name :: Lens (Namespace a) Text Source #

type Rep (Namespace srcAnnot) Source # 
type Rep (Namespace srcAnnot) = D1 (MetaData "Namespace" "Language.Thrift.Internal.Types" "language-thrift-0.8.0.1-74ptPlTr1sU1XwSnsHlCew" False) (C1 (MetaCons "Namespace" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "namespaceLanguage") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Text)) ((:*:) (S1 (MetaSel (Just Symbol "namespaceName") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Text)) (S1 (MetaSel (Just Symbol "namespaceSrcAnnot") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 srcAnnot)))))

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 # 

Methods

fmap :: (a -> b) -> Definition a -> Definition b #

(<$) :: a -> Definition b -> Definition a #

HasSrcAnnot Definition Source # 

Methods

srcAnnot :: Functor f => (a -> f a) -> Definition a -> f (Definition a) Source #

Eq srcAnnot => Eq (Definition srcAnnot) Source # 

Methods

(==) :: Definition srcAnnot -> Definition srcAnnot -> Bool #

(/=) :: Definition srcAnnot -> Definition srcAnnot -> Bool #

Data srcAnnot => Data (Definition srcAnnot) Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Definition srcAnnot -> c (Definition srcAnnot) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Definition srcAnnot) #

toConstr :: Definition srcAnnot -> Constr #

dataTypeOf :: Definition srcAnnot -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c (Definition srcAnnot)) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Definition srcAnnot)) #

gmapT :: (forall b. Data b => b -> b) -> Definition srcAnnot -> Definition srcAnnot #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Definition srcAnnot -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Definition srcAnnot -> r #

gmapQ :: (forall d. Data d => d -> u) -> Definition srcAnnot -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Definition srcAnnot -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Definition srcAnnot -> m (Definition srcAnnot) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Definition srcAnnot -> m (Definition srcAnnot) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Definition srcAnnot -> m (Definition srcAnnot) #

Ord srcAnnot => Ord (Definition srcAnnot) Source # 

Methods

compare :: Definition srcAnnot -> Definition srcAnnot -> Ordering #

(<) :: Definition srcAnnot -> Definition srcAnnot -> Bool #

(<=) :: Definition srcAnnot -> Definition srcAnnot -> Bool #

(>) :: Definition srcAnnot -> Definition srcAnnot -> Bool #

(>=) :: Definition srcAnnot -> Definition srcAnnot -> Bool #

max :: Definition srcAnnot -> Definition srcAnnot -> Definition srcAnnot #

min :: Definition srcAnnot -> Definition srcAnnot -> Definition srcAnnot #

Show srcAnnot => Show (Definition srcAnnot) Source # 

Methods

showsPrec :: Int -> Definition srcAnnot -> ShowS #

show :: Definition srcAnnot -> String #

showList :: [Definition srcAnnot] -> ShowS #

Generic (Definition srcAnnot) Source # 

Associated Types

type Rep (Definition srcAnnot) :: * -> * #

Methods

from :: Definition srcAnnot -> Rep (Definition srcAnnot) x #

to :: Rep (Definition srcAnnot) x -> Definition srcAnnot #

HasName (Definition a) Source # 

Methods

name :: Lens (Definition a) Text Source #

type Rep (Definition srcAnnot) Source # 
type Rep (Definition srcAnnot) = D1 (MetaData "Definition" "Language.Thrift.Internal.Types" "language-thrift-0.8.0.1-74ptPlTr1sU1XwSnsHlCew" False) ((:+:) (C1 (MetaCons "ConstDefinition" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Const srcAnnot)))) ((:+:) (C1 (MetaCons "TypeDefinition" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Type srcAnnot)))) (C1 (MetaCons "ServiceDefinition" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Service srcAnnot))))))

data Const srcAnnot Source #

A declared constant.

const i32 code = 1;

Constructors

Const 

Fields

Instances

Functor Const Source # 

Methods

fmap :: (a -> b) -> Const a -> Const b #

(<$) :: a -> Const b -> Const a #

HasValueType Const Source # 

Methods

valueType :: Functor f => (TypeReference a -> f (TypeReference a)) -> Const a -> f (Const a) Source #

HasSrcAnnot Const Source # 

Methods

srcAnnot :: Functor f => (a -> f a) -> Const a -> f (Const a) Source #

Eq srcAnnot => Eq (Const srcAnnot) Source # 

Methods

(==) :: Const srcAnnot -> Const srcAnnot -> Bool #

(/=) :: Const srcAnnot -> Const srcAnnot -> Bool #

Data srcAnnot => Data (Const srcAnnot) Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Const srcAnnot -> c (Const srcAnnot) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Const srcAnnot) #

toConstr :: Const srcAnnot -> Constr #

dataTypeOf :: Const srcAnnot -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c (Const srcAnnot)) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Const srcAnnot)) #

gmapT :: (forall b. Data b => b -> b) -> Const srcAnnot -> Const srcAnnot #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Const srcAnnot -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Const srcAnnot -> r #

gmapQ :: (forall d. Data d => d -> u) -> Const srcAnnot -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Const srcAnnot -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Const srcAnnot -> m (Const srcAnnot) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Const srcAnnot -> m (Const srcAnnot) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Const srcAnnot -> m (Const srcAnnot) #

Ord srcAnnot => Ord (Const srcAnnot) Source # 

Methods

compare :: Const srcAnnot -> Const srcAnnot -> Ordering #

(<) :: Const srcAnnot -> Const srcAnnot -> Bool #

(<=) :: Const srcAnnot -> Const srcAnnot -> Bool #

(>) :: Const srcAnnot -> Const srcAnnot -> Bool #

(>=) :: Const srcAnnot -> Const srcAnnot -> Bool #

max :: Const srcAnnot -> Const srcAnnot -> Const srcAnnot #

min :: Const srcAnnot -> Const srcAnnot -> Const srcAnnot #

Show srcAnnot => Show (Const srcAnnot) Source # 

Methods

showsPrec :: Int -> Const srcAnnot -> ShowS #

show :: Const srcAnnot -> String #

showList :: [Const srcAnnot] -> ShowS #

Generic (Const srcAnnot) Source # 

Associated Types

type Rep (Const srcAnnot) :: * -> * #

Methods

from :: Const srcAnnot -> Rep (Const srcAnnot) x #

to :: Rep (Const srcAnnot) x -> Const srcAnnot #

HasDocstring (Const a) Source # 

Methods

docstring :: Lens (Const a) Docstring Source #

HasName (Const a) Source # 

Methods

name :: Lens (Const a) Text Source #

HasValue (Const a) (ConstValue a) Source # 

Methods

value :: Lens (Const a) (ConstValue a) Source #

type Rep (Const srcAnnot) Source # 
type Rep (Const srcAnnot) = D1 (MetaData "Const" "Language.Thrift.Internal.Types" "language-thrift-0.8.0.1-74ptPlTr1sU1XwSnsHlCew" False) (C1 (MetaCons "Const" PrefixI True) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "constValueType") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (TypeReference srcAnnot))) (S1 (MetaSel (Just Symbol "constName") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Text))) ((:*:) (S1 (MetaSel (Just Symbol "constValue") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (ConstValue srcAnnot))) ((:*:) (S1 (MetaSel (Just Symbol "constDocstring") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Docstring)) (S1 (MetaSel (Just Symbol "constSrcAnnot") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 srcAnnot))))))

data Service srcAnnot Source #

A service definition.

service MyService {
    // ...
}

Constructors

Service 

Fields

Instances

Functor Service Source # 

Methods

fmap :: (a -> b) -> Service a -> Service b #

(<$) :: a -> Service b -> Service a #

HasSrcAnnot Service Source # 

Methods

srcAnnot :: Functor f => (a -> f a) -> Service a -> f (Service a) Source #

Eq srcAnnot => Eq (Service srcAnnot) Source # 

Methods

(==) :: Service srcAnnot -> Service srcAnnot -> Bool #

(/=) :: Service srcAnnot -> Service srcAnnot -> Bool #

Data srcAnnot => Data (Service srcAnnot) Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Service srcAnnot -> c (Service srcAnnot) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Service srcAnnot) #

toConstr :: Service srcAnnot -> Constr #

dataTypeOf :: Service srcAnnot -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c (Service srcAnnot)) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Service srcAnnot)) #

gmapT :: (forall b. Data b => b -> b) -> Service srcAnnot -> Service srcAnnot #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Service srcAnnot -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Service srcAnnot -> r #

gmapQ :: (forall d. Data d => d -> u) -> Service srcAnnot -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Service srcAnnot -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Service srcAnnot -> m (Service srcAnnot) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Service srcAnnot -> m (Service srcAnnot) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Service srcAnnot -> m (Service srcAnnot) #

Ord srcAnnot => Ord (Service srcAnnot) Source # 

Methods

compare :: Service srcAnnot -> Service srcAnnot -> Ordering #

(<) :: Service srcAnnot -> Service srcAnnot -> Bool #

(<=) :: Service srcAnnot -> Service srcAnnot -> Bool #

(>) :: Service srcAnnot -> Service srcAnnot -> Bool #

(>=) :: Service srcAnnot -> Service srcAnnot -> Bool #

max :: Service srcAnnot -> Service srcAnnot -> Service srcAnnot #

min :: Service srcAnnot -> Service srcAnnot -> Service srcAnnot #

Show srcAnnot => Show (Service srcAnnot) Source # 

Methods

showsPrec :: Int -> Service srcAnnot -> ShowS #

show :: Service srcAnnot -> String #

showList :: [Service srcAnnot] -> ShowS #

Generic (Service srcAnnot) Source # 

Associated Types

type Rep (Service srcAnnot) :: * -> * #

Methods

from :: Service srcAnnot -> Rep (Service srcAnnot) x #

to :: Rep (Service srcAnnot) x -> Service srcAnnot #

HasDocstring (Service a) Source # 

Methods

docstring :: Lens (Service a) Docstring Source #

HasAnnotations (Service a) Source # 
HasName (Service a) Source # 

Methods

name :: Lens (Service a) Text Source #

type Rep (Service srcAnnot) Source # 
type Rep (Service srcAnnot) = D1 (MetaData "Service" "Language.Thrift.Internal.Types" "language-thrift-0.8.0.1-74ptPlTr1sU1XwSnsHlCew" False) (C1 (MetaCons "Service" PrefixI True) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "serviceName") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Text)) ((:*:) (S1 (MetaSel (Just Symbol "serviceExtends") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "serviceFunctions") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Function srcAnnot])))) ((:*:) (S1 (MetaSel (Just Symbol "serviceAnnotations") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [TypeAnnotation])) ((:*:) (S1 (MetaSel (Just Symbol "serviceDocstring") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Docstring)) (S1 (MetaSel (Just Symbol "serviceSrcAnnot") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 srcAnnot))))))

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 # 

Methods

fmap :: (a -> b) -> Type a -> Type b #

(<$) :: a -> Type b -> Type a #

HasSrcAnnot Type Source # 

Methods

srcAnnot :: Functor f => (a -> f a) -> Type a -> f (Type a) Source #

Eq srcAnnot => Eq (Type srcAnnot) Source # 

Methods

(==) :: Type srcAnnot -> Type srcAnnot -> Bool #

(/=) :: Type srcAnnot -> Type srcAnnot -> Bool #

Data srcAnnot => Data (Type srcAnnot) Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Type srcAnnot -> c (Type srcAnnot) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Type srcAnnot) #

toConstr :: Type srcAnnot -> Constr #

dataTypeOf :: Type srcAnnot -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c (Type srcAnnot)) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Type srcAnnot)) #

gmapT :: (forall b. Data b => b -> b) -> Type srcAnnot -> Type srcAnnot #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Type srcAnnot -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Type srcAnnot -> r #

gmapQ :: (forall d. Data d => d -> u) -> Type srcAnnot -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Type srcAnnot -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Type srcAnnot -> m (Type srcAnnot) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Type srcAnnot -> m (Type srcAnnot) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Type srcAnnot -> m (Type srcAnnot) #

Ord srcAnnot => Ord (Type srcAnnot) Source # 

Methods

compare :: Type srcAnnot -> Type srcAnnot -> Ordering #

(<) :: Type srcAnnot -> Type srcAnnot -> Bool #

(<=) :: Type srcAnnot -> Type srcAnnot -> Bool #

(>) :: Type srcAnnot -> Type srcAnnot -> Bool #

(>=) :: Type srcAnnot -> Type srcAnnot -> Bool #

max :: Type srcAnnot -> Type srcAnnot -> Type srcAnnot #

min :: Type srcAnnot -> Type srcAnnot -> Type srcAnnot #

Show srcAnnot => Show (Type srcAnnot) Source # 

Methods

showsPrec :: Int -> Type srcAnnot -> ShowS #

show :: Type srcAnnot -> String #

showList :: [Type srcAnnot] -> ShowS #

Generic (Type srcAnnot) Source # 

Associated Types

type Rep (Type srcAnnot) :: * -> * #

Methods

from :: Type srcAnnot -> Rep (Type srcAnnot) x #

to :: Rep (Type srcAnnot) x -> Type srcAnnot #

HasName (Type a) Source # 

Methods

name :: Lens (Type a) Text 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 # 

Methods

fmap :: (a -> b) -> Typedef a -> Typedef b #

(<$) :: a -> Typedef b -> Typedef a #

HasSrcAnnot Typedef Source # 

Methods

srcAnnot :: Functor f => (a -> f a) -> Typedef a -> f (Typedef a) Source #

Eq srcAnnot => Eq (Typedef srcAnnot) Source # 

Methods

(==) :: Typedef srcAnnot -> Typedef srcAnnot -> Bool #

(/=) :: Typedef srcAnnot -> Typedef srcAnnot -> Bool #

Data srcAnnot => Data (Typedef srcAnnot) Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Typedef srcAnnot -> c (Typedef srcAnnot) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Typedef srcAnnot) #

toConstr :: Typedef srcAnnot -> Constr #

dataTypeOf :: Typedef srcAnnot -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c (Typedef srcAnnot)) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Typedef srcAnnot)) #

gmapT :: (forall b. Data b => b -> b) -> Typedef srcAnnot -> Typedef srcAnnot #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Typedef srcAnnot -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Typedef srcAnnot -> r #

gmapQ :: (forall d. Data d => d -> u) -> Typedef srcAnnot -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Typedef srcAnnot -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Typedef srcAnnot -> m (Typedef srcAnnot) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Typedef srcAnnot -> m (Typedef srcAnnot) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Typedef srcAnnot -> m (Typedef srcAnnot) #

Ord srcAnnot => Ord (Typedef srcAnnot) Source # 

Methods

compare :: Typedef srcAnnot -> Typedef srcAnnot -> Ordering #

(<) :: Typedef srcAnnot -> Typedef srcAnnot -> Bool #

(<=) :: Typedef srcAnnot -> Typedef srcAnnot -> Bool #

(>) :: Typedef srcAnnot -> Typedef srcAnnot -> Bool #

(>=) :: Typedef srcAnnot -> Typedef srcAnnot -> Bool #

max :: Typedef srcAnnot -> Typedef srcAnnot -> Typedef srcAnnot #

min :: Typedef srcAnnot -> Typedef srcAnnot -> Typedef srcAnnot #

Show srcAnnot => Show (Typedef srcAnnot) Source # 

Methods

showsPrec :: Int -> Typedef srcAnnot -> ShowS #

show :: Typedef srcAnnot -> String #

showList :: [Typedef srcAnnot] -> ShowS #

Generic (Typedef srcAnnot) Source # 

Associated Types

type Rep (Typedef srcAnnot) :: * -> * #

Methods

from :: Typedef srcAnnot -> Rep (Typedef srcAnnot) x #

to :: Rep (Typedef srcAnnot) x -> Typedef srcAnnot #

HasDocstring (Typedef a) Source # 

Methods

docstring :: Lens (Typedef a) Docstring Source #

HasAnnotations (Typedef a) Source # 
HasName (Typedef a) Source # 

Methods

name :: Lens (Typedef a) Text Source #

type Rep (Typedef srcAnnot) Source # 
type Rep (Typedef srcAnnot) = D1 (MetaData "Typedef" "Language.Thrift.Internal.Types" "language-thrift-0.8.0.1-74ptPlTr1sU1XwSnsHlCew" False) (C1 (MetaCons "Typedef" PrefixI True) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "typedefTargetType") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (TypeReference srcAnnot))) (S1 (MetaSel (Just Symbol "typedefName") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Text))) ((:*:) (S1 (MetaSel (Just Symbol "typedefAnnotations") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [TypeAnnotation])) ((:*:) (S1 (MetaSel (Just Symbol "typedefDocstring") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Docstring)) (S1 (MetaSel (Just Symbol "typedefSrcAnnot") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 srcAnnot))))))

data Enum srcAnnot Source #

Enums are sets of named integer values.

enum Role {
    User = 1, Admin = 2
}

Constructors

Enum 

Fields

Instances

Functor Enum Source # 

Methods

fmap :: (a -> b) -> Enum a -> Enum b #

(<$) :: a -> Enum b -> Enum a #

HasSrcAnnot Enum Source # 

Methods

srcAnnot :: Functor f => (a -> f a) -> Enum a -> f (Enum a) Source #

Eq srcAnnot => Eq (Enum srcAnnot) Source # 

Methods

(==) :: Enum srcAnnot -> Enum srcAnnot -> Bool #

(/=) :: Enum srcAnnot -> Enum srcAnnot -> Bool #

Data srcAnnot => Data (Enum srcAnnot) Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Enum srcAnnot -> c (Enum srcAnnot) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Enum srcAnnot) #

toConstr :: Enum srcAnnot -> Constr #

dataTypeOf :: Enum srcAnnot -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c (Enum srcAnnot)) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Enum srcAnnot)) #

gmapT :: (forall b. Data b => b -> b) -> Enum srcAnnot -> Enum srcAnnot #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Enum srcAnnot -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Enum srcAnnot -> r #

gmapQ :: (forall d. Data d => d -> u) -> Enum srcAnnot -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Enum srcAnnot -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Enum srcAnnot -> m (Enum srcAnnot) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Enum srcAnnot -> m (Enum srcAnnot) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Enum srcAnnot -> m (Enum srcAnnot) #

Ord srcAnnot => Ord (Enum srcAnnot) Source # 

Methods

compare :: Enum srcAnnot -> Enum srcAnnot -> Ordering #

(<) :: Enum srcAnnot -> Enum srcAnnot -> Bool #

(<=) :: Enum srcAnnot -> Enum srcAnnot -> Bool #

(>) :: Enum srcAnnot -> Enum srcAnnot -> Bool #

(>=) :: Enum srcAnnot -> Enum srcAnnot -> Bool #

max :: Enum srcAnnot -> Enum srcAnnot -> Enum srcAnnot #

min :: Enum srcAnnot -> Enum srcAnnot -> Enum srcAnnot #

Show srcAnnot => Show (Enum srcAnnot) Source # 

Methods

showsPrec :: Int -> Enum srcAnnot -> ShowS #

show :: Enum srcAnnot -> String #

showList :: [Enum srcAnnot] -> ShowS #

Generic (Enum srcAnnot) Source # 

Associated Types

type Rep (Enum srcAnnot) :: * -> * #

Methods

from :: Enum srcAnnot -> Rep (Enum srcAnnot) x #

to :: Rep (Enum srcAnnot) x -> Enum srcAnnot #

HasDocstring (Enum a) Source # 

Methods

docstring :: Lens (Enum a) Docstring Source #

HasAnnotations (Enum a) Source # 

Methods

annotations :: Lens (Enum a) [TypeAnnotation] Source #

HasName (Enum a) Source # 

Methods

name :: Lens (Enum a) Text Source #

HasValues (Enum a) [EnumDef a] Source # 

Methods

values :: Lens (Enum a) [EnumDef a] Source #

type Rep (Enum srcAnnot) Source # 
type Rep (Enum srcAnnot) = D1 (MetaData "Enum" "Language.Thrift.Internal.Types" "language-thrift-0.8.0.1-74ptPlTr1sU1XwSnsHlCew" False) (C1 (MetaCons "Enum" PrefixI True) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "enumName") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Text)) (S1 (MetaSel (Just Symbol "enumValues") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [EnumDef srcAnnot]))) ((:*:) (S1 (MetaSel (Just Symbol "enumAnnotations") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [TypeAnnotation])) ((:*:) (S1 (MetaSel (Just Symbol "enumDocstring") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Docstring)) (S1 (MetaSel (Just Symbol "enumSrcAnnot") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 srcAnnot))))))

data Struct srcAnnot Source #

A struct definition

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

Constructors

Struct 

Fields

Instances

Functor Struct Source # 

Methods

fmap :: (a -> b) -> Struct a -> Struct b #

(<$) :: a -> Struct b -> Struct a #

HasFields Struct Source # 

Methods

fields :: Functor f => ([Field a] -> f [Field a]) -> Struct a -> f (Struct a) Source #

HasSrcAnnot Struct Source # 

Methods

srcAnnot :: Functor f => (a -> f a) -> Struct a -> f (Struct a) Source #

Eq srcAnnot => Eq (Struct srcAnnot) Source # 

Methods

(==) :: Struct srcAnnot -> Struct srcAnnot -> Bool #

(/=) :: Struct srcAnnot -> Struct srcAnnot -> Bool #

Data srcAnnot => Data (Struct srcAnnot) Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Struct srcAnnot -> c (Struct srcAnnot) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Struct srcAnnot) #

toConstr :: Struct srcAnnot -> Constr #

dataTypeOf :: Struct srcAnnot -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c (Struct srcAnnot)) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Struct srcAnnot)) #

gmapT :: (forall b. Data b => b -> b) -> Struct srcAnnot -> Struct srcAnnot #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Struct srcAnnot -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Struct srcAnnot -> r #

gmapQ :: (forall d. Data d => d -> u) -> Struct srcAnnot -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Struct srcAnnot -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Struct srcAnnot -> m (Struct srcAnnot) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Struct srcAnnot -> m (Struct srcAnnot) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Struct srcAnnot -> m (Struct srcAnnot) #

Ord srcAnnot => Ord (Struct srcAnnot) Source # 

Methods

compare :: Struct srcAnnot -> Struct srcAnnot -> Ordering #

(<) :: Struct srcAnnot -> Struct srcAnnot -> Bool #

(<=) :: Struct srcAnnot -> Struct srcAnnot -> Bool #

(>) :: Struct srcAnnot -> Struct srcAnnot -> Bool #

(>=) :: Struct srcAnnot -> Struct srcAnnot -> Bool #

max :: Struct srcAnnot -> Struct srcAnnot -> Struct srcAnnot #

min :: Struct srcAnnot -> Struct srcAnnot -> Struct srcAnnot #

Show srcAnnot => Show (Struct srcAnnot) Source # 

Methods

showsPrec :: Int -> Struct srcAnnot -> ShowS #

show :: Struct srcAnnot -> String #

showList :: [Struct srcAnnot] -> ShowS #

Generic (Struct srcAnnot) Source # 

Associated Types

type Rep (Struct srcAnnot) :: * -> * #

Methods

from :: Struct srcAnnot -> Rep (Struct srcAnnot) x #

to :: Rep (Struct srcAnnot) x -> Struct srcAnnot #

HasDocstring (Struct a) Source # 

Methods

docstring :: Lens (Struct a) Docstring Source #

HasAnnotations (Struct a) Source # 
HasName (Struct a) Source # 

Methods

name :: Lens (Struct a) Text Source #

type Rep (Struct srcAnnot) Source # 
type Rep (Struct srcAnnot) = D1 (MetaData "Struct" "Language.Thrift.Internal.Types" "language-thrift-0.8.0.1-74ptPlTr1sU1XwSnsHlCew" False) (C1 (MetaCons "Struct" PrefixI True) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "structName") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Text)) (S1 (MetaSel (Just Symbol "structFields") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Field srcAnnot]))) ((:*:) (S1 (MetaSel (Just Symbol "structAnnotations") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [TypeAnnotation])) ((:*:) (S1 (MetaSel (Just Symbol "structDocstring") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Docstring)) (S1 (MetaSel (Just Symbol "structSrcAnnot") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 srcAnnot))))))

data Union srcAnnot Source #

A union of other types.

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

Constructors

Union 

Fields

Instances

Functor Union Source # 

Methods

fmap :: (a -> b) -> Union a -> Union b #

(<$) :: a -> Union b -> Union a #

HasFields Union Source # 

Methods

fields :: Functor f => ([Field a] -> f [Field a]) -> Union a -> f (Union a) Source #

HasSrcAnnot Union Source # 

Methods

srcAnnot :: Functor f => (a -> f a) -> Union a -> f (Union a) Source #

Eq srcAnnot => Eq (Union srcAnnot) Source # 

Methods

(==) :: Union srcAnnot -> Union srcAnnot -> Bool #

(/=) :: Union srcAnnot -> Union srcAnnot -> Bool #

Data srcAnnot => Data (Union srcAnnot) Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Union srcAnnot -> c (Union srcAnnot) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Union srcAnnot) #

toConstr :: Union srcAnnot -> Constr #

dataTypeOf :: Union srcAnnot -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c (Union srcAnnot)) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Union srcAnnot)) #

gmapT :: (forall b. Data b => b -> b) -> Union srcAnnot -> Union srcAnnot #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Union srcAnnot -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Union srcAnnot -> r #

gmapQ :: (forall d. Data d => d -> u) -> Union srcAnnot -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Union srcAnnot -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Union srcAnnot -> m (Union srcAnnot) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Union srcAnnot -> m (Union srcAnnot) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Union srcAnnot -> m (Union srcAnnot) #

Ord srcAnnot => Ord (Union srcAnnot) Source # 

Methods

compare :: Union srcAnnot -> Union srcAnnot -> Ordering #

(<) :: Union srcAnnot -> Union srcAnnot -> Bool #

(<=) :: Union srcAnnot -> Union srcAnnot -> Bool #

(>) :: Union srcAnnot -> Union srcAnnot -> Bool #

(>=) :: Union srcAnnot -> Union srcAnnot -> Bool #

max :: Union srcAnnot -> Union srcAnnot -> Union srcAnnot #

min :: Union srcAnnot -> Union srcAnnot -> Union srcAnnot #

Show srcAnnot => Show (Union srcAnnot) Source # 

Methods

showsPrec :: Int -> Union srcAnnot -> ShowS #

show :: Union srcAnnot -> String #

showList :: [Union srcAnnot] -> ShowS #

Generic (Union srcAnnot) Source # 

Associated Types

type Rep (Union srcAnnot) :: * -> * #

Methods

from :: Union srcAnnot -> Rep (Union srcAnnot) x #

to :: Rep (Union srcAnnot) x -> Union srcAnnot #

HasDocstring (Union a) Source # 

Methods

docstring :: Lens (Union a) Docstring Source #

HasAnnotations (Union a) Source # 

Methods

annotations :: Lens (Union a) [TypeAnnotation] Source #

HasName (Union a) Source # 

Methods

name :: Lens (Union a) Text Source #

type Rep (Union srcAnnot) Source # 
type Rep (Union srcAnnot) = D1 (MetaData "Union" "Language.Thrift.Internal.Types" "language-thrift-0.8.0.1-74ptPlTr1sU1XwSnsHlCew" False) (C1 (MetaCons "Union" PrefixI True) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "unionName") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Text)) (S1 (MetaSel (Just Symbol "unionFields") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Field srcAnnot]))) ((:*:) (S1 (MetaSel (Just Symbol "unionAnnotations") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [TypeAnnotation])) ((:*:) (S1 (MetaSel (Just Symbol "unionDocstring") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Docstring)) (S1 (MetaSel (Just Symbol "unionSrcAnnot") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 srcAnnot))))))

data Exception srcAnnot Source #

Exception types.

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

Constructors

Exception 

Fields

Instances

Functor Exception Source # 

Methods

fmap :: (a -> b) -> Exception a -> Exception b #

(<$) :: a -> Exception b -> Exception a #

HasFields Exception Source # 

Methods

fields :: Functor f => ([Field a] -> f [Field a]) -> Exception a -> f (Exception a) Source #

HasSrcAnnot Exception Source # 

Methods

srcAnnot :: Functor f => (a -> f a) -> Exception a -> f (Exception a) Source #

Eq srcAnnot => Eq (Exception srcAnnot) Source # 

Methods

(==) :: Exception srcAnnot -> Exception srcAnnot -> Bool #

(/=) :: Exception srcAnnot -> Exception srcAnnot -> Bool #

Data srcAnnot => Data (Exception srcAnnot) Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Exception srcAnnot -> c (Exception srcAnnot) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Exception srcAnnot) #

toConstr :: Exception srcAnnot -> Constr #

dataTypeOf :: Exception srcAnnot -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c (Exception srcAnnot)) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Exception srcAnnot)) #

gmapT :: (forall b. Data b => b -> b) -> Exception srcAnnot -> Exception srcAnnot #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Exception srcAnnot -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Exception srcAnnot -> r #

gmapQ :: (forall d. Data d => d -> u) -> Exception srcAnnot -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Exception srcAnnot -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Exception srcAnnot -> m (Exception srcAnnot) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Exception srcAnnot -> m (Exception srcAnnot) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Exception srcAnnot -> m (Exception srcAnnot) #

Ord srcAnnot => Ord (Exception srcAnnot) Source # 

Methods

compare :: Exception srcAnnot -> Exception srcAnnot -> Ordering #

(<) :: Exception srcAnnot -> Exception srcAnnot -> Bool #

(<=) :: Exception srcAnnot -> Exception srcAnnot -> Bool #

(>) :: Exception srcAnnot -> Exception srcAnnot -> Bool #

(>=) :: Exception srcAnnot -> Exception srcAnnot -> Bool #

max :: Exception srcAnnot -> Exception srcAnnot -> Exception srcAnnot #

min :: Exception srcAnnot -> Exception srcAnnot -> Exception srcAnnot #

Show srcAnnot => Show (Exception srcAnnot) Source # 

Methods

showsPrec :: Int -> Exception srcAnnot -> ShowS #

show :: Exception srcAnnot -> String #

showList :: [Exception srcAnnot] -> ShowS #

Generic (Exception srcAnnot) Source # 

Associated Types

type Rep (Exception srcAnnot) :: * -> * #

Methods

from :: Exception srcAnnot -> Rep (Exception srcAnnot) x #

to :: Rep (Exception srcAnnot) x -> Exception srcAnnot #

HasDocstring (Exception a) Source # 

Methods

docstring :: Lens (Exception a) Docstring Source #

HasAnnotations (Exception a) Source # 
HasName (Exception a) Source # 

Methods

name :: Lens (Exception a) Text Source #

type Rep (Exception srcAnnot) Source # 
type Rep (Exception srcAnnot) = D1 (MetaData "Exception" "Language.Thrift.Internal.Types" "language-thrift-0.8.0.1-74ptPlTr1sU1XwSnsHlCew" False) (C1 (MetaCons "Exception" PrefixI True) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "exceptionName") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Text)) (S1 (MetaSel (Just Symbol "exceptionFields") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Field srcAnnot]))) ((:*:) (S1 (MetaSel (Just Symbol "exceptionAnnotations") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [TypeAnnotation])) ((:*:) (S1 (MetaSel (Just Symbol "exceptionDocstring") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Docstring)) (S1 (MetaSel (Just Symbol "exceptionSrcAnnot") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 srcAnnot))))))

data Senum srcAnnot Source #

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

Constructors

Senum 

Fields

Instances

Functor Senum Source # 

Methods

fmap :: (a -> b) -> Senum a -> Senum b #

(<$) :: a -> Senum b -> Senum a #

HasSrcAnnot Senum Source # 

Methods

srcAnnot :: Functor f => (a -> f a) -> Senum a -> f (Senum a) Source #

Eq srcAnnot => Eq (Senum srcAnnot) Source # 

Methods

(==) :: Senum srcAnnot -> Senum srcAnnot -> Bool #

(/=) :: Senum srcAnnot -> Senum srcAnnot -> Bool #

Data srcAnnot => Data (Senum srcAnnot) Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Senum srcAnnot -> c (Senum srcAnnot) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Senum srcAnnot) #

toConstr :: Senum srcAnnot -> Constr #

dataTypeOf :: Senum srcAnnot -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c (Senum srcAnnot)) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Senum srcAnnot)) #

gmapT :: (forall b. Data b => b -> b) -> Senum srcAnnot -> Senum srcAnnot #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Senum srcAnnot -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Senum srcAnnot -> r #

gmapQ :: (forall d. Data d => d -> u) -> Senum srcAnnot -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Senum srcAnnot -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Senum srcAnnot -> m (Senum srcAnnot) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Senum srcAnnot -> m (Senum srcAnnot) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Senum srcAnnot -> m (Senum srcAnnot) #

Ord srcAnnot => Ord (Senum srcAnnot) Source # 

Methods

compare :: Senum srcAnnot -> Senum srcAnnot -> Ordering #

(<) :: Senum srcAnnot -> Senum srcAnnot -> Bool #

(<=) :: Senum srcAnnot -> Senum srcAnnot -> Bool #

(>) :: Senum srcAnnot -> Senum srcAnnot -> Bool #

(>=) :: Senum srcAnnot -> Senum srcAnnot -> Bool #

max :: Senum srcAnnot -> Senum srcAnnot -> Senum srcAnnot #

min :: Senum srcAnnot -> Senum srcAnnot -> Senum srcAnnot #

Show srcAnnot => Show (Senum srcAnnot) Source # 

Methods

showsPrec :: Int -> Senum srcAnnot -> ShowS #

show :: Senum srcAnnot -> String #

showList :: [Senum srcAnnot] -> ShowS #

Generic (Senum srcAnnot) Source # 

Associated Types

type Rep (Senum srcAnnot) :: * -> * #

Methods

from :: Senum srcAnnot -> Rep (Senum srcAnnot) x #

to :: Rep (Senum srcAnnot) x -> Senum srcAnnot #

HasDocstring (Senum a) Source # 

Methods

docstring :: Lens (Senum a) Docstring Source #

HasAnnotations (Senum a) Source # 

Methods

annotations :: Lens (Senum a) [TypeAnnotation] Source #

HasName (Senum a) Source # 

Methods

name :: Lens (Senum a) Text Source #

HasValues (Senum a) [Text] Source # 

Methods

values :: Lens (Senum a) [Text] Source #

type Rep (Senum srcAnnot) Source # 
type Rep (Senum srcAnnot) = D1 (MetaData "Senum" "Language.Thrift.Internal.Types" "language-thrift-0.8.0.1-74ptPlTr1sU1XwSnsHlCew" False) (C1 (MetaCons "Senum" PrefixI True) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "senumName") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Text)) (S1 (MetaSel (Just Symbol "senumValues") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Text]))) ((:*:) (S1 (MetaSel (Just Symbol "senumAnnotations") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [TypeAnnotation])) ((:*:) (S1 (MetaSel (Just Symbol "senumDocstring") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Docstring)) (S1 (MetaSel (Just Symbol "senumSrcAnnot") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 srcAnnot))))))

data FieldRequiredness Source #

Whether a field is required or optional.

Constructors

Required

The field is required.

Optional

The field is optional.

Instances

Eq FieldRequiredness Source # 
Data FieldRequiredness Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> FieldRequiredness -> c FieldRequiredness #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c FieldRequiredness #

toConstr :: FieldRequiredness -> Constr #

dataTypeOf :: FieldRequiredness -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c FieldRequiredness) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c FieldRequiredness) #

gmapT :: (forall b. Data b => b -> b) -> FieldRequiredness -> FieldRequiredness #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> FieldRequiredness -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> FieldRequiredness -> r #

gmapQ :: (forall d. Data d => d -> u) -> FieldRequiredness -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> FieldRequiredness -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> FieldRequiredness -> m FieldRequiredness #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> FieldRequiredness -> m FieldRequiredness #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> FieldRequiredness -> m FieldRequiredness #

Ord FieldRequiredness Source # 
Show FieldRequiredness Source # 
Generic FieldRequiredness Source # 
type Rep FieldRequiredness Source # 
type Rep FieldRequiredness = D1 (MetaData "FieldRequiredness" "Language.Thrift.Internal.Types" "language-thrift-0.8.0.1-74ptPlTr1sU1XwSnsHlCew" False) ((:+:) (C1 (MetaCons "Required" PrefixI False) U1) (C1 (MetaCons "Optional" PrefixI False) U1))

data Field srcAnnot Source #

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

Constructors

Field 

Fields

Instances

Functor Field Source # 

Methods

fmap :: (a -> b) -> Field a -> Field b #

(<$) :: a -> Field b -> Field a #

HasValueType Field Source # 

Methods

valueType :: Functor f => (TypeReference a -> f (TypeReference a)) -> Field a -> f (Field a) Source #

HasSrcAnnot Field Source # 

Methods

srcAnnot :: Functor f => (a -> f a) -> Field a -> f (Field a) Source #

Eq srcAnnot => Eq (Field srcAnnot) Source # 

Methods

(==) :: Field srcAnnot -> Field srcAnnot -> Bool #

(/=) :: Field srcAnnot -> Field srcAnnot -> Bool #

Data srcAnnot => Data (Field srcAnnot) Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Field srcAnnot -> c (Field srcAnnot) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Field srcAnnot) #

toConstr :: Field srcAnnot -> Constr #

dataTypeOf :: Field srcAnnot -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c (Field srcAnnot)) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Field srcAnnot)) #

gmapT :: (forall b. Data b => b -> b) -> Field srcAnnot -> Field srcAnnot #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Field srcAnnot -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Field srcAnnot -> r #

gmapQ :: (forall d. Data d => d -> u) -> Field srcAnnot -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Field srcAnnot -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Field srcAnnot -> m (Field srcAnnot) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Field srcAnnot -> m (Field srcAnnot) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Field srcAnnot -> m (Field srcAnnot) #

Ord srcAnnot => Ord (Field srcAnnot) Source # 

Methods

compare :: Field srcAnnot -> Field srcAnnot -> Ordering #

(<) :: Field srcAnnot -> Field srcAnnot -> Bool #

(<=) :: Field srcAnnot -> Field srcAnnot -> Bool #

(>) :: Field srcAnnot -> Field srcAnnot -> Bool #

(>=) :: Field srcAnnot -> Field srcAnnot -> Bool #

max :: Field srcAnnot -> Field srcAnnot -> Field srcAnnot #

min :: Field srcAnnot -> Field srcAnnot -> Field srcAnnot #

Show srcAnnot => Show (Field srcAnnot) Source # 

Methods

showsPrec :: Int -> Field srcAnnot -> ShowS #

show :: Field srcAnnot -> String #

showList :: [Field srcAnnot] -> ShowS #

Generic (Field srcAnnot) Source # 

Associated Types

type Rep (Field srcAnnot) :: * -> * #

Methods

from :: Field srcAnnot -> Rep (Field srcAnnot) x #

to :: Rep (Field srcAnnot) x -> Field srcAnnot #

HasDocstring (Field a) Source # 

Methods

docstring :: Lens (Field a) Docstring Source #

HasAnnotations (Field a) Source # 

Methods

annotations :: Lens (Field a) [TypeAnnotation] Source #

HasName (Field a) Source # 

Methods

name :: Lens (Field a) Text Source #

type Rep (Field srcAnnot) Source # 

data EnumDef srcAnnot Source #

A named value inside an enum.

Constructors

EnumDef 

Fields

Instances

Functor EnumDef Source # 

Methods

fmap :: (a -> b) -> EnumDef a -> EnumDef b #

(<$) :: a -> EnumDef b -> EnumDef a #

HasSrcAnnot EnumDef Source # 

Methods

srcAnnot :: Functor f => (a -> f a) -> EnumDef a -> f (EnumDef a) Source #

Eq srcAnnot => Eq (EnumDef srcAnnot) Source # 

Methods

(==) :: EnumDef srcAnnot -> EnumDef srcAnnot -> Bool #

(/=) :: EnumDef srcAnnot -> EnumDef srcAnnot -> Bool #

Data srcAnnot => Data (EnumDef srcAnnot) Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> EnumDef srcAnnot -> c (EnumDef srcAnnot) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (EnumDef srcAnnot) #

toConstr :: EnumDef srcAnnot -> Constr #

dataTypeOf :: EnumDef srcAnnot -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c (EnumDef srcAnnot)) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (EnumDef srcAnnot)) #

gmapT :: (forall b. Data b => b -> b) -> EnumDef srcAnnot -> EnumDef srcAnnot #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> EnumDef srcAnnot -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> EnumDef srcAnnot -> r #

gmapQ :: (forall d. Data d => d -> u) -> EnumDef srcAnnot -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> EnumDef srcAnnot -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> EnumDef srcAnnot -> m (EnumDef srcAnnot) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> EnumDef srcAnnot -> m (EnumDef srcAnnot) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> EnumDef srcAnnot -> m (EnumDef srcAnnot) #

Ord srcAnnot => Ord (EnumDef srcAnnot) Source # 

Methods

compare :: EnumDef srcAnnot -> EnumDef srcAnnot -> Ordering #

(<) :: EnumDef srcAnnot -> EnumDef srcAnnot -> Bool #

(<=) :: EnumDef srcAnnot -> EnumDef srcAnnot -> Bool #

(>) :: EnumDef srcAnnot -> EnumDef srcAnnot -> Bool #

(>=) :: EnumDef srcAnnot -> EnumDef srcAnnot -> Bool #

max :: EnumDef srcAnnot -> EnumDef srcAnnot -> EnumDef srcAnnot #

min :: EnumDef srcAnnot -> EnumDef srcAnnot -> EnumDef srcAnnot #

Show srcAnnot => Show (EnumDef srcAnnot) Source # 

Methods

showsPrec :: Int -> EnumDef srcAnnot -> ShowS #

show :: EnumDef srcAnnot -> String #

showList :: [EnumDef srcAnnot] -> ShowS #

Generic (EnumDef srcAnnot) Source # 

Associated Types

type Rep (EnumDef srcAnnot) :: * -> * #

Methods

from :: EnumDef srcAnnot -> Rep (EnumDef srcAnnot) x #

to :: Rep (EnumDef srcAnnot) x -> EnumDef srcAnnot #

HasDocstring (EnumDef a) Source # 

Methods

docstring :: Lens (EnumDef a) Docstring Source #

HasAnnotations (EnumDef a) Source # 
HasName (EnumDef a) Source # 

Methods

name :: Lens (EnumDef a) Text Source #

HasValues (Enum a) [EnumDef a] Source # 

Methods

values :: Lens (Enum a) [EnumDef a] Source #

HasValue (EnumDef a) (Maybe Integer) Source # 

Methods

value :: Lens (EnumDef a) (Maybe Integer) Source #

type Rep (EnumDef srcAnnot) Source # 
type Rep (EnumDef srcAnnot) = D1 (MetaData "EnumDef" "Language.Thrift.Internal.Types" "language-thrift-0.8.0.1-74ptPlTr1sU1XwSnsHlCew" False) (C1 (MetaCons "EnumDef" PrefixI True) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "enumDefName") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Text)) (S1 (MetaSel (Just Symbol "enumDefValue") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Integer)))) ((:*:) (S1 (MetaSel (Just Symbol "enumDefAnnotations") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [TypeAnnotation])) ((:*:) (S1 (MetaSel (Just Symbol "enumDefDocstring") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Docstring)) (S1 (MetaSel (Just Symbol "enumDefSrcAnnot") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 srcAnnot))))))

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 # 

Methods

fmap :: (a -> b) -> ConstValue a -> ConstValue b #

(<$) :: a -> ConstValue b -> ConstValue a #

HasSrcAnnot ConstValue Source # 

Methods

srcAnnot :: Functor f => (a -> f a) -> ConstValue a -> f (ConstValue a) Source #

Eq srcAnnot => Eq (ConstValue srcAnnot) Source # 

Methods

(==) :: ConstValue srcAnnot -> ConstValue srcAnnot -> Bool #

(/=) :: ConstValue srcAnnot -> ConstValue srcAnnot -> Bool #

Data srcAnnot => Data (ConstValue srcAnnot) Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ConstValue srcAnnot -> c (ConstValue srcAnnot) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (ConstValue srcAnnot) #

toConstr :: ConstValue srcAnnot -> Constr #

dataTypeOf :: ConstValue srcAnnot -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c (ConstValue srcAnnot)) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (ConstValue srcAnnot)) #

gmapT :: (forall b. Data b => b -> b) -> ConstValue srcAnnot -> ConstValue srcAnnot #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ConstValue srcAnnot -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ConstValue srcAnnot -> r #

gmapQ :: (forall d. Data d => d -> u) -> ConstValue srcAnnot -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> ConstValue srcAnnot -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ConstValue srcAnnot -> m (ConstValue srcAnnot) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ConstValue srcAnnot -> m (ConstValue srcAnnot) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ConstValue srcAnnot -> m (ConstValue srcAnnot) #

Ord srcAnnot => Ord (ConstValue srcAnnot) Source # 

Methods

compare :: ConstValue srcAnnot -> ConstValue srcAnnot -> Ordering #

(<) :: ConstValue srcAnnot -> ConstValue srcAnnot -> Bool #

(<=) :: ConstValue srcAnnot -> ConstValue srcAnnot -> Bool #

(>) :: ConstValue srcAnnot -> ConstValue srcAnnot -> Bool #

(>=) :: ConstValue srcAnnot -> ConstValue srcAnnot -> Bool #

max :: ConstValue srcAnnot -> ConstValue srcAnnot -> ConstValue srcAnnot #

min :: ConstValue srcAnnot -> ConstValue srcAnnot -> ConstValue srcAnnot #

Show srcAnnot => Show (ConstValue srcAnnot) Source # 

Methods

showsPrec :: Int -> ConstValue srcAnnot -> ShowS #

show :: ConstValue srcAnnot -> String #

showList :: [ConstValue srcAnnot] -> ShowS #

Generic (ConstValue srcAnnot) Source # 

Associated Types

type Rep (ConstValue srcAnnot) :: * -> * #

Methods

from :: ConstValue srcAnnot -> Rep (ConstValue srcAnnot) x #

to :: Rep (ConstValue srcAnnot) x -> ConstValue srcAnnot #

HasValue (Const a) (ConstValue a) Source # 

Methods

value :: Lens (Const a) (ConstValue a) Source #

type Rep (ConstValue srcAnnot) Source # 
type Rep (ConstValue srcAnnot) = D1 (MetaData "ConstValue" "Language.Thrift.Internal.Types" "language-thrift-0.8.0.1-74ptPlTr1sU1XwSnsHlCew" False) ((:+:) ((:+:) (C1 (MetaCons "ConstInt" PrefixI False) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Integer)) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 srcAnnot)))) ((:+:) (C1 (MetaCons "ConstFloat" PrefixI False) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Double)) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 srcAnnot)))) (C1 (MetaCons "ConstLiteral" PrefixI False) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Text)) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 srcAnnot)))))) ((:+:) (C1 (MetaCons "ConstIdentifier" PrefixI False) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Text)) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 srcAnnot)))) ((:+:) (C1 (MetaCons "ConstList" PrefixI False) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [ConstValue srcAnnot])) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 srcAnnot)))) (C1 (MetaCons "ConstMap" PrefixI False) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [(ConstValue srcAnnot, ConstValue srcAnnot)])) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 srcAnnot)))))))

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 # 

Methods

fmap :: (a -> b) -> TypeReference a -> TypeReference b #

(<$) :: a -> TypeReference b -> TypeReference a #

HasSrcAnnot TypeReference Source # 

Methods

srcAnnot :: Functor f => (a -> f a) -> TypeReference a -> f (TypeReference a) Source #

Eq srcAnnot => Eq (TypeReference srcAnnot) Source # 

Methods

(==) :: TypeReference srcAnnot -> TypeReference srcAnnot -> Bool #

(/=) :: TypeReference srcAnnot -> TypeReference srcAnnot -> Bool #

Data srcAnnot => Data (TypeReference srcAnnot) Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> TypeReference srcAnnot -> c (TypeReference srcAnnot) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (TypeReference srcAnnot) #

toConstr :: TypeReference srcAnnot -> Constr #

dataTypeOf :: TypeReference srcAnnot -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c (TypeReference srcAnnot)) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (TypeReference srcAnnot)) #

gmapT :: (forall b. Data b => b -> b) -> TypeReference srcAnnot -> TypeReference srcAnnot #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> TypeReference srcAnnot -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> TypeReference srcAnnot -> r #

gmapQ :: (forall d. Data d => d -> u) -> TypeReference srcAnnot -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> TypeReference srcAnnot -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> TypeReference srcAnnot -> m (TypeReference srcAnnot) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> TypeReference srcAnnot -> m (TypeReference srcAnnot) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> TypeReference srcAnnot -> m (TypeReference srcAnnot) #

Ord srcAnnot => Ord (TypeReference srcAnnot) Source # 

Methods

compare :: TypeReference srcAnnot -> TypeReference srcAnnot -> Ordering #

(<) :: TypeReference srcAnnot -> TypeReference srcAnnot -> Bool #

(<=) :: TypeReference srcAnnot -> TypeReference srcAnnot -> Bool #

(>) :: TypeReference srcAnnot -> TypeReference srcAnnot -> Bool #

(>=) :: TypeReference srcAnnot -> TypeReference srcAnnot -> Bool #

max :: TypeReference srcAnnot -> TypeReference srcAnnot -> TypeReference srcAnnot #

min :: TypeReference srcAnnot -> TypeReference srcAnnot -> TypeReference srcAnnot #

Show srcAnnot => Show (TypeReference srcAnnot) Source # 

Methods

showsPrec :: Int -> TypeReference srcAnnot -> ShowS #

show :: TypeReference srcAnnot -> String #

showList :: [TypeReference srcAnnot] -> ShowS #

Generic (TypeReference srcAnnot) Source # 

Associated Types

type Rep (TypeReference srcAnnot) :: * -> * #

Methods

from :: TypeReference srcAnnot -> Rep (TypeReference srcAnnot) x #

to :: Rep (TypeReference srcAnnot) x -> TypeReference srcAnnot #

type Rep (TypeReference srcAnnot) Source # 
type Rep (TypeReference srcAnnot) = D1 (MetaData "TypeReference" "Language.Thrift.Internal.Types" "language-thrift-0.8.0.1-74ptPlTr1sU1XwSnsHlCew" False) ((:+:) ((:+:) ((:+:) (C1 (MetaCons "DefinedType" PrefixI False) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Text)) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 srcAnnot)))) ((:+:) (C1 (MetaCons "StringType" PrefixI False) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [TypeAnnotation])) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 srcAnnot)))) (C1 (MetaCons "BinaryType" PrefixI False) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [TypeAnnotation])) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 srcAnnot)))))) ((:+:) (C1 (MetaCons "SListType" PrefixI False) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [TypeAnnotation])) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 srcAnnot)))) ((:+:) (C1 (MetaCons "BoolType" PrefixI False) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [TypeAnnotation])) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 srcAnnot)))) (C1 (MetaCons "ByteType" PrefixI False) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [TypeAnnotation])) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 srcAnnot))))))) ((:+:) ((:+:) (C1 (MetaCons "I16Type" PrefixI False) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [TypeAnnotation])) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 srcAnnot)))) ((:+:) (C1 (MetaCons "I32Type" PrefixI False) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [TypeAnnotation])) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 srcAnnot)))) (C1 (MetaCons "I64Type" PrefixI False) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [TypeAnnotation])) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 srcAnnot)))))) ((:+:) ((:+:) (C1 (MetaCons "DoubleType" PrefixI False) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [TypeAnnotation])) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 srcAnnot)))) (C1 (MetaCons "MapType" PrefixI False) ((:*:) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (TypeReference srcAnnot))) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (TypeReference srcAnnot)))) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [TypeAnnotation])) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 srcAnnot)))))) ((:+:) (C1 (MetaCons "SetType" PrefixI False) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (TypeReference srcAnnot))) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [TypeAnnotation])) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 srcAnnot))))) (C1 (MetaCons "ListType" PrefixI False) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (TypeReference srcAnnot))) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [TypeAnnotation])) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 srcAnnot)))))))))

data Function srcAnnot Source #

A function defined inside a service.

Constructors

Function 

Fields

Instances

Functor Function Source # 

Methods

fmap :: (a -> b) -> Function a -> Function b #

(<$) :: a -> Function b -> Function a #

HasSrcAnnot Function Source # 

Methods

srcAnnot :: Functor f => (a -> f a) -> Function a -> f (Function a) Source #

Eq srcAnnot => Eq (Function srcAnnot) Source # 

Methods

(==) :: Function srcAnnot -> Function srcAnnot -> Bool #

(/=) :: Function srcAnnot -> Function srcAnnot -> Bool #

Data srcAnnot => Data (Function srcAnnot) Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Function srcAnnot -> c (Function srcAnnot) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Function srcAnnot) #

toConstr :: Function srcAnnot -> Constr #

dataTypeOf :: Function srcAnnot -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c (Function srcAnnot)) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Function srcAnnot)) #

gmapT :: (forall b. Data b => b -> b) -> Function srcAnnot -> Function srcAnnot #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Function srcAnnot -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Function srcAnnot -> r #

gmapQ :: (forall d. Data d => d -> u) -> Function srcAnnot -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Function srcAnnot -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Function srcAnnot -> m (Function srcAnnot) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Function srcAnnot -> m (Function srcAnnot) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Function srcAnnot -> m (Function srcAnnot) #

Ord srcAnnot => Ord (Function srcAnnot) Source # 

Methods

compare :: Function srcAnnot -> Function srcAnnot -> Ordering #

(<) :: Function srcAnnot -> Function srcAnnot -> Bool #

(<=) :: Function srcAnnot -> Function srcAnnot -> Bool #

(>) :: Function srcAnnot -> Function srcAnnot -> Bool #

(>=) :: Function srcAnnot -> Function srcAnnot -> Bool #

max :: Function srcAnnot -> Function srcAnnot -> Function srcAnnot #

min :: Function srcAnnot -> Function srcAnnot -> Function srcAnnot #

Show srcAnnot => Show (Function srcAnnot) Source # 

Methods

showsPrec :: Int -> Function srcAnnot -> ShowS #

show :: Function srcAnnot -> String #

showList :: [Function srcAnnot] -> ShowS #

Generic (Function srcAnnot) Source # 

Associated Types

type Rep (Function srcAnnot) :: * -> * #

Methods

from :: Function srcAnnot -> Rep (Function srcAnnot) x #

to :: Rep (Function srcAnnot) x -> Function srcAnnot #

HasDocstring (Function a) Source # 

Methods

docstring :: Lens (Function a) Docstring Source #

HasAnnotations (Function a) Source # 
HasName (Function a) Source # 

Methods

name :: Lens (Function a) Text Source #

type Rep (Function srcAnnot) Source # 
type Rep (Function srcAnnot) = D1 (MetaData "Function" "Language.Thrift.Internal.Types" "language-thrift-0.8.0.1-74ptPlTr1sU1XwSnsHlCew" False) (C1 (MetaCons "Function" PrefixI True) ((:*:) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "functionOneWay") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Bool)) (S1 (MetaSel (Just Symbol "functionReturnType") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe (TypeReference srcAnnot))))) ((:*:) (S1 (MetaSel (Just Symbol "functionName") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Text)) (S1 (MetaSel (Just Symbol "functionParameters") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Field srcAnnot])))) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "functionExceptions") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe [Field srcAnnot]))) (S1 (MetaSel (Just Symbol "functionAnnotations") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [TypeAnnotation]))) ((:*:) (S1 (MetaSel (Just Symbol "functionDocstring") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Docstring)) (S1 (MetaSel (Just Symbol "functionSrcAnnot") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 srcAnnot))))))

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

Instances

Eq TypeAnnotation Source # 
Data TypeAnnotation Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> TypeAnnotation -> c TypeAnnotation #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c TypeAnnotation #

toConstr :: TypeAnnotation -> Constr #

dataTypeOf :: TypeAnnotation -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c TypeAnnotation) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c TypeAnnotation) #

gmapT :: (forall b. Data b => b -> b) -> TypeAnnotation -> TypeAnnotation #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> TypeAnnotation -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> TypeAnnotation -> r #

gmapQ :: (forall d. Data d => d -> u) -> TypeAnnotation -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> TypeAnnotation -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> TypeAnnotation -> m TypeAnnotation #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> TypeAnnotation -> m TypeAnnotation #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> TypeAnnotation -> m TypeAnnotation #

Ord TypeAnnotation Source # 
Show TypeAnnotation Source # 
Generic TypeAnnotation Source # 

Associated Types

type Rep TypeAnnotation :: * -> * #

HasName TypeAnnotation Source # 
HasValue TypeAnnotation (Maybe Text) Source # 
type Rep TypeAnnotation Source # 
type Rep TypeAnnotation = D1 (MetaData "TypeAnnotation" "Language.Thrift.Internal.Types" "language-thrift-0.8.0.1-74ptPlTr1sU1XwSnsHlCew" False) (C1 (MetaCons "TypeAnnotation" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "typeAnnotationName") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Text)) (S1 (MetaSel (Just Symbol "typeAnnotationValue") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Text)))))

type Docstring = Maybe Text Source #

Docstrings are Javadoc-style comments attached various defined objects.

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

Typeclasses

class HasFields t where Source #

Minimal complete definition

fields

Methods

fields :: Lens (t a) [Field a] Source #

Instances

HasFields Exception Source # 

Methods

fields :: Functor f => ([Field a] -> f [Field a]) -> Exception a -> f (Exception a) Source #

HasFields Union Source # 

Methods

fields :: Functor f => ([Field a] -> f [Field a]) -> Union a -> f (Union a) Source #

HasFields Struct Source # 

Methods

fields :: Functor f => ([Field a] -> f [Field a]) -> Struct a -> f (Struct a) Source #

class HasName t where Source #

Minimal complete definition

name

Methods

name :: Lens t Text Source #

Instances

HasName TypeAnnotation Source # 
HasName (Namespace a) Source # 

Methods

name :: Lens (Namespace a) Text Source #

HasName (Definition a) Source # 

Methods

name :: Lens (Definition a) Text Source #

HasName (Type a) Source # 

Methods

name :: Lens (Type a) Text Source #

HasName (Senum a) Source # 

Methods

name :: Lens (Senum a) Text Source #

HasName (Exception a) Source # 

Methods

name :: Lens (Exception a) Text Source #

HasName (Union a) Source # 

Methods

name :: Lens (Union a) Text Source #

HasName (Struct a) Source # 

Methods

name :: Lens (Struct a) Text Source #

HasName (Enum a) Source # 

Methods

name :: Lens (Enum a) Text Source #

HasName (EnumDef a) Source # 

Methods

name :: Lens (EnumDef a) Text Source #

HasName (Typedef a) Source # 

Methods

name :: Lens (Typedef a) Text Source #

HasName (Const a) Source # 

Methods

name :: Lens (Const a) Text Source #

HasName (Service a) Source # 

Methods

name :: Lens (Service a) Text Source #

HasName (Function a) Source # 

Methods

name :: Lens (Function a) Text Source #

HasName (Field a) Source # 

Methods

name :: Lens (Field a) Text Source #

class HasSrcAnnot t where Source #

Minimal complete definition

srcAnnot

Methods

srcAnnot :: Lens (t a) a Source #

Instances

HasSrcAnnot Include Source # 

Methods

srcAnnot :: Functor f => (a -> f a) -> Include a -> f (Include a) Source #

HasSrcAnnot Namespace Source # 

Methods

srcAnnot :: Functor f => (a -> f a) -> Namespace a -> f (Namespace a) Source #

HasSrcAnnot Definition Source # 

Methods

srcAnnot :: Functor f => (a -> f a) -> Definition a -> f (Definition a) Source #

HasSrcAnnot Type Source # 

Methods

srcAnnot :: Functor f => (a -> f a) -> Type a -> f (Type a) Source #

HasSrcAnnot Senum Source # 

Methods

srcAnnot :: Functor f => (a -> f a) -> Senum a -> f (Senum a) Source #

HasSrcAnnot Exception Source # 

Methods

srcAnnot :: Functor f => (a -> f a) -> Exception a -> f (Exception a) Source #

HasSrcAnnot Union Source # 

Methods

srcAnnot :: Functor f => (a -> f a) -> Union a -> f (Union a) Source #

HasSrcAnnot Struct Source # 

Methods

srcAnnot :: Functor f => (a -> f a) -> Struct a -> f (Struct a) Source #

HasSrcAnnot Enum Source # 

Methods

srcAnnot :: Functor f => (a -> f a) -> Enum a -> f (Enum a) Source #

HasSrcAnnot EnumDef Source # 

Methods

srcAnnot :: Functor f => (a -> f a) -> EnumDef a -> f (EnumDef a) Source #

HasSrcAnnot Typedef Source # 

Methods

srcAnnot :: Functor f => (a -> f a) -> Typedef a -> f (Typedef a) Source #

HasSrcAnnot Const Source # 

Methods

srcAnnot :: Functor f => (a -> f a) -> Const a -> f (Const a) Source #

HasSrcAnnot Service Source # 

Methods

srcAnnot :: Functor f => (a -> f a) -> Service a -> f (Service a) Source #

HasSrcAnnot Function Source # 

Methods

srcAnnot :: Functor f => (a -> f a) -> Function a -> f (Function a) Source #

HasSrcAnnot Field Source # 

Methods

srcAnnot :: Functor f => (a -> f a) -> Field a -> f (Field a) Source #

HasSrcAnnot TypeReference Source # 

Methods

srcAnnot :: Functor f => (a -> f a) -> TypeReference a -> f (TypeReference a) Source #

HasSrcAnnot ConstValue Source # 

Methods

srcAnnot :: Functor f => (a -> f a) -> ConstValue a -> f (ConstValue a) Source #

class HasValue s a | s -> a where Source #

Minimal complete definition

value

Methods

value :: Lens s a Source #

class HasValues s a | s -> a where Source #

Minimal complete definition

values

Methods

values :: Lens s a Source #

Instances

HasValues (Senum a) [Text] Source # 

Methods

values :: Lens (Senum a) [Text] Source #

HasValues (Enum a) [EnumDef a] Source # 

Methods

values :: Lens (Enum a) [EnumDef a] Source #

class HasValueType t where Source #

Minimal complete definition

valueType

Methods

valueType :: Lens (t a) (TypeReference a) Source #

Instances