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
/= :: UniqueId -> UniqueId -> Bool
$c/= :: UniqueId -> UniqueId -> Bool
== :: UniqueId -> UniqueId -> Bool
$c== :: 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
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 = 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
    U8
systemId <- Object -> String -> Parser U8
forall value. FromJSON value => Object -> String -> Parser value
Json.required Object
object String
"system_id"
    RemoteId
remoteId <- Object -> String -> Parser RemoteId
forall value. FromJSON value => Object -> String -> Parser value
Json.required Object
object String
"remote_id"
    U8
localId <- Object -> String -> Parser U8
forall value. FromJSON value => Object -> String -> Parser value
Json.required Object
object String
"local_id"
    UniqueId -> Parser UniqueId
forall (f :: * -> *) a. Applicative f => a -> f a
pure UniqueId :: U8 -> RemoteId -> U8 -> UniqueId
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 = [Pair] -> Value
Json.object
    [ String -> U8 -> Pair
forall value pair.
(ToJSON value, KeyValue pair) =>
String -> value -> pair
Json.pair String
"system_id" (U8 -> Pair) -> U8 -> Pair
forall a b. (a -> b) -> a -> b
$ UniqueId -> U8
systemId UniqueId
x
    , String -> RemoteId -> Pair
forall value pair.
(ToJSON value, KeyValue pair) =>
String -> value -> pair
Json.pair String
"remote_id" (RemoteId -> Pair) -> RemoteId -> Pair
forall a b. (a -> b) -> a -> b
$ UniqueId -> RemoteId
remoteId UniqueId
x
    , String -> U8 -> Pair
forall value pair.
(ToJSON value, KeyValue pair) =>
String -> value -> pair
Json.pair String
"local_id" (U8 -> Pair) -> U8 -> Pair
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
$ [(Pair, Bool)] -> Value
Schema.object
  [ (String -> Value -> Pair
forall value pair.
(ToJSON value, KeyValue pair) =>
String -> value -> pair
Json.pair String
"system_id" (Value -> Pair) -> Value -> Pair
forall a b. (a -> b) -> a -> b
$ Schema -> Value
Schema.ref Schema
U8.schema, Bool
True)
  , (String -> Value -> Pair
forall value pair.
(ToJSON value, KeyValue pair) =>
String -> value -> pair
Json.pair String
"remote_id" (Value -> Pair) -> Value -> Pair
forall a b. (a -> b) -> a -> b
$ Schema -> Value
Schema.ref Schema
RemoteId.schema, Bool
True)
  , (String -> Value -> Pair
forall value pair.
(ToJSON value, KeyValue pair) =>
String -> value -> pair
Json.pair String
"local_id" (Value -> Pair) -> Value -> Pair
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
  U8
systemId <- String -> BitGet U8 -> BitGet U8
forall a. String -> BitGet a -> BitGet a
BitGet.label String
"systemId" BitGet U8
U8.bitGet
  RemoteId
remoteId <- String -> BitGet RemoteId -> BitGet RemoteId
forall a. String -> BitGet a -> BitGet a
BitGet.label String
"remoteId" (BitGet RemoteId -> BitGet RemoteId)
-> BitGet RemoteId -> BitGet RemoteId
forall a b. (a -> b) -> a -> b
$ Version -> U8 -> BitGet RemoteId
RemoteId.bitGet Version
version U8
systemId
  U8
localId <- String -> BitGet U8 -> BitGet U8
forall a. String -> BitGet a -> BitGet a
BitGet.label String
"localId" BitGet U8
U8.bitGet
  UniqueId -> BitGet UniqueId
forall (f :: * -> *) a. Applicative f => a -> f a
pure UniqueId :: U8 -> RemoteId -> U8 -> UniqueId
UniqueId { U8
systemId :: U8
systemId :: U8
systemId, RemoteId
remoteId :: RemoteId
remoteId :: RemoteId
remoteId, U8
localId :: U8
localId :: U8
localId }