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
(UniqueId -> UniqueId -> Bool)
-> (UniqueId -> UniqueId -> Bool) -> Eq UniqueId
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: UniqueId -> UniqueId -> Bool
== :: UniqueId -> UniqueId -> Bool
$c/= :: UniqueId -> UniqueId -> Bool
/= :: UniqueId -> UniqueId -> Bool
Eq, Int -> UniqueId -> ShowS
[UniqueId] -> ShowS
UniqueId -> String
(Int -> UniqueId -> ShowS)
-> (UniqueId -> String) -> ([UniqueId] -> ShowS) -> Show UniqueId
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> UniqueId -> ShowS
showsPrec :: Int -> UniqueId -> ShowS
$cshow :: UniqueId -> String
show :: UniqueId -> String
$cshowList :: [UniqueId] -> ShowS
showList :: [UniqueId] -> ShowS
Show)

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

instance Json.ToJSON UniqueId where
  toJSON :: UniqueId -> Value
toJSON UniqueId
x =
    [(Key, Value)] -> Value
Json.object
      [ String -> U8 -> (Key, Value)
forall value e p.
(ToJSON value, KeyValue e p) =>
String -> value -> p
Json.pair String
"system_id" (U8 -> (Key, Value)) -> U8 -> (Key, Value)
forall a b. (a -> b) -> a -> b
$ UniqueId -> U8
systemId UniqueId
x,
        String -> RemoteId -> (Key, Value)
forall value e p.
(ToJSON value, KeyValue e p) =>
String -> value -> p
Json.pair String
"remote_id" (RemoteId -> (Key, Value)) -> RemoteId -> (Key, Value)
forall a b. (a -> b) -> a -> b
$ UniqueId -> RemoteId
remoteId UniqueId
x,
        String -> U8 -> (Key, Value)
forall value e p.
(ToJSON value, KeyValue e p) =>
String -> value -> p
Json.pair String
"local_id" (U8 -> (Key, Value)) -> U8 -> (Key, Value)
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" (Value -> Schema) -> Value -> Schema
forall a b. (a -> b) -> a -> b
$
    [((Key, Value), Bool)] -> Value
Schema.object
      [ (String -> Value -> (Key, Value)
forall value e p.
(ToJSON value, KeyValue e p) =>
String -> value -> p
Json.pair String
"system_id" (Value -> (Key, Value)) -> Value -> (Key, Value)
forall a b. (a -> b) -> a -> b
$ Schema -> Value
Schema.ref Schema
U8.schema, Bool
True),
        (String -> Value -> (Key, Value)
forall value e p.
(ToJSON value, KeyValue e p) =>
String -> value -> p
Json.pair String
"remote_id" (Value -> (Key, Value)) -> Value -> (Key, Value)
forall a b. (a -> b) -> a -> b
$ Schema -> Value
Schema.ref Schema
RemoteId.schema, Bool
True),
        (String -> Value -> (Key, Value)
forall value e p.
(ToJSON value, KeyValue e p) =>
String -> value -> p
Json.pair String
"local_id" (Value -> (Key, Value)) -> Value -> (Key, Value)
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)
    BitPut -> BitPut -> BitPut
forall a. Semigroup a => a -> a -> a
<> RemoteId -> BitPut
RemoteId.bitPut (UniqueId -> RemoteId
remoteId UniqueId
uniqueIdAttribute)
    BitPut -> BitPut -> BitPut
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 = String -> BitGet UniqueId -> BitGet UniqueId
forall a. String -> BitGet a -> BitGet a
BitGet.label String
"UniqueId" (BitGet UniqueId -> BitGet UniqueId)
-> BitGet UniqueId -> BitGet UniqueId
forall a b. (a -> b) -> a -> b
$ do
  systemId <- String -> BitGet U8 -> BitGet U8
forall a. String -> BitGet a -> BitGet a
BitGet.label String
"systemId" BitGet U8
U8.bitGet
  remoteId <- BitGet.label "remoteId" $ RemoteId.bitGet version systemId
  localId <- BitGet.label "localId" U8.bitGet
  pure UniqueId {systemId, remoteId, localId}