module Rattletrap.Type.Attribute.Enum where import qualified Data.Word as Word import Prelude hiding (Enum) import qualified Rattletrap.BitGet as BitGet import qualified Rattletrap.BitPut as BitPut import qualified Rattletrap.Schema as Schema import qualified Rattletrap.Utility.Json as Json newtype Enum = Enum { Enum -> Word16 value :: Word.Word16 } deriving (Enum -> Enum -> Bool forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a /= :: Enum -> Enum -> Bool $c/= :: Enum -> Enum -> Bool == :: Enum -> Enum -> Bool $c== :: Enum -> Enum -> Bool Eq, Int -> Enum -> ShowS [Enum] -> ShowS Enum -> String forall a. (Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a showList :: [Enum] -> ShowS $cshowList :: [Enum] -> ShowS show :: Enum -> String $cshow :: Enum -> String showsPrec :: Int -> Enum -> ShowS $cshowsPrec :: Int -> Enum -> ShowS Show) instance Json.FromJSON Enum where parseJSON :: Value -> Parser Enum parseJSON = forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b fmap Word16 -> Enum Enum forall b c a. (b -> c) -> (a -> b) -> a -> c . forall a. FromJSON a => Value -> Parser a Json.parseJSON instance Json.ToJSON Enum where toJSON :: Enum -> Value toJSON = forall a. ToJSON a => a -> Value Json.toJSON forall b c a. (b -> c) -> (a -> b) -> a -> c . Enum -> Word16 value schema :: Schema.Schema schema :: Schema schema = String -> Value -> Schema Schema.named String "attribute-enum" forall a b. (a -> b) -> a -> b $ Schema -> Value Schema.ref Schema Schema.integer bitPut :: Enum -> BitPut.BitPut bitPut :: Enum -> BitPut bitPut Enum enumAttribute = forall a. Bits a => Int -> a -> BitPut BitPut.bits Int 11 (Enum -> Word16 value Enum enumAttribute) bitGet :: BitGet.BitGet Enum bitGet :: BitGet Enum bitGet = forall a. String -> BitGet a -> BitGet a BitGet.label String "Enum" forall a b. (a -> b) -> a -> b $ do Word16 value <- forall a. String -> BitGet a -> BitGet a BitGet.label String "value" forall a b. (a -> b) -> a -> b $ forall a. Bits a => Int -> BitGet a BitGet.bits Int 11 forall (f :: * -> *) a. Applicative f => a -> f a pure Enum { Word16 value :: Word16 value :: Word16 value }