ombra-1.1.0.0: Render engine.

LicenseBSD3
Maintainerziocroc@gmail.com
Stabilityexperimental
PortabilityGHC only
Safe HaskellNone
LanguageHaskell2010

Graphics.Rendering.Ombra.Draw

Contents

Description

 

Synopsis

Documentation

data Draw o a Source #

An implementation of MonadDraw and MonadDrawBuffers.

Instances

GLES => MonadDrawBuffers Draw Source # 
GLES => MonadRead GVec4 Draw Source # 
(FragmentShaderOutput o, GLES) => MonadDraw o Draw Source # 
MonadBase IO (Draw o) Source # 

Methods

liftBase :: IO α -> Draw o α #

MonadBaseControl IO (Draw o) Source # 

Associated Types

type StM (Draw o :: * -> *) a :: * #

Methods

liftBaseWith :: (RunInBase (Draw o) IO -> IO a) -> Draw o a #

restoreM :: StM (Draw o) a -> Draw o a #

Monad (Draw o) Source # 

Methods

(>>=) :: Draw o a -> (a -> Draw o b) -> Draw o b #

(>>) :: Draw o a -> Draw o b -> Draw o b #

return :: a -> Draw o a #

fail :: String -> Draw o a #

Functor (Draw o) Source # 

Methods

fmap :: (a -> b) -> Draw o a -> Draw o b #

(<$) :: a -> Draw o b -> Draw o a #

Applicative (Draw o) Source # 

Methods

pure :: a -> Draw o a #

(<*>) :: Draw o (a -> b) -> Draw o a -> Draw o b #

(*>) :: Draw o a -> Draw o b -> Draw o b #

(<*) :: Draw o a -> Draw o b -> Draw o a #

MonadIO (Draw o) Source # 

Methods

liftIO :: IO a -> Draw o a #

GLES => MonadCulling (Draw o) Source # 

Methods

withCulling :: Maybe CullFace -> Draw o a -> Draw o a Source #

GLES => MonadScreen (Draw o) Source # 

Methods

currentViewport :: Draw o ((Int, Int), (Int, Int))

resizeViewport :: (Int, Int) -> (Int, Int) -> Draw o () Source #

GLES => MonadTexture (Draw o) Source # 

Methods

getTexture :: Texture -> Draw o (Either String LoadedTexture)

withActiveTextures :: [Texture] -> (String -> Draw o a) -> ([Sampler2D] -> Draw o a) -> Draw o a

newTexture :: Int -> Int -> TextureParameters -> Int -> (Texture -> GL ()) -> Draw o LoadedTexture

type StM (Draw o) a Source # 
type StM (Draw o) a

Running the Draw monad

runDraw Source #

Arguments

:: GLES 
=> Int

Viewport width

-> Int

Viewport height

-> Ctx 
-> Draw GVec4 a 
-> IO a 

Run a Draw program.

Draw actions

class (MonadGeometry (m o), MonadProgram (m o), MonadTexture (m o), MonadScreen (m o)) => MonadDraw o m where Source #

Monads that can be used to draw Images.

Methods

withColorMask :: (Bool, Bool, Bool, Bool) -> m o a -> m o a Source #

Enable/disable writing to one or more color channels.

withDepthTest :: Bool -> m o a -> m o a Source #

Enable/disable depth testing.

withDepthMask :: Bool -> m o a -> m o a Source #

Enable/disable writing to the depth buffer.

clearColor :: m o () Source #

Clear the color buffer.

clearColorWith :: Vec4 -> m o () Source #

Clear the color buffer filling it with the given color.

clearDepth :: m o () Source #

Clear the depth buffer.

clearDepthWith :: Double -> m o () Source #

Clear the depth buffer filling it with the given value.

clearStencil :: m o () Source #

Clear the stencil buffer.

clearStencilWith :: Int -> m o () Source #

Clear the stencil buffer filling it with the given value.

class MonadDrawBuffers m where Source #

