{-# LANGUAGE DeriveGeneric #-} {-# LANGUAGE DuplicateRecordFields #-} {-# LANGUAGE StrictData #-} module Octane.Type.Vector (Vector(..)) where import qualified Control.DeepSeq as DeepSeq import qualified Data.Aeson as Aeson import qualified GHC.Generics as Generics -- | Three values packed together. Although the fields are called @x@, @y@, and -- @z@, that may not be what they actually represent. -- -- This cannot be an instance of 'Data.Binary.Bits.BinaryBit' because it is not -- always serialized the same way. Sometimes it is three values run together, -- but other times it has a flag for the presence of each value. data Vector a = Vector { x :: a , y :: a , z :: a } deriving (Eq, Generics.Generic, Show) instance (DeepSeq.NFData a) => DeepSeq.NFData (Vector a) where -- | Encoded as a JSON array with 3 elements. -- -- Aeson.encode (Vector 1 2 3 :: Vector Int) -- "[1,2,3]" instance (Aeson.ToJSON a) => Aeson.ToJSON (Vector a) where toJSON vector = Aeson.toJSON [ x vector , y vector , z vector ]