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