{-# LANGUAGE PatternSynonyms #-} {-# OPTIONS_GHC -Wall -fno-warn-tabs #-} module Gpu.Vulkan.Sampler.Type where import qualified Gpu.Vulkan.Sampler.Middle as M newtype S s = S { forall s. S s -> S sToMiddle :: M.S } deriving Int -> S s -> ShowS [S s] -> ShowS S s -> String (Int -> S s -> ShowS) -> (S s -> String) -> ([S s] -> ShowS) -> Show (S s) forall s. Int -> S s -> ShowS forall s. [S s] -> ShowS forall s. S s -> String forall a. (Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a $cshowsPrec :: forall s. Int -> S s -> ShowS showsPrec :: Int -> S s -> ShowS $cshow :: forall s. S s -> String show :: S s -> String $cshowList :: forall s. [S s] -> ShowS showList :: [S s] -> ShowS Show pattern Null :: S s pattern $mNull :: forall {r} {s}. S s -> ((# #) -> r) -> ((# #) -> r) -> r $bNull :: forall s. S s Null <- S M.Null where Null = S -> S s forall s. S -> S s S S M.Null