{-# OPTIONS_HADDOCK ignore-exports#-}
{-# LANGUAGE DataKinds                  #-}
{-# LANGUAGE DeriveDataTypeable         #-}
{-# LANGUAGE DeriveGeneric              #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE PatternSynonyms            #-}
{-# LANGUAGE Strict                     #-}
module Graphics.Vulkan.Types.Enum.FrontFace
       (VkFrontFace(VkFrontFace, VK_FRONT_FACE_COUNTER_CLOCKWISE,
                    VK_FRONT_FACE_CLOCKWISE))
       where
import           Data.Data                       (Data)
import           Foreign.Storable                (Storable)
import           GHC.Generics                    (Generic)
import           GHC.Read                        (choose, expectP)
import           Graphics.Vulkan.Marshal         (Int32)
import           Text.ParserCombinators.ReadPrec (prec, step, (+++))
import           Text.Read                       (Read (..), parens)
import           Text.Read.Lex                   (Lexeme (..))

-- | type = @enum@
--
--   <https://www.khronos.org/registry/vulkan/specs/1.1-extensions/html/vkspec.html#VkFrontFace VkFrontFace registry at www.khronos.org>
newtype VkFrontFace = VkFrontFace Int32
                        deriving (VkFrontFace -> VkFrontFace -> Bool
(VkFrontFace -> VkFrontFace -> Bool)
-> (VkFrontFace -> VkFrontFace -> Bool) -> Eq VkFrontFace
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: VkFrontFace -> VkFrontFace -> Bool
$c/= :: VkFrontFace -> VkFrontFace -> Bool
== :: VkFrontFace -> VkFrontFace -> Bool
$c== :: VkFrontFace -> VkFrontFace -> Bool
Eq, Eq VkFrontFace
Eq VkFrontFace
-> (VkFrontFace -> VkFrontFace -> Ordering)
-> (VkFrontFace -> VkFrontFace -> Bool)
-> (VkFrontFace -> VkFrontFace -> Bool)
-> (VkFrontFace -> VkFrontFace -> Bool)
-> (VkFrontFace -> VkFrontFace -> Bool)
-> (VkFrontFace -> VkFrontFace -> VkFrontFace)
-> (VkFrontFace -> VkFrontFace -> VkFrontFace)
-> Ord VkFrontFace
VkFrontFace -> VkFrontFace -> Bool
VkFrontFace -> VkFrontFace -> Ordering
VkFrontFace -> VkFrontFace -> VkFrontFace
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 :: VkFrontFace -> VkFrontFace -> VkFrontFace
$cmin :: VkFrontFace -> VkFrontFace -> VkFrontFace
max :: VkFrontFace -> VkFrontFace -> VkFrontFace
$cmax :: VkFrontFace -> VkFrontFace -> VkFrontFace
>= :: VkFrontFace -> VkFrontFace -> Bool
$c>= :: VkFrontFace -> VkFrontFace -> Bool
> :: VkFrontFace -> VkFrontFace -> Bool
$c> :: VkFrontFace -> VkFrontFace -> Bool
<= :: VkFrontFace -> VkFrontFace -> Bool
$c<= :: VkFrontFace -> VkFrontFace -> Bool
< :: VkFrontFace -> VkFrontFace -> Bool
$c< :: VkFrontFace -> VkFrontFace -> Bool
compare :: VkFrontFace -> VkFrontFace -> Ordering
$ccompare :: VkFrontFace -> VkFrontFace -> Ordering
$cp1Ord :: Eq VkFrontFace
Ord, Integer -> VkFrontFace
VkFrontFace -> VkFrontFace
VkFrontFace -> VkFrontFace -> VkFrontFace
(VkFrontFace -> VkFrontFace -> VkFrontFace)
-> (VkFrontFace -> VkFrontFace -> VkFrontFace)
-> (VkFrontFace -> VkFrontFace -> VkFrontFace)
-> (VkFrontFace -> VkFrontFace)
-> (VkFrontFace -> VkFrontFace)
-> (VkFrontFace -> VkFrontFace)
-> (Integer -> VkFrontFace)
-> Num VkFrontFace
forall a.
(a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a)
-> (a -> a)
-> (a -> a)
-> (Integer -> a)
-> Num a
fromInteger :: Integer -> VkFrontFace
$cfromInteger :: Integer -> VkFrontFace
signum :: VkFrontFace -> VkFrontFace
$csignum :: VkFrontFace -> VkFrontFace
abs :: VkFrontFace -> VkFrontFace
$cabs :: VkFrontFace -> VkFrontFace
negate :: VkFrontFace -> VkFrontFace
$cnegate :: VkFrontFace -> VkFrontFace
* :: VkFrontFace -> VkFrontFace -> VkFrontFace
$c* :: VkFrontFace -> VkFrontFace -> VkFrontFace
- :: VkFrontFace -> VkFrontFace -> VkFrontFace
$c- :: VkFrontFace -> VkFrontFace -> VkFrontFace
+ :: VkFrontFace -> VkFrontFace -> VkFrontFace
$c+ :: VkFrontFace -> VkFrontFace -> VkFrontFace
Num, VkFrontFace
VkFrontFace -> VkFrontFace -> Bounded VkFrontFace
forall a. a -> a -> Bounded a
maxBound :: VkFrontFace
$cmaxBound :: VkFrontFace
minBound :: VkFrontFace
$cminBound :: VkFrontFace
Bounded, Ptr b -> Int -> IO VkFrontFace
Ptr b -> Int -> VkFrontFace -> IO ()
Ptr VkFrontFace -> IO VkFrontFace
Ptr VkFrontFace -> Int -> IO VkFrontFace
Ptr VkFrontFace -> Int -> VkFrontFace -> IO ()
Ptr VkFrontFace -> VkFrontFace -> IO ()
VkFrontFace -> Int
(VkFrontFace -> Int)
-> (VkFrontFace -> Int)
-> (Ptr VkFrontFace -> Int -> IO VkFrontFace)
-> (Ptr VkFrontFace -> Int -> VkFrontFace -> IO ())
-> (forall b. Ptr b -> Int -> IO VkFrontFace)
-> (forall b. Ptr b -> Int -> VkFrontFace -> IO ())
-> (Ptr VkFrontFace -> IO VkFrontFace)
-> (Ptr VkFrontFace -> VkFrontFace -> IO ())
-> Storable VkFrontFace
forall b. Ptr b -> Int -> IO VkFrontFace
forall b. Ptr b -> Int -> VkFrontFace -> IO ()
forall a.
(a -> Int)
-> (a -> Int)
-> (Ptr a -> Int -> IO a)
-> (Ptr a -> Int -> a -> IO ())
-> (forall b. Ptr b -> Int -> IO a)
-> (forall b. Ptr b -> Int -> a -> IO ())
-> (Ptr a -> IO a)
-> (Ptr a -> a -> IO ())
-> Storable a
poke :: Ptr VkFrontFace -> VkFrontFace -> IO ()
$cpoke :: Ptr VkFrontFace -> VkFrontFace -> IO ()
peek :: Ptr VkFrontFace -> IO VkFrontFace
$cpeek :: Ptr VkFrontFace -> IO VkFrontFace
pokeByteOff :: Ptr b -> Int -> VkFrontFace -> IO ()
$cpokeByteOff :: forall b. Ptr b -> Int -> VkFrontFace -> IO ()
peekByteOff :: Ptr b -> Int -> IO VkFrontFace
$cpeekByteOff :: forall b. Ptr b -> Int -> IO VkFrontFace
pokeElemOff :: Ptr VkFrontFace -> Int -> VkFrontFace -> IO ()
$cpokeElemOff :: Ptr VkFrontFace -> Int -> VkFrontFace -> IO ()
peekElemOff :: Ptr VkFrontFace -> Int -> IO VkFrontFace
$cpeekElemOff :: Ptr VkFrontFace -> Int -> IO VkFrontFace
alignment :: VkFrontFace -> Int
$calignment :: VkFrontFace -> Int
sizeOf :: VkFrontFace -> Int
$csizeOf :: VkFrontFace -> Int
Storable, Int -> VkFrontFace
VkFrontFace -> Int
VkFrontFace -> [VkFrontFace]
VkFrontFace -> VkFrontFace
VkFrontFace -> VkFrontFace -> [VkFrontFace]
VkFrontFace -> VkFrontFace -> VkFrontFace -> [VkFrontFace]
(VkFrontFace -> VkFrontFace)
-> (VkFrontFace -> VkFrontFace)
-> (Int -> VkFrontFace)
-> (VkFrontFace -> Int)
-> (VkFrontFace -> [VkFrontFace])
-> (VkFrontFace -> VkFrontFace -> [VkFrontFace])
-> (VkFrontFace -> VkFrontFace -> [VkFrontFace])
-> (VkFrontFace -> VkFrontFace -> VkFrontFace -> [VkFrontFace])
-> Enum VkFrontFace
forall a.
(a -> a)
-> (a -> a)
-> (Int -> a)
-> (a -> Int)
-> (a -> [a])
-> (a -> a -> [a])
-> (a -> a -> [a])
-> (a -> a -> a -> [a])
-> Enum a
enumFromThenTo :: VkFrontFace -> VkFrontFace -> VkFrontFace -> [VkFrontFace]
$cenumFromThenTo :: VkFrontFace -> VkFrontFace -> VkFrontFace -> [VkFrontFace]
enumFromTo :: VkFrontFace -> VkFrontFace -> [VkFrontFace]
$cenumFromTo :: VkFrontFace -> VkFrontFace -> [VkFrontFace]
enumFromThen :: VkFrontFace -> VkFrontFace -> [VkFrontFace]
$cenumFromThen :: VkFrontFace -> VkFrontFace -> [VkFrontFace]
enumFrom :: VkFrontFace -> [VkFrontFace]
$cenumFrom :: VkFrontFace -> [VkFrontFace]
fromEnum :: VkFrontFace -> Int
$cfromEnum :: VkFrontFace -> Int
toEnum :: Int -> VkFrontFace
$ctoEnum :: Int -> VkFrontFace
pred :: VkFrontFace -> VkFrontFace
$cpred :: VkFrontFace -> VkFrontFace
succ :: VkFrontFace -> VkFrontFace
$csucc :: VkFrontFace -> VkFrontFace
Enum, Typeable VkFrontFace
DataType
Constr
Typeable VkFrontFace
-> (forall (c :: * -> *).
    (forall d b. Data d => c (d -> b) -> d -> c b)
    -> (forall g. g -> c g) -> VkFrontFace -> c VkFrontFace)
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c VkFrontFace)
-> (VkFrontFace -> Constr)
-> (VkFrontFace -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
    Typeable t =>
    (forall d. Data d => c (t d)) -> Maybe (c VkFrontFace))
-> (forall (t :: * -> * -> *) (c :: * -> *).
    Typeable t =>
    (forall d e. (Data d, Data e) => c (t d e))
    -> Maybe (c VkFrontFace))
-> ((forall b. Data b => b -> b) -> VkFrontFace -> VkFrontFace)
-> (forall r r'.
    (r -> r' -> r)
    -> r -> (forall d. Data d => d -> r') -> VkFrontFace -> r)
-> (forall r r'.
    (r' -> r -> r)
    -> r -> (forall d. Data d => d -> r') -> VkFrontFace -> r)
-> (forall u. (forall d. Data d => d -> u) -> VkFrontFace -> [u])
-> (forall u.
    Int -> (forall d. Data d => d -> u) -> VkFrontFace -> u)
-> (forall (m :: * -> *).
    Monad m =>
    (forall d. Data d => d -> m d) -> VkFrontFace -> m VkFrontFace)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> VkFrontFace -> m VkFrontFace)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> VkFrontFace -> m VkFrontFace)
-> Data VkFrontFace
VkFrontFace -> DataType
VkFrontFace -> Constr
(forall b. Data b => b -> b) -> VkFrontFace -> VkFrontFace
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> VkFrontFace -> c VkFrontFace
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c VkFrontFace
forall a.
Typeable a
-> (forall (c :: * -> *).
    (forall d b. Data d => c (d -> b) -> d -> c b)
    -> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
    Typeable t =>
    (forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
    Typeable t =>
    (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
    (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
    (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
    Monad m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u. Int -> (forall d. Data d => d -> u) -> VkFrontFace -> u
forall u. (forall d. Data d => d -> u) -> VkFrontFace -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> VkFrontFace -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> VkFrontFace -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> VkFrontFace -> m VkFrontFace
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> VkFrontFace -> m VkFrontFace
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c VkFrontFace
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> VkFrontFace -> c VkFrontFace
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c VkFrontFace)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c VkFrontFace)
$cVkFrontFace :: Constr
$tVkFrontFace :: DataType
gmapMo :: (forall d. Data d => d -> m d) -> VkFrontFace -> m VkFrontFace
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> VkFrontFace -> m VkFrontFace
gmapMp :: (forall d. Data d => d -> m d) -> VkFrontFace -> m VkFrontFace
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> VkFrontFace -> m VkFrontFace
gmapM :: (forall d. Data d => d -> m d) -> VkFrontFace -> m VkFrontFace
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> VkFrontFace -> m VkFrontFace
gmapQi :: Int -> (forall d. Data d => d -> u) -> VkFrontFace -> u
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> VkFrontFace -> u
gmapQ :: (forall d. Data d => d -> u) -> VkFrontFace -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> VkFrontFace -> [u]
gmapQr :: (r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> VkFrontFace -> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> VkFrontFace -> r
gmapQl :: (r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> VkFrontFace -> r
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> VkFrontFace -> r
gmapT :: (forall b. Data b => b -> b) -> VkFrontFace -> VkFrontFace
$cgmapT :: (forall b. Data b => b -> b) -> VkFrontFace -> VkFrontFace
dataCast2 :: (forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c VkFrontFace)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c VkFrontFace)
dataCast1 :: (forall d. Data d => c (t d)) -> Maybe (c VkFrontFace)
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c VkFrontFace)
dataTypeOf :: VkFrontFace -> DataType
$cdataTypeOf :: VkFrontFace -> DataType
toConstr :: VkFrontFace -> Constr
$ctoConstr :: VkFrontFace -> Constr
gunfold :: (forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c VkFrontFace
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c VkFrontFace
gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> VkFrontFace -> c VkFrontFace
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> VkFrontFace -> c VkFrontFace
$cp1Data :: Typeable VkFrontFace
Data, (forall x. VkFrontFace -> Rep VkFrontFace x)
-> (forall x. Rep VkFrontFace x -> VkFrontFace)
-> Generic VkFrontFace
forall x. Rep VkFrontFace x -> VkFrontFace
forall x. VkFrontFace -> Rep VkFrontFace x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep VkFrontFace x -> VkFrontFace
$cfrom :: forall x. VkFrontFace -> Rep VkFrontFace x
Generic)

instance Show VkFrontFace where
        showsPrec :: Int -> VkFrontFace -> ShowS
showsPrec Int
_ VkFrontFace
VK_FRONT_FACE_COUNTER_CLOCKWISE
          = String -> ShowS
showString String
"VK_FRONT_FACE_COUNTER_CLOCKWISE"
        showsPrec Int
_ VkFrontFace
VK_FRONT_FACE_CLOCKWISE
          = String -> ShowS
showString String
"VK_FRONT_FACE_CLOCKWISE"
        showsPrec Int
p (VkFrontFace Int32
x)
          = Bool -> ShowS -> ShowS
showParen (Int
p Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
>= Int
11) (String -> ShowS
showString String
"VkFrontFace " ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> Int32 -> ShowS
forall a. Show a => Int -> a -> ShowS
showsPrec Int
11 Int32
x)

instance Read VkFrontFace where
        readPrec :: ReadPrec VkFrontFace
readPrec
          = ReadPrec VkFrontFace -> ReadPrec VkFrontFace
forall a. ReadPrec a -> ReadPrec a
parens
              ([(String, ReadPrec VkFrontFace)] -> ReadPrec VkFrontFace
forall a. [(String, ReadPrec a)] -> ReadPrec a
choose
                 [(String
"VK_FRONT_FACE_COUNTER_CLOCKWISE",
                   VkFrontFace -> ReadPrec VkFrontFace
forall (f :: * -> *) a. Applicative f => a -> f a
pure VkFrontFace
VK_FRONT_FACE_COUNTER_CLOCKWISE),
                  (String
"VK_FRONT_FACE_CLOCKWISE", VkFrontFace -> ReadPrec VkFrontFace
forall (f :: * -> *) a. Applicative f => a -> f a
pure VkFrontFace
VK_FRONT_FACE_CLOCKWISE)]
                 ReadPrec VkFrontFace
-> ReadPrec VkFrontFace -> ReadPrec VkFrontFace
forall a. ReadPrec a -> ReadPrec a -> ReadPrec a
+++
                 Int -> ReadPrec VkFrontFace -> ReadPrec VkFrontFace
forall a. Int -> ReadPrec a -> ReadPrec a
prec Int
10
                   (Lexeme -> ReadPrec ()
expectP (String -> Lexeme
Ident String
"VkFrontFace") ReadPrec () -> ReadPrec VkFrontFace -> ReadPrec VkFrontFace
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> (Int32 -> VkFrontFace
VkFrontFace (Int32 -> VkFrontFace) -> ReadPrec Int32 -> ReadPrec VkFrontFace
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ReadPrec Int32 -> ReadPrec Int32
forall a. ReadPrec a -> ReadPrec a
step ReadPrec Int32
forall a. Read a => ReadPrec a
readPrec)))

pattern VK_FRONT_FACE_COUNTER_CLOCKWISE :: VkFrontFace

pattern $bVK_FRONT_FACE_COUNTER_CLOCKWISE :: VkFrontFace
$mVK_FRONT_FACE_COUNTER_CLOCKWISE :: forall r. VkFrontFace -> (Void# -> r) -> (Void# -> r) -> r
VK_FRONT_FACE_COUNTER_CLOCKWISE = VkFrontFace 0

pattern VK_FRONT_FACE_CLOCKWISE :: VkFrontFace

pattern $bVK_FRONT_FACE_CLOCKWISE :: VkFrontFace
$mVK_FRONT_FACE_CLOCKWISE :: forall r. VkFrontFace -> (Void# -> r) -> (Void# -> r) -> r
VK_FRONT_FACE_CLOCKWISE = VkFrontFace 1