{-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE Trustworthy #-}
module Games.ECS.Prototype.PrototypeID where
import Games.ECS.Serialisation
import Control.Lens
import Data.Interned.Text
import Data.Hashable
import GHC.Generics
import Data.String
newtype PrototypeID = PrototypeID {PrototypeID -> InternedText
_unPrototypeID :: InternedText}
deriving newtype (PrototypeID -> PrototypeID -> Bool
(PrototypeID -> PrototypeID -> Bool)
-> (PrototypeID -> PrototypeID -> Bool) -> Eq PrototypeID
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: PrototypeID -> PrototypeID -> Bool
== :: PrototypeID -> PrototypeID -> Bool
$c/= :: PrototypeID -> PrototypeID -> Bool
/= :: PrototypeID -> PrototypeID -> Bool
Eq, Eq PrototypeID
Eq PrototypeID =>
(PrototypeID -> PrototypeID -> Ordering)
-> (PrototypeID -> PrototypeID -> Bool)
-> (PrototypeID -> PrototypeID -> Bool)
-> (PrototypeID -> PrototypeID -> Bool)
-> (PrototypeID -> PrototypeID -> Bool)
-> (PrototypeID -> PrototypeID -> PrototypeID)
-> (PrototypeID -> PrototypeID -> PrototypeID)
-> Ord PrototypeID
PrototypeID -> PrototypeID -> Bool
PrototypeID -> PrototypeID -> Ordering
PrototypeID -> PrototypeID -> PrototypeID
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
$ccompare :: PrototypeID -> PrototypeID -> Ordering
compare :: PrototypeID -> PrototypeID -> Ordering
$c< :: PrototypeID -> PrototypeID -> Bool
< :: PrototypeID -> PrototypeID -> Bool
$c<= :: PrototypeID -> PrototypeID -> Bool
<= :: PrototypeID -> PrototypeID -> Bool
$c> :: PrototypeID -> PrototypeID -> Bool
> :: PrototypeID -> PrototypeID -> Bool
$c>= :: PrototypeID -> PrototypeID -> Bool
>= :: PrototypeID -> PrototypeID -> Bool
$cmax :: PrototypeID -> PrototypeID -> PrototypeID
max :: PrototypeID -> PrototypeID -> PrototypeID
$cmin :: PrototypeID -> PrototypeID -> PrototypeID
min :: PrototypeID -> PrototypeID -> PrototypeID
Ord, Int -> PrototypeID -> ShowS
[PrototypeID] -> ShowS
PrototypeID -> String
(Int -> PrototypeID -> ShowS)
-> (PrototypeID -> String)
-> ([PrototypeID] -> ShowS)
-> Show PrototypeID
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> PrototypeID -> ShowS
showsPrec :: Int -> PrototypeID -> ShowS
$cshow :: PrototypeID -> String
show :: PrototypeID -> String
$cshowList :: [PrototypeID] -> ShowS
showList :: [PrototypeID] -> ShowS
Show)
deriving newtype (Name -> PU [Attribute] PrototypeID
(Name -> PU [Attribute] PrototypeID)
-> XMLPickleAsAttribute PrototypeID
forall a. (Name -> PU [Attribute] a) -> XMLPickleAsAttribute a
$cpickleAsAttribute :: Name -> PU [Attribute] PrototypeID
pickleAsAttribute :: Name -> PU [Attribute] PrototypeID
XMLPickleAsAttribute)
deriving stock ((forall x. PrototypeID -> Rep PrototypeID x)
-> (forall x. Rep PrototypeID x -> PrototypeID)
-> Generic PrototypeID
forall x. Rep PrototypeID x -> PrototypeID
forall x. PrototypeID -> Rep PrototypeID x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. PrototypeID -> Rep PrototypeID x
from :: forall x. PrototypeID -> Rep PrototypeID x
$cto :: forall x. Rep PrototypeID x -> PrototypeID
to :: forall x. Rep PrototypeID x -> PrototypeID
Generic)
deriving newtype (Eq PrototypeID
Eq PrototypeID =>
(Int -> PrototypeID -> Int)
-> (PrototypeID -> Int) -> Hashable PrototypeID
Int -> PrototypeID -> Int
PrototypeID -> Int
forall a. Eq a => (Int -> a -> Int) -> (a -> Int) -> Hashable a
$chashWithSalt :: Int -> PrototypeID -> Int
hashWithSalt :: Int -> PrototypeID -> Int
$chash :: PrototypeID -> Int
hash :: PrototypeID -> Int
Hashable)
deriving newtype String -> PrototypeID
(String -> PrototypeID) -> IsString PrototypeID
forall a. (String -> a) -> IsString a
$cfromString :: String -> PrototypeID
fromString :: String -> PrototypeID
IsString
makeClassy ''PrototypeID
instance {-# OVERLAPS #-} XMLPickler [Node] PrototypeID where
{-# INLINE xpickle #-}
xpickle :: PU [Node] PrototypeID
xpickle =
(InternedText -> PrototypeID)
-> (PrototypeID -> InternedText)
-> PU [Node] InternedText
-> PU [Node] PrototypeID
forall a b t. (a -> b) -> (b -> a) -> PU t a -> PU t b
xpWrap
InternedText -> PrototypeID
PrototypeID
PrototypeID -> InternedText
_unPrototypeID
PU [Node] InternedText
forall t a. XMLPickler t a => PU t a
xpickle