-- | Language definition for AVRO (@.avdl@) files,
--   as defined in <http://avro.apache.org/docs/1.8.2/spec.html>.
module Language.Avro.Types
  ( module Language.Avro.Types,
    Schema (..),
  )
where

import Data.Avro
import Data.Set
import qualified Data.Text as T

-- | Whole definition of protocol.
data Protocol
  = Protocol
      { Protocol -> Maybe Namespace
ns :: Maybe Namespace,
        Protocol -> Text
pname :: T.Text,
        Protocol -> Set ImportType
imports :: Set ImportType,
        Protocol -> Set Schema
types :: Set Schema,
        Protocol -> Set Method
messages :: Set Method
      }
  deriving (Protocol -> Protocol -> Bool
(Protocol -> Protocol -> Bool)
-> (Protocol -> Protocol -> Bool) -> Eq Protocol
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Protocol -> Protocol -> Bool
$c/= :: Protocol -> Protocol -> Bool
== :: Protocol -> Protocol -> Bool
$c== :: Protocol -> Protocol -> Bool
Eq, Int -> Protocol -> ShowS
[Protocol] -> ShowS
Protocol -> String
(Int -> Protocol -> ShowS)
-> (Protocol -> String) -> ([Protocol] -> ShowS) -> Show Protocol
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Protocol] -> ShowS
$cshowList :: [Protocol] -> ShowS
show :: Protocol -> String
$cshow :: Protocol -> String
showsPrec :: Int -> Protocol -> ShowS
$cshowsPrec :: Int -> Protocol -> ShowS
Show, Eq Protocol
Eq Protocol =>
(Protocol -> Protocol -> Ordering)
-> (Protocol -> Protocol -> Bool)
-> (Protocol -> Protocol -> Bool)
-> (Protocol -> Protocol -> Bool)
-> (Protocol -> Protocol -> Bool)
-> (Protocol -> Protocol -> Protocol)
-> (Protocol -> Protocol -> Protocol)
-> Ord Protocol
Protocol -> Protocol -> Bool
Protocol -> Protocol -> Ordering
Protocol -> Protocol -> Protocol
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: Protocol -> Protocol -> Protocol
$cmin :: Protocol -> Protocol -> Protocol
max :: Protocol -> Protocol -> Protocol
$cmax :: Protocol -> Protocol -> Protocol
>= :: Protocol -> Protocol -> Bool
$c>= :: Protocol -> Protocol -> Bool
> :: Protocol -> Protocol -> Bool
$c> :: Protocol -> Protocol -> Bool
<= :: Protocol -> Protocol -> Bool
$c<= :: Protocol -> Protocol -> Bool
< :: Protocol -> Protocol -> Bool
$c< :: Protocol -> Protocol -> Bool
compare :: Protocol -> Protocol -> Ordering
$ccompare :: Protocol -> Protocol -> Ordering
$cp1Ord :: Eq Protocol
Ord)

instance Semigroup Protocol where
  p1 :: Protocol
p1 <> :: Protocol -> Protocol -> Protocol
<> p2 :: Protocol
p2 =
    Maybe Namespace
-> Text -> Set ImportType -> Set Schema -> Set Method -> Protocol
Protocol
      (Protocol -> Maybe Namespace
ns Protocol
p1)
      (Protocol -> Text
pname Protocol
p1)
      (Protocol -> Set ImportType
imports Protocol
p1 Set ImportType -> Set ImportType -> Set ImportType
forall a. Semigroup a => a -> a -> a
<> Protocol -> Set ImportType
imports Protocol
p2)
      (Protocol -> Set Schema
types Protocol
p1 Set Schema -> Set Schema -> Set Schema
forall a. Semigroup a => a -> a -> a
<> Protocol -> Set Schema
types Protocol
p2)
      (Protocol -> Set Method
messages Protocol
p1 Set Method -> Set Method -> Set Method
forall a. Semigroup a => a -> a -> a
<> Protocol -> Set Method
messages Protocol
p2)

