Safe Haskell | Safe |
---|---|
Language | Haskell2010 |
Elements in the Protocol Buffers syntax, as defined in https://developers.google.com/protocol-buffers/docs/reference/proto3-spec
Synopsis
- type Identifier = Text
- type FullIdentifier = [Identifier]
- data ProtoBuf = ProtoBuf {
- syntax :: Maybe Text
- package :: Maybe FullIdentifier
- imports :: [(ImportType, Text)]
- options :: [Option]
- types :: [TypeDeclaration]
- services :: [ServiceDeclaration]
- declsToProtoBuf :: [Declaration] -> ProtoBuf
- safeHead :: [a] -> Maybe a
- data Declaration where
- DSyntax :: Text -> Declaration
- DImport :: ImportType -> Text -> Declaration
- DPackage :: FullIdentifier -> Declaration
- DOption :: Option -> Declaration
- DType :: TypeDeclaration -> Declaration
- DService :: ServiceDeclaration -> Declaration
- data Option where
- Option :: FullIdentifier -> Constant -> Option
- data TypeDeclaration where
- DEnum :: Identifier -> [Option] -> [EnumField] -> TypeDeclaration
- DMessage :: Identifier -> [Option] -> [Reserved] -> [MessageField] -> [TypeDeclaration] -> TypeDeclaration
- data ServiceDeclaration where
- Service :: Identifier -> [Option] -> [Method] -> ServiceDeclaration
- data Method where
- Method :: Identifier -> Repetition -> FieldType -> Repetition -> FieldType -> [Option] -> Method
- data ImportType
- data Constant where
- data EnumField where
- EnumField :: FieldName -> FieldNumber -> [Option] -> EnumField
- type TypeName = FullIdentifier
- data FieldType
- type FieldName = Identifier
- type FieldNumber = Int
- data MessageField where
- NormalField :: Repetition -> FieldType -> FieldName -> FieldNumber -> [Option] -> MessageField
- OneOfField :: FieldName -> [MessageField] -> MessageField
- MapField :: FieldType -> FieldType -> FieldName -> FieldNumber -> [Option] -> MessageField
- data Repetition
- pattern Stream :: Repetition
- type Reserved = [ReservedValue]
- data ReservedValue where
- RInt :: Int -> ReservedValue
- RRange :: Int -> Int -> ReservedValue
- RName :: Identifier -> ReservedValue
Documentation
type Identifier = Text Source #
type FullIdentifier = [Identifier] Source #
Whole definition, in which declarations are sorted out by their form.
ProtoBuf | |
|
declsToProtoBuf :: [Declaration] -> ProtoBuf Source #
data Declaration where Source #
Declarations, that is, anything which may appear in the top-level.
DSyntax :: Text -> Declaration | |
DImport :: ImportType -> Text -> Declaration | |
DPackage :: FullIdentifier -> Declaration | |
DOption :: Option -> Declaration | |
DType :: TypeDeclaration -> Declaration | |
DService :: ServiceDeclaration -> Declaration |
Instances
Eq Declaration Source # | |
Defined in Language.ProtocolBuffers.Types (==) :: Declaration -> Declaration -> Bool # (/=) :: Declaration -> Declaration -> Bool # | |
Show Declaration Source # | |
Defined in Language.ProtocolBuffers.Types showsPrec :: Int -> Declaration -> ShowS # show :: Declaration -> String # showList :: [Declaration] -> ShowS # |
Option :: FullIdentifier -> Constant -> Option |
data TypeDeclaration where Source #
DEnum :: Identifier -> [Option] -> [EnumField] -> TypeDeclaration | |
DMessage :: Identifier -> [Option] -> [Reserved] -> [MessageField] -> [TypeDeclaration] -> TypeDeclaration |
Instances
Eq TypeDeclaration Source # | |
Defined in Language.ProtocolBuffers.Types (==) :: TypeDeclaration -> TypeDeclaration -> Bool # (/=) :: TypeDeclaration -> TypeDeclaration -> Bool # | |
Show TypeDeclaration Source # | |
Defined in Language.ProtocolBuffers.Types showsPrec :: Int -> TypeDeclaration -> ShowS # show :: TypeDeclaration -> String # showList :: [TypeDeclaration] -> ShowS # |
data ServiceDeclaration where Source #
Service :: Identifier -> [Option] -> [Method] -> ServiceDeclaration |
Instances
Eq ServiceDeclaration Source # | |
Defined in Language.ProtocolBuffers.Types (==) :: ServiceDeclaration -> ServiceDeclaration -> Bool # (/=) :: ServiceDeclaration -> ServiceDeclaration -> Bool # | |
Show ServiceDeclaration Source # | |
Defined in Language.ProtocolBuffers.Types showsPrec :: Int -> ServiceDeclaration -> ShowS # show :: ServiceDeclaration -> String # showList :: [ServiceDeclaration] -> ShowS # |
Method :: Identifier -> Repetition -> FieldType -> Repetition -> FieldType -> [Option] -> Method |
data ImportType Source #
Instances
Eq ImportType Source # | |
Defined in Language.ProtocolBuffers.Types (==) :: ImportType -> ImportType -> Bool # (/=) :: ImportType -> ImportType -> Bool # | |
Show ImportType Source # | |
Defined in Language.ProtocolBuffers.Types showsPrec :: Int -> ImportType -> ShowS # show :: ImportType -> String # showList :: [ImportType] -> ShowS # |
KIdentifier :: FullIdentifier -> Constant | |
KInt :: Integer -> Constant | |
KFloat :: Float -> Constant | |
KString :: Text -> Constant | |
KBool :: Bool -> Constant | |
KObject :: [(Text, Constant)] -> Constant |
EnumField :: FieldName -> FieldNumber -> [Option] -> EnumField |
type TypeName = FullIdentifier Source #
TInt32 | |
TInt64 | |
TUInt32 | |
TUInt64 | |
TSInt32 | |
TSInt64 | |
TFixed32 | |
TFixed64 | |
TSFixed32 | |
TSFixed64 | |
TDouble | |
TBool | |
TString | |
TBytes | |
TOther TypeName |
type FieldName = Identifier Source #
type FieldNumber = Int Source #
data MessageField where Source #
NormalField :: Repetition -> FieldType -> FieldName -> FieldNumber -> [Option] -> MessageField | |
OneOfField :: FieldName -> [MessageField] -> MessageField | |
MapField :: FieldType -> FieldType -> FieldName -> FieldNumber -> [Option] -> MessageField |
Instances
Eq MessageField Source # | |
Defined in Language.ProtocolBuffers.Types (==) :: MessageField -> MessageField -> Bool # (/=) :: MessageField -> MessageField -> Bool # | |
Show MessageField Source # | |
Defined in Language.ProtocolBuffers.Types showsPrec :: Int -> MessageField -> ShowS # show :: MessageField -> String # showList :: [MessageField] -> ShowS # |
data Repetition Source #
Instances
Eq Repetition Source # | |
Defined in Language.ProtocolBuffers.Types (==) :: Repetition -> Repetition -> Bool # (/=) :: Repetition -> Repetition -> Bool # | |
Show Repetition Source # | |
Defined in Language.ProtocolBuffers.Types showsPrec :: Int -> Repetition -> ShowS # show :: Repetition -> String # showList :: [Repetition] -> ShowS # |
pattern Stream :: Repetition Source #
type Reserved = [ReservedValue] Source #
data ReservedValue where Source #
RInt :: Int -> ReservedValue | |
RRange :: Int -> Int -> ReservedValue | |
RName :: Identifier -> ReservedValue |
Instances
Eq ReservedValue Source # | |
Defined in Language.ProtocolBuffers.Types (==) :: ReservedValue -> ReservedValue -> Bool # (/=) :: ReservedValue -> ReservedValue -> Bool # | |
Show ReservedValue Source # | |
Defined in Language.ProtocolBuffers.Types showsPrec :: Int -> ReservedValue -> ShowS # show :: ReservedValue -> String # showList :: [ReservedValue] -> ShowS # |