module Rattletrap.Type.Attribute.UniqueId where

import qualified Rattletrap.BitGet as BitGet
import qualified Rattletrap.BitPut as BitPut
import qualified Rattletrap.Schema as Schema
import qualified Rattletrap.Type.RemoteId as RemoteId
import qualified Rattletrap.Type.U8 as U8
import qualified Rattletrap.Type.Version as Version
import qualified Rattletrap.Utility.Json as Json

data UniqueId = UniqueId
  { UniqueId -> U8
systemId :: U8.U8,
    UniqueId -> RemoteId
remoteId :: RemoteId.RemoteId,
    UniqueId -> U8
localId :: U8.U8
  }
  deriving (UniqueId -> UniqueId -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: UniqueId -> UniqueId -> Bool
$c/= :: UniqueId -> UniqueId -> Bool
== :: UniqueId -> UniqueId -> Bool
$c== :: UniqueId -> UniqueId -> Bool
Eq, Int -> UniqueId -> ShowS
[UniqueId] -> ShowS
UniqueId -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [UniqueId] -> ShowS
$cshowList :: [UniqueId] -> ShowS
show :: UniqueId -> String
$cshow :: UniqueId -> String
showsPrec :: Int -> UniqueId -> ShowS
$cshowsPrec :: Int -> UniqueId -> ShowS
Show)

instance Json.FromJSON UniqueId where
  parseJSON :: Value -> Parser UniqueId
parseJSON = forall a. String -> (Object -> Parser a) -> Value -> Parser a
Json.withObject String
"UniqueId" forall a b. (a -> b) -> a -> b
$ \Object
object -> do
    U8
systemId <- forall value. FromJSON value => Object -> String -> Parser value
Json.required Object
object String
"system_id"
    RemoteId
remoteId <- forall value. FromJSON value => Object -> String -> Parser value
Json.required Object
object String
"remote_id"
    U8
localId <- forall value. FromJSON value => Object -> String -> Parser value
Json.required Object
object String
"local_id"
    forall (f :: * -> *) a. Applicative f => a -> f a
pure UniqueId {U8
systemId :: U8
systemId :: U8
systemId, RemoteId
remoteId :: RemoteId
remoteId :: RemoteId
remoteId, U8
localId :: U8
localId :: U8
localId}

instance Json.ToJSON UniqueId where
  toJSON :: UniqueId -> Value
toJSON UniqueId
x =
    [(Key, Value)] -> Value
Json.object
      [ forall value pair.
(ToJSON value, KeyValue pair) =>
String -> value -> pair
Json.pair String
"system_id" forall a b. (a -> b) -> a -> b
$ UniqueId -> U8
systemId UniqueId
x,
        forall value pair.
(ToJSON value, KeyValue pair) =>
String -> value -> pair
Json.pair String
"remote_id" forall a b. (a -> b) -> a -> b
$ UniqueId -> RemoteId
remoteId UniqueId
x,
        forall value pair.
(ToJSON value, KeyValue pair) =>
String -> value -> pair
Json.pair String
"local_id" forall a b. (a -> b) -> a -> b
$ UniqueId -> U8
localId UniqueId
x
      ]

schema :: Schema.Schema
schema :: Schema
schema =
  String -> Value -> Schema
Schema.named String
"attribute-unique-id" forall a b. (a -> b) -> a -> b
$
    [((Key, Value), Bool)] -> Value
Schema.object
      [ (forall value pair.
(ToJSON value, KeyValue pair) =>
String -> value -> pair
Json.pair String
"system_id" forall a b. (a -> b) -> a -> b
$ Schema -> Value
Schema.ref Schema
U8.schema, Bool
True),
        (forall value pair.
(ToJSON value, KeyValue pair) =>
String -> value -> pair
Json.pair String
"remote_id" forall a b. (a -> b) -> a -> b
$ Schema -> Value
Schema.ref Schema
RemoteId.schema, Bool
True),
        (forall value pair.
(ToJSON value, KeyValue pair) =>
String -> value -> pair
Json.pair String
"local_id" forall a b. (a -> b) -> a -> b
$ Schema -> Value
Schema.ref Schema
U8.schema, Bool
True)
      ]

bitPut :: UniqueId -> BitPut.BitPut
bitPut :: UniqueId -> BitPut
bitPut UniqueId
uniqueIdAttribute =
  U8 -> BitPut
U8.bitPut (UniqueId -> U8
systemId UniqueId
uniqueIdAttribute)
    forall a. Semigroup a => a -> a -> a
<> RemoteId -> BitPut
RemoteId.bitPut (UniqueId -> RemoteId
remoteId UniqueId
uniqueIdAttribute)
    forall a. Semigroup a => a -> a -> a
<> U8 -> BitPut
U8.bitPut (UniqueId -> U8
localId UniqueId
uniqueIdAttribute)

bitGet :: Version.Version -> BitGet.BitGet UniqueId
bitGet :: Version -> BitGet UniqueId
bitGet Version
version = forall a. String -> BitGet a -> BitGet a
BitGet.label String
"UniqueId" forall a b. (a -> b) -> a -> b
$ do
  U8
systemId <- forall a. String -> BitGet a -> BitGet a
BitGet.label String
"systemId" BitGet U8
U8.bitGet
  RemoteId
remoteId <- forall a. String -> BitGet a -> BitGet a
BitGet.label String
"remoteId" forall a b. (a -> b) -> a -> b
$ Version -> U8 -> BitGet RemoteId
RemoteId.bitGet Version
version U8
systemId
  U8
localId <- forall a. String -> BitGet a -> BitGet a
BitGet.label String
"localId" BitGet U8
U8.bitGet
  forall (f :: * -> *) a. Applicative f => a -> f a
pure UniqueId {U8
systemId :: U8
systemId :: U8
systemId, RemoteId
remoteId :: RemoteId
remoteId :: RemoteId
remoteId, U8
localId :: U8
localId :: U8
localId}