{-# LANGUAGE TemplateHaskell #-}

module Rattletrap.Type.Cache
  ( Cache(..)
  )
where

import Rattletrap.Type.AttributeMapping
import Rattletrap.Type.Common
import Rattletrap.Type.List
import Rattletrap.Type.Word32le

data Cache = Cache
  { Cache -> Word32le
cacheClassId :: Word32le
  , Cache -> Word32le
cacheParentCacheId :: Word32le
  , Cache -> Word32le
cacheCacheId :: Word32le
  , Cache -> List AttributeMapping
cacheAttributeMappings :: List AttributeMapping
  } deriving (Cache -> Cache -> Bool
(Cache -> Cache -> Bool) -> (Cache -> Cache -> Bool) -> Eq Cache
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Cache -> Cache -> Bool
$c/= :: Cache -> Cache -> Bool
== :: Cache -> Cache -> Bool
$c== :: Cache -> Cache -> Bool
Eq, Eq Cache
Eq Cache
-> (Cache -> Cache -> Ordering)
-> (Cache -> Cache -> Bool)
-> (Cache -> Cache -> Bool)
-> (Cache -> Cache -> Bool)
-> (Cache -> Cache -> Bool)
-> (Cache -> Cache -> Cache)
-> (Cache -> Cache -> Cache)
-> Ord Cache
Cache -> Cache -> Bool
Cache -> Cache -> Ordering
Cache -> Cache -> Cache
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: Cache -> Cache -> Cache
$cmin :: Cache -> Cache -> Cache
max :: Cache -> Cache -> Cache
$cmax :: Cache -> Cache -> Cache
>= :: Cache -> Cache -> Bool
$c>= :: Cache -> Cache -> Bool
> :: Cache -> Cache -> Bool
$c> :: Cache -> Cache -> Bool
<= :: Cache -> Cache -> Bool
$c<= :: Cache -> Cache -> Bool
< :: Cache -> Cache -> Bool
$c< :: Cache -> Cache -> Bool
compare :: Cache -> Cache -> Ordering
$ccompare :: Cache -> Cache -> Ordering
$cp1Ord :: Eq Cache
Ord, Int -> Cache -> ShowS
[Cache] -> ShowS
Cache -> String
(Int -> Cache -> ShowS)
-> (Cache -> String) -> ([Cache] -> ShowS) -> Show Cache
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Cache] -> ShowS
$cshowList :: [Cache] -> ShowS
show :: Cache -> String
$cshow :: Cache -> String
showsPrec :: Int -> Cache -> ShowS
$cshowsPrec :: Int -> Cache -> ShowS
Show)

$(deriveJson ''Cache)