-- | Newtype for the namespace of methods and protocols.
newtype Namespace
  = Namespace [T.Text]
  deriving (Namespace -> Namespace -> Bool
(Namespace -> Namespace -> Bool)
-> (Namespace -> Namespace -> Bool) -> Eq Namespace
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Namespace -> Namespace -> Bool
$c/= :: Namespace -> Namespace -> Bool
== :: Namespace -> Namespace -> Bool
$c== :: Namespace -> Namespace -> Bool
Eq, Int -> Namespace -> ShowS
[Namespace] -> ShowS
Namespace -> String
(Int -> Namespace -> ShowS)
-> (Namespace -> String)
-> ([Namespace] -> ShowS)
-> Show Namespace
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Namespace] -> ShowS
$cshowList :: [Namespace] -> ShowS
show :: Namespace -> String
$cshow :: Namespace -> String
showsPrec :: Int -> Namespace -> ShowS
$cshowsPrec :: Int -> Namespace -> ShowS
Show, Eq Namespace
Eq Namespace =>
(Namespace -> Namespace -> Ordering)
-> (Namespace -> Namespace -> Bool)
-> (Namespace -> Namespace -> Bool)
-> (Namespace -> Namespace -> Bool)
-> (Namespace -> Namespace -> Bool)
-> (Namespace -> Namespace -> Namespace)
-> (Namespace -> Namespace -> Namespace)
-> Ord Namespace
Namespace -> Namespace -> Bool
Namespace -> Namespace -> Ordering
Namespace -> Namespace -> Namespace
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: Namespace -> Namespace -> Namespace
$cmin :: Namespace -> Namespace -> Namespace
max :: Namespace -> Namespace -> Namespace
$cmax :: Namespace -> Namespace -> Namespace
>= :: Namespace -> Namespace -> Bool
$c>= :: Namespace -> Namespace -> Bool
> :: Namespace -> Namespace -> Bool
$c> :: Namespace -> Namespace -> Bool
<= :: Namespace -> Namespace -> Bool
$c<= :: Namespace -> Namespace -> Bool
< :: Namespace -> Namespace -> Bool
$c< :: Namespace -> Namespace -> Bool
compare :: Namespace -> Namespace -> Ordering
$ccompare :: Namespace -> Namespace -> Ordering
$cp1Ord :: Eq Namespace
Ord)

type Aliases = [TypeName]

-- | Type for special annotations.
data Annotation
  = Annotation
      { Annotation -> Text
ann :: T.Text,
        Annotation -> Text
abody :: T.Text
      }
  deriving (Annotation -> Annotation -> Bool
(Annotation -> Annotation -> Bool)
-> (Annotation -> Annotation -> Bool) -> Eq Annotation
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Annotation -> Annotation -> Bool
$c/= :: Annotation -> Annotation -> Bool
== :: Annotation -> Annotation -> Bool
$c== :: Annotation -> Annotation -> Bool
Eq, Int -> Annotation -> ShowS
[Annotation] -> ShowS
Annotation -> String
(Int -> Annotation -> ShowS)
-> (Annotation -> String)
-> ([Annotation] -> ShowS)
-> Show Annotation
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Annotation] -> ShowS
$cshowList :: [Annotation] -> ShowS
show :: Annotation -> String
$cshow :: Annotation -> String
showsPrec :: Int -> Annotation -> ShowS
$cshowsPrec :: Int -> Annotation -> ShowS
Show)

-- | Type for the possible import types in 'Protocol'.
data ImportType
  = IdlImport T.Text
  | ProtocolImport T.Text
  | SchemaImport T.Text
  deriving (ImportType -> ImportType -> Bool
(ImportType -> ImportType -> Bool)
-> (ImportType -> ImportType -> Bool) -> Eq ImportType
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ImportType -> ImportType -> Bool
$c/= :: ImportType -> ImportType -> Bool
== :: ImportType -> ImportType -> Bool
$c== :: ImportType -> ImportType -> Bool
Eq, Int -> ImportType -> ShowS
[ImportType] -> ShowS
ImportType -> String
(Int -> ImportType -> ShowS)
-> (ImportType -> String)
-> ([ImportType] -> ShowS)
-> Show ImportType
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ImportType] -> ShowS
$cshowList :: [ImportType] -> ShowS
show :: ImportType -> String
$cshow :: ImportType -> String
showsPrec :: Int -> ImportType -> ShowS
$cshowsPrec :: Int -> ImportType -> ShowS
Show, Eq ImportType
Eq ImportType =>
(ImportType -> ImportType -> Ordering)
-> (ImportType -> ImportType -> Bool)
-> (ImportType -> ImportType -> Bool)
-> (ImportType -> ImportType -> Bool)
-> (ImportType -> ImportType -> Bool)
-> (ImportType -> ImportType -> ImportType)
-> (ImportType -> ImportType -> ImportType)
-> Ord ImportType
ImportType -> ImportType -> Bool
ImportType -> ImportType -> Ordering
ImportType -> ImportType -> ImportType
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: ImportType -> ImportType -> ImportType
$cmin :: ImportType -> ImportType -> ImportType
max :: ImportType -> ImportType -> ImportType
$cmax :: ImportType -> ImportType -> ImportType
>= :: ImportType -> ImportType -> Bool
$c>= :: ImportType -> ImportType -> Bool
> :: ImportType -> ImportType -> Bool
$c> :: ImportType -> ImportType -> Bool
<= :: ImportType -> ImportType -> Bool
$c<= :: ImportType -> ImportType -> Bool
< :: ImportType -> ImportType -> Bool
$c< :: ImportType -> ImportType -> Bool
compare :: ImportType -> ImportType -> Ordering
$ccompare :: ImportType -> ImportType -> Ordering
$cp1Ord :: Eq ImportType
Ord)

