module Rattletrap.Type.RemoteId.Switch where

import qualified Rattletrap.BitGet as BitGet
import qualified Rattletrap.BitPut as BitPut
import qualified Rattletrap.Schema as Schema
import qualified Rattletrap.Type.U64 as U64
import qualified Rattletrap.Utility.Json as Json

data Switch = Switch
  { Switch -> U64
a :: U64.U64,
    Switch -> U64
b :: U64.U64,
    Switch -> U64
c :: U64.U64,
    Switch -> U64
d :: U64.U64
  }
  deriving (Switch -> Switch -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Switch -> Switch -> Bool
$c/= :: Switch -> Switch -> Bool
== :: Switch -> Switch -> Bool
$c== :: Switch -> Switch -> Bool
Eq, Int -> Switch -> ShowS
[Switch] -> ShowS
Switch -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Switch] -> ShowS
$cshowList :: [Switch] -> ShowS
show :: Switch -> String
$cshow :: Switch -> String
showsPrec :: Int -> Switch -> ShowS
$cshowsPrec :: Int -> Switch -> ShowS
Show)

instance Json.FromJSON Switch where
  parseJSON :: Value -> Parser Switch
parseJSON Value
json = do
    (U64
a, U64
b, U64
c, U64
d) <- forall a. FromJSON a => Value -> Parser a
Json.parseJSON Value
json
    forall (f :: * -> *) a. Applicative f => a -> f a
pure Switch {U64
a :: U64
a :: U64
a, U64
b :: U64
b :: U64
b, U64
c :: U64
c :: U64
c, U64
d :: U64
d :: U64
d}

instance Json.ToJSON Switch where
  toJSON :: Switch -> Value
toJSON Switch
x = forall a. ToJSON a => a -> Value
Json.toJSON (Switch -> U64
a Switch
x, Switch -> U64
b Switch
x, Switch -> U64
c Switch
x, Switch -> U64
d Switch
x)

schema :: Schema.Schema
schema :: Schema
schema =
  String -> Value -> Schema
Schema.named String
"remote-id-switch" forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Value] -> Value
Schema.tuple forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Int -> a -> [a]
replicate Int
4 forall a b. (a -> b) -> a -> b
$
    Schema -> Value
Schema.ref
      Schema
U64.schema

bitPut :: Switch -> BitPut.BitPut
bitPut :: Switch -> BitPut
bitPut Switch
x =
  U64 -> BitPut
U64.bitPut (Switch -> U64
a Switch
x) forall a. Semigroup a => a -> a -> a
<> U64 -> BitPut
U64.bitPut (Switch -> U64
b Switch
x) forall a. Semigroup a => a -> a -> a
<> U64 -> BitPut
U64.bitPut (Switch -> U64
c Switch
x) forall a. Semigroup a => a -> a -> a
<> U64 -> BitPut
U64.bitPut (Switch -> U64
d Switch
x)

bitGet :: BitGet.BitGet Switch
bitGet :: BitGet Switch
bitGet = forall a. String -> BitGet a -> BitGet a
BitGet.label String
"Switch" forall a b. (a -> b) -> a -> b
$ do
  U64
a <- BitGet U64
U64.bitGet
  U64
b <- BitGet U64
U64.bitGet
  U64
c <- BitGet U64
U64.bitGet
  U64
d <- BitGet U64
U64.bitGet
  forall (f :: * -> *) a. Applicative f => a -> f a
pure Switch {U64
a :: U64
a :: U64
a, U64
b :: U64
b :: U64
b, U64
c :: U64
c :: U64
c, U64
d :: U64
d :: U64
d}