Monads that support drawing to GBuffers and DepthBuffers.

Methods

createBuffers :: FragmentShaderOutput o => Int -> Int -> GBufferInfo o -> DepthBufferInfo -> m o a -> m o' (a, BufferPair o) Source #

Create a GBuffer and a DepthBuffer and draw something to them.

createGBuffer :: FragmentShaderOutput o => GBufferInfo o -> DepthBuffer -> m o a -> m o' (a, BufferPair o) Source #

createDepthBuffer :: FragmentShaderOutput o => GBuffer o -> DepthBufferInfo -> m o a -> m o' (a, BufferPair o) Source #

drawBuffers :: FragmentShaderOutput o => BufferPair o -> m o a -> m o' a Source #

Draw an image to some buffers.

class MonadDraw o m => MonadRead o m where Source #

Methods

readColor :: (Int, Int, Int, Int) -> m o [Color] Source #

Read a rectangle of pixel colors from the screen (or texture).

readColorFloat :: (Int, Int, Int, Int) -> m o [Vec4] Source #

readColor variant that read color vectors.

readDepth :: (Int, Int, Int, Int) -> m o [Word16] Source #

Read a rectangle of pixel depths from the screen (or texture). Not supported on WebGL!

readDepthFloat :: (Int, Int, Int, Int) -> m o [Float] Source #

readDepth variants that read floats. Not supported on WebGL as well.

readStencil :: (Int, Int, Int, Int) -> m o [Word8] Source #

Read a rectangle of stencil values from the screen (or texture). Not supported on WebGL!

class (GLES, Monad m) => MonadScreen m where Source #

Minimal complete definition

currentViewport, resizeViewport

Methods

resizeViewport :: (Int, Int) -> (Int, Int) -> m () Source #

Resize the drawing space.

Instances

GLES => MonadScreen (Draw o) Source # 

Methods

currentViewport :: Draw o ((Int, Int), (Int, Int))

resizeViewport :: (Int, Int) -> (Int, Int) -> Draw o () Source #

Culling

class GLES => MonadCulling m where Source #

Minimal complete definition

withCulling

Methods

withCulling :: Maybe CullFace -> m a -> m a Source #

Instances

GLES => MonadCulling (Draw o) Source # 

Methods

withCulling :: Maybe CullFace -> Draw o a -> Draw o a Source #

Resources

In Ombra, GPU resources are allocated when they're needed, and they're kept alive by their corresponding CPU resources. Specifically, these resources are Geometries, Textures and Shaders. This means that, when a CPU resource is garbage collected, the GPU resource is also removed. The functions below let you manage allocation and deallocation manually. Note that if you try to use a resource that was deallocated with the remove* functions, it will be allocated again.

data ResStatus r Source #

Constructors

Loaded r 
Unloaded 
Error String 

Instances

Functor ResStatus Source # 

Methods

fmap :: (a -> b) -> ResStatus a -> ResStatus b #

(<$) :: a -> ResStatus b -> ResStatus a #

preloadGeometry :: (GLES, GeometryVertex g, ElementType e) => Geometry e g -> Draw o (Maybe String) Source #

Manually allocate a Geometry in the GPU. Eventually returns an error string.

preloadTexture :: GLES => Texture -> Draw o (Maybe String) Source #

Manually allocate a Texture in the GPU.

removeGeometry :: (GLES, GeometryVertex g, ElementType e) => Geometry e g -> Draw o () Source #

Manually delete a Geometry from the GPU.

removeTexture :: GLES => Texture -> Draw o () Source #

Manually delete a Texture from the GPU.

checkGeometry :: (GLES, GeometryVertex g, ElementType e) => Geometry e g -> Draw o (ResStatus ()) Source #

Check if a Geometry failed to load.

checkTexture :: (GLES, Num a) => Texture -> Draw o (ResStatus (a, a)) Source #

Check if a Texture failed to load. Eventually returns the texture width and height.