module Language.Avro.Types
( module Language.Avro.Types,
Schema (..),
)
where
import Data.Avro.Schema
import Data.Avro.Types.Value
import Data.Set
import qualified Data.Text as T
data Protocol
= Protocol
{ ns :: Maybe Namespace,
pname :: T.Text,
imports :: Set ImportType,
types :: Set Schema,
messages :: Set Method
}
deriving (Eq, Show, Ord)
instance Semigroup Protocol where
p1 <> p2 =
Protocol
(ns p1)
(pname p1)
(imports p1 <> imports p2)
(types p1 <> types p2)
(messages p1 <> messages p2)
newtype Namespace
= Namespace [T.Text]
deriving (Eq, Show, Ord)
type Aliases = [TypeName]
data Annotation
= Annotation
{ ann :: T.Text,
abody :: T.Text
}
deriving (Eq, Show)
data ImportType
= IdlImport T.Text
| ProtocolImport T.Text
| SchemaImport T.Text
deriving (Eq, Show, Ord)
data Argument
= Argument
{ atype :: Schema,
aname :: T.Text
}
deriving (Eq, Show, Ord)
data Method
= Method
{ mname :: T.Text,
args :: [Argument],
result :: Schema,
throws :: Schema,
oneway :: Bool
}
deriving (Eq, Show, Ord)