{-# LANGUAGE TemplateHaskell #-}

module Rattletrap.Type.Int8Vector
  ( Int8Vector(..)
  )
where

import Rattletrap.Type.Common
import Rattletrap.Type.Int8le

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

$(deriveJson ''Int8Vector)