{-# LANGUAGE DerivingStrategies #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
module FlatBuffers.Internal.Compiler.ValidSyntaxTree
(
FlatBuffers.Internal.Compiler.SyntaxTree.Namespace(..)
, FlatBuffers.Internal.Compiler.SyntaxTree.Ident(..)
, FlatBuffers.Internal.Compiler.SyntaxTree.TypeRef(..)
, FlatBuffers.Internal.Compiler.SyntaxTree.HasIdent(..)
, EnumDecl(..)
, EnumVal(..)
, EnumType(..)
, StructDecl(..)
, StructField(..)
, StructFieldType(..)
, DefaultVal(..)
, Required(..)
, IsRoot(..)
, TableDecl(..)
, TableField(..)
, TableFieldType(..)
, VectorElementType(..)
, UnionDecl(..)
, UnionVal(..)
) where
import Data.Int
import Data.List.NonEmpty ( NonEmpty )
import Data.Scientific ( Scientific )
import Data.String ( IsString(..) )
import Data.Text ( Text )
import Data.Word
import FlatBuffers.Internal.Compiler.SyntaxTree ( HasIdent(..), Ident(..), Namespace(..), TypeRef(..) )
import FlatBuffers.Internal.Types
instance HasIdent EnumDecl where getIdent = enumIdent
instance HasIdent EnumVal where getIdent = enumValIdent
instance HasIdent StructDecl where getIdent = structIdent
instance HasIdent StructField where getIdent = structFieldIdent
instance HasIdent TableDecl where getIdent = tableIdent
instance HasIdent TableField where getIdent = tableFieldIdent
instance HasIdent UnionDecl where getIdent = unionIdent
instance HasIdent UnionVal where getIdent = unionValIdent
data EnumDecl = EnumDecl
{ enumIdent :: !Ident
, enumType :: !EnumType
, enumVals :: !(NonEmpty EnumVal)
} deriving (Show, Eq)
data EnumVal = EnumVal
{ enumValIdent :: !Ident
, enumValInt :: !Integer
} deriving (Show, Eq)
data EnumType
= EInt8
| EInt16
| EInt32
| EInt64
| EWord8
| EWord16
| EWord32
| EWord64
deriving (Show, Eq)
data StructDecl = StructDecl
{ structIdent :: !Ident
, structAlignment :: !Alignment
, structSize :: !InlineSize
, structFields :: !(NonEmpty StructField)
} deriving (Show, Eq)
data StructField = StructField
{ structFieldIdent :: !Ident
, structFieldPadding :: !Word8
, structFieldOffset :: !Word16
, structFieldType :: !StructFieldType
} deriving (Show, Eq)
data StructFieldType
= SInt8
| SInt16
| SInt32
| SInt64
| SWord8
| SWord16
| SWord32
| SWord64
| SFloat
| SDouble
| SBool
| SEnum
!TypeRef
!EnumType
| SStruct !(Namespace, StructDecl)
deriving (Show, Eq)
newtype DefaultVal a = DefaultVal a
deriving newtype (Eq, Show, Num, IsString, Ord, Enum, Real, Integral, Fractional)
data Required = Req | Opt
deriving (Eq, Show)
data IsRoot
= NotRoot
| IsRoot !(Maybe Text)
deriving (Eq, Show)
data TableDecl = TableDecl
{ tableIdent :: !Ident
, tableIsRoot :: !IsRoot
, tableFields :: ![TableField]
} deriving (Eq, Show)
data TableField = TableField
{ tableFieldId :: !Integer
, tableFieldIdent :: !Ident
, tableFieldType :: !TableFieldType
, tableFieldDeprecated :: !Bool
} deriving (Eq, Show)
data TableFieldType
= TInt8 !(DefaultVal Int8)
| TInt16 !(DefaultVal Int16)
| TInt32 !(DefaultVal Int32)
| TInt64 !(DefaultVal Int64)
| TWord8 !(DefaultVal Word8)
| TWord16 !(DefaultVal Word16)
| TWord32 !(DefaultVal Word32)
| TWord64 !(DefaultVal Word64)
| TFloat !(DefaultVal Scientific)
| TDouble !(DefaultVal Scientific)
| TBool !(DefaultVal Bool)
| TString !Required
| TEnum !TypeRef !EnumType !(DefaultVal Integer)
| TStruct !TypeRef !Required
| TTable !TypeRef !Required
| TUnion !TypeRef !Required
| TVector !Required !VectorElementType
deriving (Eq, Show)
data VectorElementType
= VInt8
| VInt16
| VInt32
| VInt64
| VWord8
| VWord16
| VWord32
| VWord64
| VFloat
| VDouble
| VBool
| VString
| VEnum !TypeRef !EnumType
| VStruct !TypeRef
| VTable !TypeRef
| VUnion !TypeRef
deriving (Eq, Show)
data UnionDecl = UnionDecl
{ unionIdent :: !Ident
, unionVals :: !(NonEmpty UnionVal)
} deriving (Show, Eq)
data UnionVal = UnionVal
{ unionValIdent :: !Ident
, unionValTableRef :: !TypeRef
} deriving (Show, Eq)