| Safe Haskell | Safe-Inferred |
|---|---|
| Language | Haskell2010 |
Engine.Setup.Window
Synopsis
- data Window
- allocate :: (MonadUnliftIO m, MonadReader env m, HasLogFunc env, MonadResource m) => Bool -> Maybe (Int, Int) -> Natural -> SizePicker -> Text -> m ([InstanceRequirement], Window)
- createWindow :: (MonadIO m, MonadReader env m, HasLogFunc env) => Bool -> Maybe (Int, Int) -> Natural -> SizePicker -> Text -> m ([InstanceRequirement], Window)
- destroyWindow :: (MonadIO m, MonadReader env m, HasLogFunc env) => Window -> m ()
- type SizePicker = NonEmpty (Monitor, VideoMode) -> (Monitor, VideoMode)
- pickLargest :: SizePicker
- data SurfaceKHR
- allocateSurface :: MonadResource m => Window -> Instance -> m (ReleaseKey, SurfaceKHR)
- createSurface :: MonadIO m => Window -> Instance -> m SurfaceKHR
- getExtent2D :: Window -> IO Extent2D
- data GLFWError
- data Error
Documentation
Reprisents a GLFW window value. See the Window Guide
Instances
| Data Window | |
Defined in Graphics.UI.GLFW.Types Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Window -> c Window Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Window Source # toConstr :: Window -> Constr Source # dataTypeOf :: Window -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Window) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Window) Source # gmapT :: (forall b. Data b => b -> b) -> Window -> Window Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Window -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Window -> r Source # gmapQ :: (forall d. Data d => d -> u) -> Window -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> Window -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Window -> m Window Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Window -> m Window Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Window -> m Window Source # | |
| Generic Window | |
| Show Window | |
| Eq Window | |
| Ord Window | |
| type Rep Window | |
Defined in Graphics.UI.GLFW.Types type Rep Window = D1 ('MetaData "Window" "Graphics.UI.GLFW.Types" "GLFW-b-3.3.0.0-3be570e09ffa2a2e6308e9805ce91330653eacb3112e153ff220a38e8742d734" 'True) (C1 ('MetaCons "Window" 'PrefixI 'True) (S1 ('MetaSel ('Just "unWindow") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Ptr C'GLFWwindow)))) | |
allocate :: (MonadUnliftIO m, MonadReader env m, HasLogFunc env, MonadResource m) => Bool -> Maybe (Int, Int) -> Natural -> SizePicker -> Text -> m ([InstanceRequirement], Window) Source #
createWindow :: (MonadIO m, MonadReader env m, HasLogFunc env) => Bool -> Maybe (Int, Int) -> Natural -> SizePicker -> Text -> m ([InstanceRequirement], Window) Source #
destroyWindow :: (MonadIO m, MonadReader env m, HasLogFunc env) => Window -> m () Source #
data SurfaceKHR Source #
VkSurfaceKHR - Opaque handle to a surface object
Description
The VK_KHR_surface extension declares the SurfaceKHR object, and
provides a function for destroying SurfaceKHR objects. Separate
platform-specific extensions each provide a function for creating a
SurfaceKHR object for the respective platform. From the application’s
perspective this is an opaque handle, just like the handles of other
Vulkan objects.
See Also
VK_KHR_surface,
PhysicalDeviceSurfaceInfo2KHR,
SwapchainCreateInfoKHR,
createAndroidSurfaceKHR,
createDirectFBSurfaceEXT,
createDisplayPlaneSurfaceKHR,
createHeadlessSurfaceEXT,
createIOSSurfaceMVK,
createImagePipeSurfaceFUCHSIA,
createMacOSSurfaceMVK,
createMetalSurfaceEXT,
createScreenSurfaceQNX,
createStreamDescriptorSurfaceGGP,
createViSurfaceNN,
createWaylandSurfaceKHR,
createWin32SurfaceKHR,
createXcbSurfaceKHR,
createXlibSurfaceKHR,
destroySurfaceKHR,
getDeviceGroupSurfacePresentModesKHR,
getPhysicalDevicePresentRectanglesKHR,
getPhysicalDeviceSurfaceCapabilities2EXT,
getPhysicalDeviceSurfaceCapabilitiesKHR,
getPhysicalDeviceSurfaceFormatsKHR,
getPhysicalDeviceSurfacePresentModesKHR,
getPhysicalDeviceSurfaceSupportKHR
Instances
allocateSurface :: MonadResource m => Window -> Instance -> m (ReleaseKey, SurfaceKHR) Source #
createSurface :: MonadIO m => Window -> Instance -> m SurfaceKHR Source #
Instances
| Exception GLFWError Source # | |
Defined in Engine.Setup.Window Methods toException :: GLFWError -> SomeException Source # fromException :: SomeException -> Maybe GLFWError Source # displayException :: GLFWError -> String Source # | |
| Show GLFWError Source # | |
| Eq GLFWError Source # | |
| Ord GLFWError Source # | |
Defined in Engine.Setup.Window | |
An enum for one of the GLFW error codes.
Instances
| Data Error | |
Defined in Graphics.UI.GLFW.Types Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Error -> c Error Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Error Source # toConstr :: Error -> Constr Source # dataTypeOf :: Error -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Error) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Error) Source # gmapT :: (forall b. Data b => b -> b) -> Error -> Error Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Error -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Error -> r Source # gmapQ :: (forall d. Data d => d -> u) -> Error -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> Error -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Error -> m Error Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Error -> m Error Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Error -> m Error Source # | |
| Bounded Error | |
| Enum Error | |
Defined in Graphics.UI.GLFW.Types Methods succ :: Error -> Error Source # pred :: Error -> Error Source # toEnum :: Int -> Error Source # fromEnum :: Error -> Int Source # enumFrom :: Error -> [Error] Source # enumFromThen :: Error -> Error -> [Error] Source # enumFromTo :: Error -> Error -> [Error] Source # enumFromThenTo :: Error -> Error -> Error -> [Error] Source # | |
| Generic Error | |
| Read Error | |
| Show Error | |
| NFData Error | |
Defined in Graphics.UI.GLFW.Types | |
| Eq Error | |
| Ord Error | |
Defined in Graphics.UI.GLFW.Types | |
| type Rep Error | |
Defined in Graphics.UI.GLFW.Types type Rep Error = D1 ('MetaData "Error" "Graphics.UI.GLFW.Types" "GLFW-b-3.3.0.0-3be570e09ffa2a2e6308e9805ce91330653eacb3112e153ff220a38e8742d734" 'False) (((C1 ('MetaCons "Error'NotInitialized" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Error'NoCurrentContext" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "Error'InvalidEnum" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Error'InvalidValue" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "Error'OutOfMemory" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Error'ApiUnavailable" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "Error'VersionUnavailable" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "Error'PlatformError" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Error'FormatUnavailable" 'PrefixI 'False) (U1 :: Type -> Type))))) | |