language-thrift-0.13.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-Inferred
LanguageHaskell2010

Language.Thrift.AST

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

Instances details
Functor Program Source # 
Instance details

Defined in Language.Thrift.Internal.AST

Methods

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

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

Data srcAnnot => Data (Program srcAnnot) Source # 
Instance details

Defined in Language.Thrift.Internal.AST

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 :: forall r r'. (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) #

Generic (Program srcAnnot) Source # 
Instance details

Defined in Language.Thrift.Internal.AST

Associated Types

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

Methods

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

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

Show srcAnnot => Show (Program srcAnnot) Source # 
Instance details

Defined in Language.Thrift.Internal.AST

Methods

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

show :: Program srcAnnot -> String #

showList :: [Program srcAnnot] -> ShowS #

Eq srcAnnot => Eq (Program srcAnnot) Source # 
Instance details

Defined in Language.Thrift.Internal.AST

Methods

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

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

Ord srcAnnot => Ord (Program srcAnnot) Source # 
Instance details

Defined in Language.Thrift.Internal.AST

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 #

type Rep (Program srcAnnot) Source # 
Instance details

Defined in Language.Thrift.Internal.AST

type Rep (Program srcAnnot) = D1 ('MetaData "Program" "Language.Thrift.Internal.AST" "language-thrift-0.13.0.0-2JnIzIE0JHWGHhFakpJNs3" 'False) (C1 ('MetaCons "Program" 'PrefixI 'True) (S1 ('MetaSel ('Just "programHeaders") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Header srcAnnot]) :*: S1 ('MetaSel ('Just "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

Instances details
Functor Header Source # 
Instance details

Defined in Language.Thrift.Internal.AST

Methods

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

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

Data srcAnnot => Data (Header srcAnnot) Source # 
Instance details

Defined in Language.Thrift.Internal.AST

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 :: forall r r'. (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) #

Generic (Header srcAnnot) Source # 
Instance details

Defined in Language.Thrift.Internal.AST

Associated Types

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

Methods

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

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

Show srcAnnot => Show (Header srcAnnot) Source # 
Instance details

Defined in Language.Thrift.Internal.AST

Methods

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

show :: Header srcAnnot -> String #

showList :: [Header srcAnnot] -> ShowS #

Eq srcAnnot => Eq (Header srcAnnot) Source # 
Instance details

Defined in Language.Thrift.Internal.AST

Methods

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

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

Ord srcAnnot => Ord (Header srcAnnot) Source # 
Instance details

Defined in Language.Thrift.Internal.AST

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 #

type Rep (Header srcAnnot) Source # 
Instance details

Defined in Language.Thrift.Internal.AST

type Rep (Header srcAnnot) = D1 ('MetaData "Header" "Language.Thrift.Internal.AST" "language-thrift-0.13.0.0-2JnIzIE0JHWGHhFakpJNs3" 'False) (C1 ('MetaCons "HeaderInclude" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Include srcAnnot))) :+: C1 ('MetaCons "HeaderNamespace" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe 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

Instances details
Functor Include Source # 
Instance details

Defined in Language.Thrift.Internal.AST

Methods

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

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

HasSrcAnnot Include Source # 
Instance details

Defined in Language.Thrift.Internal.AST

Methods

srcAnnot :: Lens (Include a) a Source #

Data srcAnnot => Data (Include srcAnnot) Source # 
Instance details

Defined in Language.Thrift.Internal.AST

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 :: forall r r'. (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) #

Generic (Include srcAnnot) Source # 
Instance details

Defined in Language.Thrift.Internal.AST

Associated Types

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

Methods

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

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

Show srcAnnot => Show (Include srcAnnot) Source # 
Instance details

Defined in Language.Thrift.Internal.AST

Methods

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

show :: Include srcAnnot -> String #

showList :: [Include srcAnnot] -> ShowS #

Eq srcAnnot => Eq (Include srcAnnot) Source # 
Instance details

Defined in Language.Thrift.Internal.AST

Methods

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

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

Ord srcAnnot => Ord (Include srcAnnot) Source # 
Instance details

Defined in Language.Thrift.Internal.AST

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 #

type Rep (Include srcAnnot) Source # 
Instance details

Defined in Language.Thrift.Internal.AST

type Rep (Include srcAnnot) = D1 ('MetaData "Include" "Language.Thrift.Internal.AST" "language-thrift-0.13.0.0-2JnIzIE0JHWGHhFakpJNs3" 'False) (C1 ('MetaCons "Include" 'PrefixI 'True) (S1 ('MetaSel ('Just "includePath") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text) :*: S1 ('MetaSel ('Just "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

Instances details
Functor Namespace Source # 
Instance details

Defined in Language.Thrift.Internal.AST

Methods

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

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

HasSrcAnnot Namespace Source # 
Instance details

Defined in Language.Thrift.Internal.AST

Methods

srcAnnot :: Lens (Namespace a) a Source #

Data srcAnnot => Data (Namespace srcAnnot) Source # 
Instance details

Defined in Language.Thrift.Internal.AST

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 :: forall r r'. (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) #

Generic (Namespace srcAnnot) Source # 
Instance details

Defined in Language.Thrift.Internal.AST

Associated Types

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

Methods

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

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

Show srcAnnot => Show (Namespace srcAnnot) Source # 
Instance details

Defined in Language.Thrift.Internal.AST

Methods

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

show :: Namespace srcAnnot -> String #

showList :: [Namespace srcAnnot] -> ShowS #

Eq srcAnnot => Eq (Namespace srcAnnot) Source # 
Instance details

Defined in Language.Thrift.Internal.AST

Methods

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

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

Ord srcAnnot => Ord (Namespace srcAnnot) Source # 
Instance details

Defined in Language.Thrift.Internal.AST

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 #

HasName (Namespace a) Source # 
Instance details

Defined in Language.Thrift.Internal.AST

Methods

name :: Lens (Namespace a) Text Source #

type Rep (Namespace srcAnnot) Source # 
Instance details

Defined in Language.Thrift.Internal.AST

type Rep (Namespace srcAnnot) = D1 ('MetaData "Namespace" "Language.Thrift.Internal.AST" "language-thrift-0.13.0.0-2JnIzIE0JHWGHhFakpJNs3" 'False) (C1 ('MetaCons "Namespace" 'PrefixI 'True) (S1 ('MetaSel ('Just "namespaceLanguage") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text) :*: (S1 ('MetaSel ('Just "namespaceName") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text) :*: S1 ('MetaSel ('Just "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

Instances details
Functor Definition Source # 
Instance details

Defined in Language.Thrift.Internal.AST

Methods

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

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

HasSrcAnnot Definition Source # 
Instance details

Defined in Language.Thrift.Internal.AST

Methods

srcAnnot :: Lens (Definition a) a Source #

Data srcAnnot => Data (Definition srcAnnot) Source # 
Instance details

Defined in Language.Thrift.Internal.AST

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 :: forall r r'. (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) #

Generic (Definition srcAnnot) Source # 
Instance details

Defined in Language.Thrift.Internal.AST

Associated Types

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

Methods

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

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

Show srcAnnot => Show (Definition srcAnnot) Source # 
Instance details

Defined in Language.Thrift.Internal.AST

Methods

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

show :: Definition srcAnnot -> String #

showList :: [Definition srcAnnot] -> ShowS #

Eq srcAnnot => Eq (Definition srcAnnot) Source # 
Instance details

Defined in Language.Thrift.Internal.AST

Methods

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

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

Ord srcAnnot => Ord (Definition srcAnnot) Source # 
Instance details

Defined in Language.Thrift.Internal.AST

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 #

HasName (Definition a) Source # 
Instance details

Defined in Language.Thrift.Internal.AST

Methods

name :: Lens (Definition a) Text Source #

type Rep (Definition srcAnnot) Source # 
Instance details

Defined in Language.Thrift.Internal.AST

type Rep (Definition srcAnnot) = D1 ('MetaData "Definition" "Language.Thrift.Internal.AST" "language-thrift-0.13.0.0-2JnIzIE0JHWGHhFakpJNs3" 'False) (C1 ('MetaCons "ConstDefinition" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Const srcAnnot))) :+: (C1 ('MetaCons "TypeDefinition" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Type srcAnnot))) :+: C1 ('MetaCons "ServiceDefinition" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Service srcAnnot)))))

data Const srcAnnot Source #

A declared constant.

const i32 code = 1;

Constructors

Const 

Fields

Instances

Instances details
Functor Const Source # 
Instance details

Defined in Language.Thrift.Internal.AST

Methods

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

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

HasSrcAnnot Const Source # 
Instance details

Defined in Language.Thrift.Internal.AST

Methods

srcAnnot :: Lens (Const a) a Source #

HasValueType Const Source # 
Instance details

Defined in Language.Thrift.Internal.AST

Methods

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

Data srcAnnot => Data (Const srcAnnot) Source # 
Instance details

Defined in Language.Thrift.Internal.AST

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 :: forall r r'. (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) #

Generic (Const srcAnnot) Source # 
Instance details

Defined in Language.Thrift.Internal.AST

Associated Types

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

Methods

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

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

Show srcAnnot => Show (Const srcAnnot) Source # 
Instance details

Defined in Language.Thrift.Internal.AST

Methods

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

show :: Const srcAnnot -> String #

showList :: [Const srcAnnot] -> ShowS #

Eq srcAnnot => Eq (Const srcAnnot) Source # 
Instance details

Defined in Language.Thrift.Internal.AST

Methods

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

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

Ord srcAnnot => Ord (Const srcAnnot) Source # 
Instance details

Defined in Language.Thrift.Internal.AST

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 #

HasDocstring (Const a) Source # 
Instance details

Defined in Language.Thrift.Internal.AST

Methods

docstring :: Lens (Const a) Docstring Source #

HasName (Const a) Source # 
Instance details

Defined in Language.Thrift.Internal.AST

Methods

name :: Lens (Const a) Text Source #

HasValue (Const a) (ConstValue a) Source # 
Instance details

Defined in Language.Thrift.Internal.AST

Methods

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

type Rep (Const srcAnnot) Source # 
Instance details

Defined in Language.Thrift.Internal.AST

type Rep (Const srcAnnot) = D1 ('MetaData "Const" "Language.Thrift.Internal.AST" "language-thrift-0.13.0.0-2JnIzIE0JHWGHhFakpJNs3" 'False) (C1 ('MetaCons "Const" 'PrefixI 'True) ((S1 ('MetaSel ('Just "constValueType") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (TypeReference srcAnnot)) :*: S1 ('MetaSel ('Just "constName") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text)) :*: (S1 ('MetaSel ('Just "constValue") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (ConstValue srcAnnot)) :*: (S1 ('MetaSel ('Just "constDocstring") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Docstring) :*: S1 ('MetaSel ('Just "constSrcAnnot") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 srcAnnot)))))

data Service srcAnnot Source #

A service definition.

service MyService {
    // ...
}

Constructors

Service 

Fields

Instances

Instances details
Functor Service Source # 
Instance details

Defined in Language.Thrift.Internal.AST

Methods

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

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

HasSrcAnnot Service Source # 
Instance details

Defined in Language.Thrift.Internal.AST

Methods

srcAnnot :: Lens (Service a) a Source #

Data srcAnnot => Data (Service srcAnnot) Source # 
Instance details

Defined in Language.Thrift.Internal.AST

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 :: forall r r'. (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) #

Generic (Service srcAnnot) Source # 
Instance details

Defined in Language.Thrift.Internal.AST

Associated Types

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

Methods

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

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

Show srcAnnot => Show (Service srcAnnot) Source # 
Instance details

Defined in Language.Thrift.Internal.AST

Methods

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

show :: Service srcAnnot -> String #

showList :: [Service srcAnnot] -> ShowS #

Eq srcAnnot => Eq (Service srcAnnot) Source # 
Instance details

Defined in Language.Thrift.Internal.AST

Methods

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

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

Ord srcAnnot => Ord (Service srcAnnot) Source # 
Instance details

Defined in Language.Thrift.Internal.AST

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 #

HasAnnotations (Service a) Source # 
Instance details

Defined in Language.Thrift.Internal.AST

HasDocstring (Service a) Source # 
Instance details

Defined in Language.Thrift.Internal.AST

Methods

docstring :: Lens (Service a) Docstring Source #

HasName (Service a) Source # 
Instance details

Defined in Language.Thrift.Internal.AST

Methods

name :: Lens (Service a) Text Source #

type Rep (Service srcAnnot) Source # 
Instance details

Defined in Language.Thrift.Internal.AST

type Rep (Service srcAnnot) = D1 ('MetaData "Service" "Language.Thrift.Internal.AST" "language-thrift-0.13.0.0-2JnIzIE0JHWGHhFakpJNs3" 'False) (C1 ('MetaCons "Service" 'PrefixI 'True) ((S1 ('MetaSel ('Just "serviceName") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text) :*: (S1 ('MetaSel ('Just "serviceExtends") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Text)) :*: S1 ('MetaSel ('Just "serviceFunctions") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Function srcAnnot]))) :*: (S1 ('MetaSel ('Just "serviceAnnotations") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [TypeAnnotation]) :*: (S1 ('MetaSel ('Just "serviceDocstring") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Docstring) :*: S1 ('MetaSel ('Just "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)

structunionexception

SenumType (Senum srcAnnot)
senum

Instances

Instances details
Functor Type Source # 
Instance details

Defined in Language.Thrift.Internal.AST

Methods

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

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

HasSrcAnnot Type Source # 
Instance details

Defined in Language.Thrift.Internal.AST

Methods

srcAnnot :: Lens (Type a) a Source #

Data srcAnnot => Data (Type srcAnnot) Source # 
Instance details

Defined in Language.Thrift.Internal.AST

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 :: forall r r'. (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) #

Generic (Type srcAnnot) Source # 
Instance details

Defined in Language.Thrift.Internal.AST

Associated Types

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

Methods

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

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

Show srcAnnot => Show (Type srcAnnot) Source # 
Instance details

Defined in Language.Thrift.Internal.AST

Methods

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

show :: Type srcAnnot -> String #

showList :: [Type srcAnnot] -> ShowS #

Eq srcAnnot => Eq (Type srcAnnot) Source # 
Instance details

Defined in Language.Thrift.Internal.AST

Methods

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

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

Ord srcAnnot => Ord (Type srcAnnot) Source # 
Instance details

Defined in Language.Thrift.Internal.AST

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 #

HasName (Type a) Source # 
Instance details

Defined in Language.Thrift.Internal.AST

Methods

name :: Lens (Type a) Text Source #

type Rep (Type srcAnnot) Source # 
Instance details

Defined in Language.Thrift.Internal.AST

type Rep (Type srcAnnot) = D1 ('MetaData "Type" "Language.Thrift.Internal.AST" "language-thrift-0.13.0.0-2JnIzIE0JHWGHhFakpJNs3" 'False) ((C1 ('MetaCons "TypedefType" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Typedef srcAnnot))) :+: C1 ('MetaCons "EnumType" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Enum srcAnnot)))) :+: (C1 ('MetaCons "StructType" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Struct srcAnnot))) :+: C1 ('MetaCons "SenumType" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Senum srcAnnot)))))

data Typedef srcAnnot Source #

A typedef is just an alias for another type.

typedef common.Foo Bar

Constructors

Typedef 

Fields

Instances

Instances details
Functor Typedef Source # 
Instance details

Defined in Language.Thrift.Internal.AST

Methods

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

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

HasSrcAnnot Typedef Source # 
Instance details

Defined in Language.Thrift.Internal.AST

Methods

srcAnnot :: Lens (Typedef a) a Source #

Data srcAnnot => Data (Typedef srcAnnot) Source # 
Instance details

Defined in Language.Thrift.Internal.AST

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 :: forall r r'. (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) #

Generic (Typedef srcAnnot) Source # 
Instance details

Defined in Language.Thrift.Internal.AST

Associated Types

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

Methods

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

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

Show srcAnnot => Show (Typedef srcAnnot) Source # 
Instance details

Defined in Language.Thrift.Internal.AST

Methods

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

show :: Typedef srcAnnot -> String #

showList :: [Typedef srcAnnot] -> ShowS #

Eq srcAnnot => Eq (Typedef srcAnnot) Source # 
Instance details

Defined in Language.Thrift.Internal.AST

Methods

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

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

Ord srcAnnot => Ord (Typedef srcAnnot) Source # 
Instance details

Defined in Language.Thrift.Internal.AST

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 #

HasAnnotations (Typedef a) Source # 
Instance details

Defined in Language.Thrift.Internal.AST

HasDocstring (Typedef a) Source # 
Instance details

Defined in Language.Thrift.Internal.AST

Methods

docstring :: Lens (Typedef a) Docstring Source #

HasName (Typedef a) Source # 
Instance details

Defined in Language.Thrift.Internal.AST

Methods

name :: Lens (Typedef a) Text Source #

type Rep (Typedef srcAnnot) Source # 
Instance details

Defined in Language.Thrift.Internal.AST

type Rep (Typedef srcAnnot) = D1 ('MetaData "Typedef" "Language.Thrift.Internal.AST" "language-thrift-0.13.0.0-2JnIzIE0JHWGHhFakpJNs3" 'False) (C1 ('MetaCons "Typedef" 'PrefixI 'True) ((S1 ('MetaSel ('Just "typedefTargetType") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (TypeReference srcAnnot)) :*: S1 ('MetaSel ('Just "typedefName") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text)) :*: (S1 ('MetaSel ('Just "typedefAnnotations") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [TypeAnnotation]) :*: (S1 ('MetaSel ('Just "typedefDocstring") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Docstring) :*: S1 ('MetaSel ('Just "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

Instances details
Functor Enum Source # 
Instance details

Defined in Language.Thrift.Internal.AST

Methods

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

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

HasSrcAnnot Enum Source # 
Instance details

Defined in Language.Thrift.Internal.AST

Methods

srcAnnot :: Lens (Enum a) a Source #

Data srcAnnot => Data (Enum srcAnnot) Source # 
Instance details

Defined in Language.Thrift.Internal.AST

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 :: forall r r'. (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) #

Generic (Enum srcAnnot) Source # 
Instance details

Defined in Language.Thrift.Internal.AST

Associated Types

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

Methods

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

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

Show srcAnnot => Show (Enum srcAnnot) Source # 
Instance details

Defined in Language.Thrift.Internal.AST

Methods

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

show :: Enum srcAnnot -> String #

showList :: [Enum srcAnnot] -> ShowS #

Eq srcAnnot => Eq (Enum srcAnnot) Source # 
Instance details

Defined in Language.Thrift.Internal.AST

Methods

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

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

Ord srcAnnot => Ord (Enum srcAnnot) Source # 
Instance details

Defined in Language.Thrift.Internal.AST

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 #

HasAnnotations (Enum a) Source # 
Instance details

Defined in Language.Thrift.Internal.AST

Methods

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

HasDocstring (Enum a) Source # 
Instance details

Defined in Language.Thrift.Internal.AST

Methods

docstring :: Lens (Enum a) Docstring Source #

HasName (Enum a) Source # 
Instance details

Defined in Language.Thrift.Internal.AST

Methods

name :: Lens (Enum a) Text Source #

HasValues (Enum a) [EnumDef a] Source # 
Instance details

Defined in Language.Thrift.Internal.AST

Methods

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

type Rep (Enum srcAnnot) Source # 
Instance details

Defined in Language.Thrift.Internal.AST

type Rep (Enum srcAnnot) = D1 ('MetaData "Enum" "Language.Thrift.Internal.AST" "language-thrift-0.13.0.0-2JnIzIE0JHWGHhFakpJNs3" 'False) (C1 ('MetaCons "Enum" 'PrefixI 'True) ((S1 ('MetaSel ('Just "enumName") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text) :*: S1 ('MetaSel ('Just "enumValues") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [EnumDef srcAnnot])) :*: (S1 ('MetaSel ('Just "enumAnnotations") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [TypeAnnotation]) :*: (S1 ('MetaSel ('Just "enumDocstring") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Docstring) :*: S1 ('MetaSel ('Just "enumSrcAnnot") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 srcAnnot)))))

data StructKind Source #

The kind of the struct.

Constructors

StructKind
struct
UnionKind
union
ExceptionKind
exception

Instances

Instances details
Data StructKind Source # 
Instance details

Defined in Language.Thrift.Internal.AST

Methods

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

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

toConstr :: StructKind -> Constr #

dataTypeOf :: StructKind -> DataType #

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

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

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

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

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

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

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

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

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

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

Generic StructKind Source # 
Instance details

Defined in Language.Thrift.Internal.AST

Associated Types

type Rep StructKind :: Type -> Type #

Show StructKind Source # 
Instance details

Defined in Language.Thrift.Internal.AST

Eq StructKind Source # 
Instance details

Defined in Language.Thrift.Internal.AST

Ord StructKind Source # 
Instance details

Defined in Language.Thrift.Internal.AST

type Rep StructKind Source # 
Instance details

Defined in Language.Thrift.Internal.AST

type Rep StructKind = D1 ('MetaData "StructKind" "Language.Thrift.Internal.AST" "language-thrift-0.13.0.0-2JnIzIE0JHWGHhFakpJNs3" 'False) (C1 ('MetaCons "StructKind" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "UnionKind" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "ExceptionKind" 'PrefixI 'False) (U1 :: Type -> Type)))

data Struct srcAnnot Source #

A struct, union, or exception definition.

struct User {
    1: Role role = Role.User;
}
union Value {
    1: string stringValue;
    2: i32 intValue;
}
exception UserDoesNotExist {
    1: optional string message
    2: required string username
}

Constructors

Struct 

Fields

Instances

Instances details
Functor Struct Source # 
Instance details

Defined in Language.Thrift.Internal.AST

Methods

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

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

HasFields Struct Source # 
Instance details

Defined in Language.Thrift.Internal.AST

Methods

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

HasSrcAnnot Struct Source # 
Instance details

Defined in Language.Thrift.Internal.AST

Methods

srcAnnot :: Lens (Struct a) a Source #

Data srcAnnot => Data (Struct srcAnnot) Source # 
Instance details

Defined in Language.Thrift.Internal.AST

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 :: forall r r'. (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) #

Generic (Struct srcAnnot) Source # 
Instance details

Defined in Language.Thrift.Internal.AST

Associated Types

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

Methods

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

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

Show srcAnnot => Show (Struct srcAnnot) Source # 
Instance details

Defined in Language.Thrift.Internal.AST

Methods

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

show :: Struct srcAnnot -> String #

showList :: [Struct srcAnnot] -> ShowS #

Eq srcAnnot => Eq (Struct srcAnnot) Source # 
Instance details

Defined in Language.Thrift.Internal.AST

Methods

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

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

Ord srcAnnot => Ord (Struct srcAnnot) Source # 
Instance details

Defined in Language.Thrift.Internal.AST

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 #

HasAnnotations (Struct a) Source # 
Instance details

Defined in Language.Thrift.Internal.AST

HasDocstring (Struct a) Source # 
Instance details

Defined in Language.Thrift.Internal.AST

Methods

docstring :: Lens (Struct a) Docstring Source #

HasName (Struct a) Source # 
Instance details

Defined in Language.Thrift.Internal.AST

Methods

name :: Lens (Struct a) Text Source #

type Rep (Struct srcAnnot) Source # 
Instance details

Defined in Language.Thrift.Internal.AST

type Rep (Struct srcAnnot) = D1 ('MetaData "Struct" "Language.Thrift.Internal.AST" "language-thrift-0.13.0.0-2JnIzIE0JHWGHhFakpJNs3" 'False) (C1 ('MetaCons "Struct" 'PrefixI 'True) ((S1 ('MetaSel ('Just "structKind") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 StructKind) :*: (S1 ('MetaSel ('Just "structName") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text) :*: S1 ('MetaSel ('Just "structFields") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Field srcAnnot]))) :*: (S1 ('MetaSel ('Just "structAnnotations") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [TypeAnnotation]) :*: (S1 ('MetaSel ('Just "structDocstring") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Docstring) :*: S1 ('MetaSel ('Just "structSrcAnnot") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 srcAnnot)))))

type Union = Struct Source #

Deprecated: The type has been consolidated into Struct.

A union of other types.

unionName :: Union a -> Text Source #

Deprecated: Use structName.

unionFields :: Union a -> [Field a] Source #

Deprecated: Use structFields.

unionAnnotations :: Union a -> [TypeAnnotation] Source #

Deprecated: Use structAnnotations.

unionDocstring :: Union a -> Docstring Source #

Deprecated: Use structDocstring.

unionSrcAnnot :: Union a -> a Source #

Deprecated: Use structSrcAnnot.

type Exception = Struct Source #

Deprecated: The type has been consolidated into Struct.

Exception types.

exceptionName :: Exception a -> Text Source #

Deprecated: Use structName.

exceptionFields :: Exception a -> [Field a] Source #

Deprecated: Use structFields.

exceptionAnnotations :: Exception a -> [TypeAnnotation] Source #

Deprecated: Use structAnnotations.

exceptionDocstring :: Exception a -> Docstring Source #

Deprecated: Use structDocstring.

exceptionSrcAnnot :: Exception a -> a Source #

Deprecated: Use structSrcAnnot.

data Senum srcAnnot Source #

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

Constructors

Senum 

Fields

Instances

Instances details
Functor Senum Source # 
Instance details

Defined in Language.Thrift.Internal.AST

Methods

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

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

HasSrcAnnot Senum Source # 
Instance details

Defined in Language.Thrift.Internal.AST

Methods

srcAnnot :: Lens (Senum a) a Source #

Data srcAnnot => Data (Senum srcAnnot) Source # 
Instance details

Defined in Language.Thrift.Internal.AST

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 :: forall r r'. (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) #

Generic (Senum srcAnnot) Source # 
Instance details

Defined in Language.Thrift.Internal.AST

Associated Types

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

Methods

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

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

Show srcAnnot => Show (Senum srcAnnot) Source # 
Instance details

Defined in Language.Thrift.Internal.AST

Methods

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

show :: Senum srcAnnot -> String #

showList :: [Senum srcAnnot] -> ShowS #

Eq srcAnnot => Eq (Senum srcAnnot) Source # 
Instance details

Defined in Language.Thrift.Internal.AST

Methods

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

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

Ord srcAnnot => Ord (Senum srcAnnot) Source # 
Instance details

Defined in Language.Thrift.Internal.AST

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 #

HasAnnotations (Senum a) Source # 
Instance details

Defined in Language.Thrift.Internal.AST

Methods

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

HasDocstring (Senum a) Source # 
Instance details

Defined in Language.Thrift.Internal.AST

Methods

docstring :: Lens (Senum a) Docstring Source #

HasName (Senum a) Source # 
Instance details

Defined in Language.Thrift.Internal.AST

Methods

name :: Lens (Senum a) Text Source #

HasValues (Senum a) [Text] Source # 
Instance details

Defined in Language.Thrift.Internal.AST

Methods

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

type Rep (Senum srcAnnot) Source # 
Instance details

Defined in Language.Thrift.Internal.AST

type Rep (Senum srcAnnot) = D1 ('MetaData "Senum" "Language.Thrift.Internal.AST" "language-thrift-0.13.0.0-2JnIzIE0JHWGHhFakpJNs3" 'False) (C1 ('MetaCons "Senum" 'PrefixI 'True) ((S1 ('MetaSel ('Just "senumName") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text) :*: S1 ('MetaSel ('Just "senumValues") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Text])) :*: (S1 ('MetaSel ('Just "senumAnnotations") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [TypeAnnotation]) :*: (S1 ('MetaSel ('Just "senumDocstring") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Docstring) :*: S1 ('MetaSel ('Just "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

Instances details
Data FieldRequiredness Source # 
Instance details

Defined in Language.Thrift.Internal.AST

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 :: forall r r'. (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 #

Generic FieldRequiredness Source # 
Instance details

Defined in Language.Thrift.Internal.AST

Associated Types

type Rep FieldRequiredness :: Type -> Type #

Show FieldRequiredness Source # 
Instance details

Defined in Language.Thrift.Internal.AST

Eq FieldRequiredness Source # 
Instance details

Defined in Language.Thrift.Internal.AST

Ord FieldRequiredness Source # 
Instance details

Defined in Language.Thrift.Internal.AST

type Rep FieldRequiredness Source # 
Instance details

Defined in Language.Thrift.Internal.AST

type Rep FieldRequiredness = D1 ('MetaData "FieldRequiredness" "Language.Thrift.Internal.AST" "language-thrift-0.13.0.0-2JnIzIE0JHWGHhFakpJNs3" 'False) (C1 ('MetaCons "Required" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Optional" 'PrefixI 'False) (U1 :: Type -> Type))

data Field srcAnnot Source #

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

Constructors

Field 

Fields

Instances

Instances details
Functor Field Source # 
Instance details

Defined in Language.Thrift.Internal.AST

Methods

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

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

HasSrcAnnot Field Source # 
Instance details

Defined in Language.Thrift.Internal.AST

Methods

srcAnnot :: Lens (Field a) a Source #

HasValueType Field Source # 
Instance details

Defined in Language.Thrift.Internal.AST

Methods

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

Data srcAnnot => Data (Field srcAnnot) Source # 
Instance details

Defined in Language.Thrift.Internal.AST

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 :: forall r r'. (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) #

Generic (Field srcAnnot) Source # 
Instance details

Defined in Language.Thrift.Internal.AST

Associated Types

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

Methods

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

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

Show srcAnnot => Show (Field srcAnnot) Source # 
Instance details

Defined in Language.Thrift.Internal.AST

Methods

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

show :: Field srcAnnot -> String #

showList :: [Field srcAnnot] -> ShowS #

Eq srcAnnot => Eq (Field srcAnnot) Source # 
Instance details

Defined in Language.Thrift.Internal.AST

Methods

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

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

Ord srcAnnot => Ord (Field srcAnnot) Source # 
Instance details

Defined in Language.Thrift.Internal.AST

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 #

HasAnnotations (Field a) Source # 
Instance details

Defined in Language.Thrift.Internal.AST

Methods

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

HasDocstring (Field a) Source # 
Instance details

Defined in Language.Thrift.Internal.AST

Methods

docstring :: Lens (Field a) Docstring Source #

HasName (Field a) Source # 
Instance details

Defined in Language.Thrift.Internal.AST

Methods

name :: Lens (Field a) Text Source #

type Rep (Field srcAnnot) Source # 
Instance details

Defined in Language.Thrift.Internal.AST

type Rep (Field srcAnnot) = D1 ('MetaData "Field" "Language.Thrift.Internal.AST" "language-thrift-0.13.0.0-2JnIzIE0JHWGHhFakpJNs3" 'False) (C1 ('MetaCons "Field" 'PrefixI 'True) (((S1 ('MetaSel ('Just "fieldIdentifier") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Integer)) :*: S1 ('MetaSel ('Just "fieldRequiredness") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe FieldRequiredness))) :*: (S1 ('MetaSel ('Just "fieldValueType") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (TypeReference srcAnnot)) :*: S1 ('MetaSel ('Just "fieldName") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text))) :*: ((S1 ('MetaSel ('Just "fieldDefaultValue") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe (ConstValue srcAnnot))) :*: S1 ('MetaSel ('Just "fieldAnnotations") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [TypeAnnotation])) :*: (S1 ('MetaSel ('Just "fieldDocstring") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Docstring) :*: S1 ('MetaSel ('Just "fieldSrcAnnot") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 srcAnnot)))))

data EnumDef srcAnnot Source #

A named value inside an enum.

Constructors

EnumDef 

Fields

Instances

Instances details
Functor EnumDef Source # 
Instance details

Defined in Language.Thrift.Internal.AST

Methods

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

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

HasSrcAnnot EnumDef Source # 
Instance details

Defined in Language.Thrift.Internal.AST

Methods

srcAnnot :: Lens (EnumDef a) a Source #

Data srcAnnot => Data (EnumDef srcAnnot) Source # 
Instance details

Defined in Language.Thrift.Internal.AST

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 :: forall r r'. (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) #

Generic (EnumDef srcAnnot) Source # 
Instance details

Defined in Language.Thrift.Internal.AST

Associated Types

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

Methods

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

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

Show srcAnnot => Show (EnumDef srcAnnot) Source # 
Instance details

Defined in Language.Thrift.Internal.AST

Methods

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

show :: EnumDef srcAnnot -> String #

showList :: [EnumDef srcAnnot] -> ShowS #

Eq srcAnnot => Eq (EnumDef srcAnnot) Source # 
Instance details

Defined in Language.Thrift.Internal.AST

Methods

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

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

Ord srcAnnot => Ord (EnumDef srcAnnot) Source # 
Instance details

Defined in Language.Thrift.Internal.AST

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 #

HasAnnotations (EnumDef a) Source # 
Instance details

Defined in Language.Thrift.Internal.AST

HasDocstring (EnumDef a) Source # 
Instance details

Defined in Language.Thrift.Internal.AST

Methods

docstring :: Lens (EnumDef a) Docstring Source #

HasName (EnumDef a) Source # 
Instance details

Defined in Language.Thrift.Internal.AST

Methods

name :: Lens (EnumDef a) Text Source #

HasValue (EnumDef a) (Maybe Integer) Source # 
Instance details

Defined in Language.Thrift.Internal.AST

Methods

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

HasValues (Enum a) [EnumDef a] Source # 
Instance details

Defined in Language.Thrift.Internal.AST

Methods

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

type Rep (EnumDef srcAnnot) Source # 
Instance details

Defined in Language.Thrift.Internal.AST

type Rep (EnumDef srcAnnot) = D1 ('MetaData "EnumDef" "Language.Thrift.Internal.AST" "language-thrift-0.13.0.0-2JnIzIE0JHWGHhFakpJNs3" 'False) (C1 ('MetaCons "EnumDef" 'PrefixI 'True) ((S1 ('MetaSel ('Just "enumDefName") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text) :*: S1 ('MetaSel ('Just "enumDefValue") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Integer))) :*: (S1 ('MetaSel ('Just "enumDefAnnotations") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [TypeAnnotation]) :*: (S1 ('MetaSel ('Just "enumDefDocstring") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Docstring) :*: S1 ('MetaSel ('Just "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

Instances details
Functor ConstValue Source # 
Instance details

Defined in Language.Thrift.Internal.AST

Methods

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

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

HasSrcAnnot ConstValue Source # 
Instance details

Defined in Language.Thrift.Internal.AST

Methods

srcAnnot :: Lens (ConstValue a) a Source #

Data srcAnnot => Data (ConstValue srcAnnot) Source # 
Instance details

Defined in Language.Thrift.Internal.AST

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 :: forall r r'. (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) #

Generic (ConstValue srcAnnot) Source # 
Instance details

Defined in Language.Thrift.Internal.AST

Associated Types

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

Methods

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

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

Show srcAnnot => Show (ConstValue srcAnnot) Source # 
Instance details

Defined in Language.Thrift.Internal.AST

Methods

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

show :: ConstValue srcAnnot -> String #

showList :: [ConstValue srcAnnot] -> ShowS #

Eq srcAnnot => Eq (ConstValue srcAnnot) Source # 
Instance details

Defined in Language.Thrift.Internal.AST

Methods

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

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

Ord srcAnnot => Ord (ConstValue srcAnnot) Source # 
Instance details

Defined in Language.Thrift.Internal.AST

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 #

HasValue (Const a) (ConstValue a) Source # 
Instance details

Defined in Language.Thrift.Internal.AST

Methods

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

type Rep (ConstValue srcAnnot) Source # 
Instance details

Defined in Language.Thrift.Internal.AST

type Rep (ConstValue srcAnnot) = D1 ('MetaData "ConstValue" "Language.Thrift.Internal.AST" "language-thrift-0.13.0.0-2JnIzIE0JHWGHhFakpJNs3" 'False) ((C1 ('MetaCons "ConstInt" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Integer) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 srcAnnot)) :+: (C1 ('MetaCons "ConstFloat" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Double) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 srcAnnot)) :+: C1 ('MetaCons "ConstLiteral" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 srcAnnot)))) :+: (C1 ('MetaCons "ConstIdentifier" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 srcAnnot)) :+: (C1 ('MetaCons "ConstList" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [ConstValue srcAnnot]) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 srcAnnot)) :+: C1 ('MetaCons "ConstMap" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [(ConstValue srcAnnot, ConstValue srcAnnot)]) :*: S1 ('MetaSel ('Nothing :: Maybe 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

Instances details
Functor TypeReference Source # 
Instance details

Defined in Language.Thrift.Internal.AST

Methods

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

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

HasSrcAnnot TypeReference Source # 
Instance details

Defined in Language.Thrift.Internal.AST

Methods

srcAnnot :: Lens (TypeReference a) a Source #

Data srcAnnot => Data (TypeReference srcAnnot) Source # 
Instance details

Defined in Language.Thrift.Internal.AST

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 :: forall r r'. (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) #

Generic (TypeReference srcAnnot) Source # 
Instance details

Defined in Language.Thrift.Internal.AST

Associated Types

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

Methods

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

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

Show srcAnnot => Show (TypeReference srcAnnot) Source # 
Instance details

Defined in Language.Thrift.Internal.AST

Methods

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

show :: TypeReference srcAnnot -> String #

showList :: [TypeReference srcAnnot] -> ShowS #

Eq srcAnnot => Eq (TypeReference srcAnnot) Source # 
Instance details

Defined in Language.Thrift.Internal.AST

Methods

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

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

Ord srcAnnot => Ord (TypeReference srcAnnot) Source # 
Instance details

Defined in Language.Thrift.Internal.AST

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 #

type Rep (TypeReference srcAnnot) Source # 
Instance details

Defined in Language.Thrift.Internal.AST

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

data Function srcAnnot Source #

A function defined inside a service.

Constructors

Function 

Fields

Instances

Instances details
Functor Function Source # 
Instance details

Defined in Language.Thrift.Internal.AST

Methods

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

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

HasSrcAnnot Function Source # 
Instance details

Defined in Language.Thrift.Internal.AST

Methods

srcAnnot :: Lens (Function a) a Source #

Data srcAnnot => Data (Function srcAnnot) Source # 
Instance details

Defined in Language.Thrift.Internal.AST

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 :: forall r r'. (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) #

Generic (Function srcAnnot) Source # 
Instance details

Defined in Language.Thrift.Internal.AST

Associated Types

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

Methods

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

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

Show srcAnnot => Show (Function srcAnnot) Source # 
Instance details

Defined in Language.Thrift.Internal.AST

Methods

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

show :: Function srcAnnot -> String #

showList :: [Function srcAnnot] -> ShowS #

Eq srcAnnot => Eq (Function srcAnnot) Source # 
Instance details

Defined in Language.Thrift.Internal.AST

Methods

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

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

Ord srcAnnot => Ord (Function srcAnnot) Source # 
Instance details

Defined in Language.Thrift.Internal.AST

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 #

HasAnnotations (Function a) Source # 
Instance details

Defined in Language.Thrift.Internal.AST

HasDocstring (Function a) Source # 
Instance details

Defined in Language.Thrift.Internal.AST

Methods

docstring :: Lens (Function a) Docstring Source #

HasName (Function a) Source # 
Instance details

Defined in Language.Thrift.Internal.AST

Methods

name :: Lens (Function a) Text Source #

type Rep (Function srcAnnot) Source # 
Instance details

Defined in Language.Thrift.Internal.AST

type Rep (Function srcAnnot) = D1 ('MetaData "Function" "Language.Thrift.Internal.AST" "language-thrift-0.13.0.0-2JnIzIE0JHWGHhFakpJNs3" 'False) (C1 ('MetaCons "Function" 'PrefixI 'True) (((S1 ('MetaSel ('Just "functionOneWay") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool) :*: S1 ('MetaSel ('Just "functionReturnType") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe (TypeReference srcAnnot)))) :*: (S1 ('MetaSel ('Just "functionName") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text) :*: S1 ('MetaSel ('Just "functionParameters") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Field srcAnnot]))) :*: ((S1 ('MetaSel ('Just "functionExceptions") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe [Field srcAnnot])) :*: S1 ('MetaSel ('Just "functionAnnotations") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [TypeAnnotation])) :*: (S1 ('MetaSel ('Just "functionDocstring") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Docstring) :*: S1 ('MetaSel ('Just "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

Instances details
Data TypeAnnotation Source # 
Instance details

Defined in Language.Thrift.Internal.AST

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 :: forall r r'. (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 #

Generic TypeAnnotation Source # 
Instance details

Defined in Language.Thrift.Internal.AST

Associated Types

type Rep TypeAnnotation :: Type -> Type #

Show TypeAnnotation Source # 
Instance details

Defined in Language.Thrift.Internal.AST

Eq TypeAnnotation Source # 
Instance details

Defined in Language.Thrift.Internal.AST

Ord TypeAnnotation Source # 
Instance details

Defined in Language.Thrift.Internal.AST

HasName TypeAnnotation Source # 
Instance details

Defined in Language.Thrift.Internal.AST

HasValue TypeAnnotation (Maybe Text) Source # 
Instance details

Defined in Language.Thrift.Internal.AST

type Rep TypeAnnotation Source # 
Instance details

Defined in Language.Thrift.Internal.AST

type Rep TypeAnnotation = D1 ('MetaData "TypeAnnotation" "Language.Thrift.Internal.AST" "language-thrift-0.13.0.0-2JnIzIE0JHWGHhFakpJNs3" 'False) (C1 ('MetaCons "TypeAnnotation" 'PrefixI 'True) (S1 ('MetaSel ('Just "typeAnnotationName") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text) :*: S1 ('MetaSel ('Just "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 HasAnnotations t where Source #

Methods

annotations :: Lens t [TypeAnnotation] Source #

Instances

Instances details
HasAnnotations (Enum a) Source # 
Instance details

Defined in Language.Thrift.Internal.AST

Methods

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

HasAnnotations (EnumDef a) Source # 
Instance details

Defined in Language.Thrift.Internal.AST

HasAnnotations (Field a) Source # 
Instance details

Defined in Language.Thrift.Internal.AST

Methods

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

HasAnnotations (Function a) Source # 
Instance details

Defined in Language.Thrift.Internal.AST

HasAnnotations (Senum a) Source # 
Instance details

Defined in Language.Thrift.Internal.AST

Methods

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

HasAnnotations (Service a) Source # 
Instance details

Defined in Language.Thrift.Internal.AST

HasAnnotations (Struct a) Source # 
Instance details

Defined in Language.Thrift.Internal.AST

HasAnnotations (Typedef a) Source # 
Instance details

Defined in Language.Thrift.Internal.AST

class HasDocstring t where Source #

Methods

docstring :: Lens t Docstring Source #

Instances

Instances details
HasDocstring (Const a) Source # 
Instance details

Defined in Language.Thrift.Internal.AST

Methods

docstring :: Lens (Const a) Docstring Source #

HasDocstring (Enum a) Source # 
Instance details

Defined in Language.Thrift.Internal.AST

Methods

docstring :: Lens (Enum a) Docstring Source #

HasDocstring (EnumDef a) Source # 
Instance details

Defined in Language.Thrift.Internal.AST

Methods

docstring :: Lens (EnumDef a) Docstring Source #

HasDocstring (Field a) Source # 
Instance details

Defined in Language.Thrift.Internal.AST

Methods

docstring :: Lens (Field a) Docstring Source #

HasDocstring (Function a) Source # 
Instance details

Defined in Language.Thrift.Internal.AST

Methods

docstring :: Lens (Function a) Docstring Source #

HasDocstring (Senum a) Source # 
Instance details

Defined in Language.Thrift.Internal.AST

Methods

docstring :: Lens (Senum a) Docstring Source #

HasDocstring (Service a) Source # 
Instance details

Defined in Language.Thrift.Internal.AST

Methods

docstring :: Lens (Service a) Docstring Source #

HasDocstring (Struct a) Source # 
Instance details

Defined in Language.Thrift.Internal.AST

Methods

docstring :: Lens (Struct a) Docstring Source #

HasDocstring (Typedef a) Source # 
Instance details

Defined in Language.Thrift.Internal.AST

Methods

docstring :: Lens (Typedef a) Docstring Source #

class HasFields t where Source #

Methods

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

Instances

Instances details
HasFields Struct Source # 
Instance details

Defined in Language.Thrift.Internal.AST

Methods

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

class HasName t where Source #

Methods

name :: Lens t Text Source #

Instances

Instances details
HasName TypeAnnotation Source # 
Instance details

Defined in Language.Thrift.Internal.AST

HasName (Const a) Source # 
Instance details

Defined in Language.Thrift.Internal.AST

Methods

name :: Lens (Const a) Text Source #

HasName (Definition a) Source # 
Instance details

Defined in Language.Thrift.Internal.AST

Methods

name :: Lens (Definition a) Text Source #

HasName (Enum a) Source # 
Instance details

Defined in Language.Thrift.Internal.AST

Methods

name :: Lens (Enum a) Text Source #

HasName (EnumDef a) Source # 
Instance details

Defined in Language.Thrift.Internal.AST

Methods

name :: Lens (EnumDef a) Text Source #

HasName (Field a) Source # 
Instance details

Defined in Language.Thrift.Internal.AST

Methods

name :: Lens (Field a) Text Source #

HasName (Function a) Source # 
Instance details

Defined in Language.Thrift.Internal.AST

Methods

name :: Lens (Function a) Text Source #

HasName (Namespace a) Source # 
Instance details

Defined in Language.Thrift.Internal.AST

Methods

name :: Lens (Namespace a) Text Source #

HasName (Senum a) Source # 
Instance details

Defined in Language.Thrift.Internal.AST

Methods

name :: Lens (Senum a) Text Source #

HasName (Service a) Source # 
Instance details

Defined in Language.Thrift.Internal.AST

Methods

name :: Lens (Service a) Text Source #

HasName (Struct a) Source # 
Instance details

Defined in Language.Thrift.Internal.AST

Methods

name :: Lens (Struct a) Text Source #

HasName (Type a) Source # 
Instance details

Defined in Language.Thrift.Internal.AST

Methods

name :: Lens (Type a) Text Source #

HasName (Typedef a) Source # 
Instance details

Defined in Language.Thrift.Internal.AST

Methods

name :: Lens (Typedef a) Text Source #

class HasSrcAnnot t where Source #

Methods

srcAnnot :: Lens (t a) a Source #

Instances

Instances details
HasSrcAnnot Const Source # 
Instance details

Defined in Language.Thrift.Internal.AST

Methods

srcAnnot :: Lens (Const a) a Source #

HasSrcAnnot ConstValue Source # 
Instance details

Defined in Language.Thrift.Internal.AST

Methods

srcAnnot :: Lens (ConstValue a) a Source #

HasSrcAnnot Definition Source # 
Instance details

Defined in Language.Thrift.Internal.AST

Methods

srcAnnot :: Lens (Definition a) a Source #

HasSrcAnnot Enum Source # 
Instance details

Defined in Language.Thrift.Internal.AST

Methods

srcAnnot :: Lens (Enum a) a Source #

HasSrcAnnot EnumDef Source # 
Instance details

Defined in Language.Thrift.Internal.AST

Methods

srcAnnot :: Lens (EnumDef a) a Source #

HasSrcAnnot Field Source # 
Instance details

Defined in Language.Thrift.Internal.AST

Methods

srcAnnot :: Lens (Field a) a Source #

HasSrcAnnot Function Source # 
Instance details

Defined in Language.Thrift.Internal.AST

Methods

srcAnnot :: Lens (Function a) a Source #

HasSrcAnnot Include Source # 
Instance details

Defined in Language.Thrift.Internal.AST

Methods

srcAnnot :: Lens (Include a) a Source #

HasSrcAnnot Namespace Source # 
Instance details

Defined in Language.Thrift.Internal.AST

Methods

srcAnnot :: Lens (Namespace a) a Source #

HasSrcAnnot Senum Source # 
Instance details

Defined in Language.Thrift.Internal.AST

Methods

srcAnnot :: Lens (Senum a) a Source #

HasSrcAnnot Service Source # 
Instance details

Defined in Language.Thrift.Internal.AST

Methods

srcAnnot :: Lens (Service a) a Source #

HasSrcAnnot Struct Source # 
Instance details

Defined in Language.Thrift.Internal.AST

Methods

srcAnnot :: Lens (Struct a) a Source #

HasSrcAnnot Type Source # 
Instance details

Defined in Language.Thrift.Internal.AST

Methods

srcAnnot :: Lens (Type a) a Source #

HasSrcAnnot TypeReference Source # 
Instance details

Defined in Language.Thrift.Internal.AST

Methods

srcAnnot :: Lens (TypeReference a) a Source #

HasSrcAnnot Typedef Source # 
Instance details

Defined in Language.Thrift.Internal.AST

Methods

srcAnnot :: Lens (Typedef a) a Source #

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

Methods

value :: Lens s a Source #

Instances

Instances details
HasValue TypeAnnotation (Maybe Text) Source # 
Instance details

Defined in Language.Thrift.Internal.AST

HasValue (Const a) (ConstValue a) Source # 
Instance details

Defined in Language.Thrift.Internal.AST

Methods

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

HasValue (EnumDef a) (Maybe Integer) Source # 
Instance details

Defined in Language.Thrift.Internal.AST

Methods

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

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

Methods

values :: Lens s a Source #

Instances

Instances details
HasValues (Enum a) [EnumDef a] Source # 
Instance details

Defined in Language.Thrift.Internal.AST

Methods

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

HasValues (Senum a) [Text] Source # 
Instance details

Defined in Language.Thrift.Internal.AST

Methods

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

class HasValueType t where Source #

Methods

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

Instances

Instances details
HasValueType Const Source # 
Instance details

Defined in Language.Thrift.Internal.AST

Methods

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

HasValueType Field Source # 
Instance details

Defined in Language.Thrift.Internal.AST

Methods

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