{-# LANGUAGE TemplateHaskell #-}

module Rattletrap.Type.LocationAttribute
  ( LocationAttribute(..)
  )
where

import Rattletrap.Type.Common
import Rattletrap.Type.Vector

newtype LocationAttribute = LocationAttribute
  { LocationAttribute -> Vector
locationAttributeValue :: Vector
  } deriving (LocationAttribute -> LocationAttribute -> Bool
(LocationAttribute -> LocationAttribute -> Bool)
-> (LocationAttribute -> LocationAttribute -> Bool)
-> Eq LocationAttribute
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: LocationAttribute -> LocationAttribute -> Bool
$c/= :: LocationAttribute -> LocationAttribute -> Bool
== :: LocationAttribute -> LocationAttribute -> Bool
$c== :: LocationAttribute -> LocationAttribute -> Bool
Eq, Eq LocationAttribute
Eq LocationAttribute
-> (LocationAttribute -> LocationAttribute -> Ordering)
-> (LocationAttribute -> LocationAttribute -> Bool)
-> (LocationAttribute -> LocationAttribute -> Bool)
-> (LocationAttribute -> LocationAttribute -> Bool)
-> (LocationAttribute -> LocationAttribute -> Bool)
-> (LocationAttribute -> LocationAttribute -> LocationAttribute)
-> (LocationAttribute -> LocationAttribute -> LocationAttribute)
-> Ord LocationAttribute
LocationAttribute -> LocationAttribute -> Bool
LocationAttribute -> LocationAttribute -> Ordering
LocationAttribute -> LocationAttribute -> LocationAttribute
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 :: LocationAttribute -> LocationAttribute -> LocationAttribute
$cmin :: LocationAttribute -> LocationAttribute -> LocationAttribute
max :: LocationAttribute -> LocationAttribute -> LocationAttribute
$cmax :: LocationAttribute -> LocationAttribute -> LocationAttribute
>= :: LocationAttribute -> LocationAttribute -> Bool
$c>= :: LocationAttribute -> LocationAttribute -> Bool
> :: LocationAttribute -> LocationAttribute -> Bool
$c> :: LocationAttribute -> LocationAttribute -> Bool
<= :: LocationAttribute -> LocationAttribute -> Bool
$c<= :: LocationAttribute -> LocationAttribute -> Bool
< :: LocationAttribute -> LocationAttribute -> Bool
$c< :: LocationAttribute -> LocationAttribute -> Bool
compare :: LocationAttribute -> LocationAttribute -> Ordering
$ccompare :: LocationAttribute -> LocationAttribute -> Ordering
$cp1Ord :: Eq LocationAttribute
Ord, Int -> LocationAttribute -> ShowS
[LocationAttribute] -> ShowS
LocationAttribute -> String
(Int -> LocationAttribute -> ShowS)
-> (LocationAttribute -> String)
-> ([LocationAttribute] -> ShowS)
-> Show LocationAttribute
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [LocationAttribute] -> ShowS
$cshowList :: [LocationAttribute] -> ShowS
show :: LocationAttribute -> String
$cshow :: LocationAttribute -> String
showsPrec :: Int -> LocationAttribute -> ShowS
$cshowsPrec :: Int -> LocationAttribute -> ShowS
Show)

$(deriveJson ''LocationAttribute)