-- | Helper type for the arguments of 'Method'.
data Argument
  = Argument
      { Argument -> Schema
atype :: Schema,
        Argument -> Text
aname :: T.Text
      }
  deriving (Argument -> Argument -> Bool
(Argument -> Argument -> Bool)
-> (Argument -> Argument -> Bool) -> Eq Argument
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Argument -> Argument -> Bool
$c/= :: Argument -> Argument -> Bool
== :: Argument -> Argument -> Bool
$c== :: Argument -> Argument -> Bool
Eq, Int -> Argument -> ShowS
[Argument] -> ShowS
Argument -> String
(Int -> Argument -> ShowS)
-> (Argument -> String) -> ([Argument] -> ShowS) -> Show Argument
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Argument] -> ShowS
$cshowList :: [Argument] -> ShowS
show :: Argument -> String
$cshow :: Argument -> String
showsPrec :: Int -> Argument -> ShowS
$cshowsPrec :: Int -> Argument -> ShowS
Show, Eq Argument
Eq Argument =>
(Argument -> Argument -> Ordering)
-> (Argument -> Argument -> Bool)
-> (Argument -> Argument -> Bool)
-> (Argument -> Argument -> Bool)
-> (Argument -> Argument -> Bool)
-> (Argument -> Argument -> Argument)
-> (Argument -> Argument -> Argument)
-> Ord Argument
Argument -> Argument -> Bool
Argument -> Argument -> Ordering
Argument -> Argument -> Argument
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: Argument -> Argument -> Argument
$cmin :: Argument -> Argument -> Argument
max :: Argument -> Argument -> Argument
$cmax :: Argument -> Argument -> Argument
>= :: Argument -> Argument -> Bool
$c>= :: Argument -> Argument -> Bool
> :: Argument -> Argument -> Bool
$c> :: Argument -> Argument -> Bool
<= :: Argument -> Argument -> Bool
$c<= :: Argument -> Argument -> Bool
< :: Argument -> Argument -> Bool
$c< :: Argument -> Argument -> Bool
compare :: Argument -> Argument -> Ordering
$ccompare :: Argument -> Argument -> Ordering
$cp1Ord :: Eq Argument
Ord)

-- | Type for methods/messages that belong to a protocol.
data Method
  = Method
      { Method -> Text
mname :: T.Text,
        Method -> [Argument]
args :: [Argument],
        Method -> Schema
result :: Schema,
        Method -> Schema
throws :: Schema,
        Method -> Bool
oneway :: Bool
      }
  deriving (Method -> Method -> Bool
(Method -> Method -> Bool)
-> (Method -> Method -> Bool) -> Eq Method
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Method -> Method -> Bool
$c/= :: Method -> Method -> Bool
== :: Method -> Method -> Bool
$c== :: Method -> Method -> Bool
Eq, Int -> Method -> ShowS
[Method] -> ShowS
Method -> String
(Int -> Method -> ShowS)
-> (Method -> String) -> ([Method] -> ShowS) -> Show Method
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Method] -> ShowS
$cshowList :: [Method] -> ShowS
show :: Method -> String
$cshow :: Method -> String
showsPrec :: Int -> Method -> ShowS
$cshowsPrec :: Int -> Method -> ShowS
Show, Eq Method
Eq Method =>
(Method -> Method -> Ordering)
-> (Method -> Method -> Bool)
-> (Method -> Method -> Bool)
-> (Method -> Method -> Bool)
-> (Method -> Method -> Bool)
-> (Method -> Method -> Method)
-> (Method -> Method -> Method)
-> Ord Method
Method -> Method -> Bool
Method -> Method -> Ordering
Method -> Method -> Method
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: Method -> Method -> Method
$cmin :: Method -> Method -> Method
max :: Method -> Method -> Method
$cmax :: Method -> Method -> Method
>= :: Method -> Method -> Bool
$c>= :: Method -> Method -> Bool
> :: Method -> Method -> Bool
$c> :: Method -> Method -> Bool
<= :: Method -> Method -> Bool
$c<= :: Method -> Method -> Bool
< :: Method -> Method -> Bool
$c< :: Method -> Method -> Bool
compare :: Method -> Method -> Ordering
$ccompare :: Method -> Method -> Ordering
$cp1Ord :: Eq Method
Ord)