{-# LANGUAGE TemplateHaskell #-}
module Graphics.RedViz.Texture
( Texture (..)
, name
, path
, uuid
, defaultTexture
) where
import Control.Lens
import Data.Aeson
import Data.Aeson.Encode.Pretty
import Data.Aeson.TH
import Data.UUID
import Data.Text hiding (drop)
import Graphics.RedViz.Utils (encodeStringUUID)
data Texture
= Texture
{
Texture -> String
_name :: String
, Texture -> String
_path :: FilePath
, Texture -> UUID
_uuid :: UUID
} deriving Int -> Texture -> ShowS
[Texture] -> ShowS
Texture -> String
(Int -> Texture -> ShowS)
-> (Texture -> String) -> ([Texture] -> ShowS) -> Show Texture
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Texture] -> ShowS
$cshowList :: [Texture] -> ShowS
show :: Texture -> String
$cshow :: Texture -> String
showsPrec :: Int -> Texture -> ShowS
$cshowsPrec :: Int -> Texture -> ShowS
Show
$(makeLenses ''Texture)
deriveJSON defaultOptions {fieldLabelModifier = drop 1} ''Texture
instance Eq Texture where
Texture
t0 == :: Texture -> Texture -> Bool
== Texture
t1 = Getting UUID Texture UUID -> Texture -> UUID
forall s (m :: * -> *) a. MonadReader s m => Getting a s a -> m a
view Getting UUID Texture UUID
Lens' Texture UUID
uuid Texture
t0 UUID -> UUID -> Bool
forall a. Eq a => a -> a -> Bool
== Getting UUID Texture UUID -> Texture -> UUID
forall s (m :: * -> *) a. MonadReader s m => Getting a s a -> m a
view Getting UUID Texture UUID
Lens' Texture UUID
uuid Texture
t1
instance Ord Texture where
compare :: Texture -> Texture -> Ordering
compare Texture
t0 Texture
t1 = UUID -> UUID -> Ordering
forall a. Ord a => a -> a -> Ordering
compare (Getting UUID Texture UUID -> Texture -> UUID
forall s (m :: * -> *) a. MonadReader s m => Getting a s a -> m a
view Getting UUID Texture UUID
Lens' Texture UUID
uuid Texture
t0) (Getting UUID Texture UUID -> Texture -> UUID
forall s (m :: * -> *) a. MonadReader s m => Getting a s a -> m a
view Getting UUID Texture UUID
Lens' Texture UUID
uuid Texture
t1)
defaultTexture :: Texture
defaultTexture :: Texture
defaultTexture
= String -> String -> UUID -> Texture
Texture
String
"checkerboard"
String
"./textures/checkerboard.png"
(String -> UUID
encodeStringUUID String
"./textures/checkerboard.png")
comp :: Text -> Text -> Ordering
comp :: Text -> Text -> Ordering
comp = [Text] -> Text -> Text -> Ordering
keyOrder ([Text] -> Text -> Text -> Ordering)
-> ([String] -> [Text]) -> [String] -> Text -> Text -> Ordering
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (String -> Text) -> [String] -> [Text]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap String -> Text
pack ([String] -> Text -> Text -> Ordering)
-> [String] -> Text -> Text -> Ordering
forall a b. (a -> b) -> a -> b
$ [String
"name", String
"path", String
"uuid"]