Safe Haskell | None |
---|---|
Language | Haskell2010 |
Synopsis
- newtype DrawColors os s a = DrawColors (StateT Int (Writer [Int -> (ExprM (), GlobDeclM (), s -> (IO FBOKey, IO (), IO ()))]) a)
- runDrawColors :: DrawColors os s a -> (ExprM (), GlobDeclM (), s -> (IO [FBOKey], IO (), IO ()))
- drawColor :: forall c s os. ColorRenderable c => (s -> (Image (Format c), ColorMask c, UseBlending)) -> FragColor c -> DrawColors os s ()
- draw :: forall a os f s. (s -> Blending) -> FragmentStream a -> (a -> DrawColors os s ()) -> Shader os s ()
- drawDepth :: forall a os f s d. DepthRenderable d => (s -> (Blending, Image (Format d), DepthOption)) -> FragmentStream (a, FragDepth) -> (a -> DrawColors os s ()) -> Shader os s ()
- drawStencil :: forall a os f s st. StencilRenderable st => (s -> (Blending, Image (Format st), StencilOptions)) -> FragmentStream a -> (a -> DrawColors os s ()) -> Shader os s ()
- drawDepthStencil :: forall a os f s d st. (DepthRenderable d, StencilRenderable st) => (s -> (Blending, Image (Format d), Image (Format st), DepthStencilOption)) -> FragmentStream (a, FragDepth) -> (a -> DrawColors os s ()) -> Shader os s ()
- makeFBOKeys :: IO [FBOKey] -> IO (Maybe FBOKey) -> IO (Maybe FBOKey) -> IO FBOKeys
- drawWindowColor :: forall os s c ds. ContextColorFormat c => (s -> (Window os c ds, ContextColorOption c)) -> FragmentStream (FragColor c) -> Shader os s ()
- drawWindowDepth :: forall os s c ds. DepthRenderable ds => (s -> (Window os c ds, DepthOption)) -> FragmentStream FragDepth -> Shader os s ()
- drawWindowColorDepth :: forall os s c ds. (ContextColorFormat c, DepthRenderable ds) => (s -> (Window os c ds, ContextColorOption c, DepthOption)) -> FragmentStream (FragColor c, FragDepth) -> Shader os s ()
- drawWindowStencil :: forall os s c ds. StencilRenderable ds => (s -> (Window os c ds, StencilOptions)) -> FragmentStream () -> Shader os s ()
- drawWindowColorStencil :: forall os s c ds. (ContextColorFormat c, StencilRenderable ds) => (s -> (Window os c ds, ContextColorOption c, StencilOptions)) -> FragmentStream (FragColor c) -> Shader os s ()
- drawWindowDepthStencil :: forall os s c ds. (DepthRenderable ds, StencilRenderable ds) => (s -> (Window os c ds, DepthStencilOption)) -> FragmentStream FragDepth -> Shader os s ()
- drawWindowColorDepthStencil :: forall os s c ds. (ContextColorFormat c, DepthRenderable ds, StencilRenderable ds) => (s -> (Window os c ds, ContextColorOption c, DepthStencilOption)) -> FragmentStream (FragColor c, FragDepth) -> Shader os s ()
- tellDrawcalls :: FragmentStream a -> (a -> (ExprM (), GlobDeclM (), s -> (Either WinId (IO FBOKeys, IO ()), IO ()))) -> ShaderM s ()
- makeDrawcall :: (ExprM (), GlobDeclM (), s -> (Either WinId (IO FBOKeys, IO ()), IO ())) -> FragmentStreamData -> IO (Drawcall s)
- dumpGeneratedFile :: FilePath -> String -> Text -> IO ()
- setColor :: forall c. ColorSampleable c => c -> Int -> FragColor c -> (ExprM (), GlobDeclM ())
- setDepth :: FFloat -> ExprM ()
- make3 :: (t, t1) -> t2 -> (t, t1, t2)
- type FragColor c = Color c (S F (ColorElement c))
- type FragDepth = FFloat
- setGlColorMask :: ColorSampleable f => f -> GLuint -> Color f Bool -> IO ()
- setGlContextColorOptions :: ColorSampleable f => f -> ContextColorOption f -> IO ()
- setGlBlend :: Blending -> IO ()
- setGlDepthOptions :: DepthOption -> IO ()
- setGlStencilOptions :: FrontBack StencilOption -> StencilOp -> StencilOp -> IO ()
- setGlDepthStencilOptions :: DepthStencilOption -> IO ()
- data ContextColorOption f = ContextColorOption Blending (ColorMask f)
- data DepthOption = DepthOption DepthFunction DepthMask
- type StencilOptions = FrontBack StencilOption
- data StencilOption = StencilOption {}
- data DepthStencilOption = DepthStencilOption {}
- data FrontBack a = FrontBack {}
- type ColorMask f = Color f Bool
- type DepthMask = Bool
- type DepthFunction = ComparisonFunction
- type UseBlending = Bool
- data Blending
- type ConstantColor = V4 Float
- data BlendingFactors = BlendingFactors {}
- data BlendEquation
- data BlendingFactor
- usesConstantColor :: BlendingFactor -> Bool
- data LogicOp
- = Clear
- | And
- | AndReverse
- | Copy
- | AndInverted
- | Noop
- | Xor
- | Or
- | Nor
- | Equiv
- | Invert
- | OrReverse
- | CopyInverted
- | OrInverted
- | Nand
- | Set
- data StencilOp
- = OpZero
- | OpKeep
- | OpReplace
- | OpIncr
- | OpIncrWrap
- | OpDecr
- | OpDecrWrap
- | OpInvert
- clearImageColor :: forall c os. ColorRenderable c => Image (Format c) -> Color c (ColorElement c) -> Render os ()
- clearImageDepth :: DepthRenderable d => Image (Format d) -> Float -> Render os ()
- clearImageStencil :: StencilRenderable s => Image (Format s) -> Int -> Render os ()
- clearImageDepthStencil :: Image (Format DepthStencil) -> Float -> Int -> Render os ()
- inWin :: Window os c ds -> IO () -> Render os ()
- clearWindowColor :: forall os c ds. ContextColorFormat c => Window os c ds -> Color c Float -> Render os ()
- clearWindowDepth :: DepthRenderable ds => Window os c ds -> Float -> Render os ()
- clearWindowStencil :: StencilRenderable ds => Window os c ds -> Int -> Render os ()
- clearWindowDepthStencil :: Window os c DepthStencil -> Float -> Int -> Render os ()
- maybeThrow :: Monad m => ExceptT e m (Maybe e) -> ExceptT e m ()
- glTrue :: Num n => n
- getGlBlendEquation :: BlendEquation -> GLenum
- getGlBlendFunc :: BlendingFactor -> GLenum
- getGlLogicOp :: LogicOp -> GLenum
- getGlStencilOp :: StencilOp -> GLenum
Documentation
newtype DrawColors os s a Source #
A monad in which individual color images can be drawn.
DrawColors (StateT Int (Writer [Int -> (ExprM (), GlobDeclM (), s -> (IO FBOKey, IO (), IO ()))]) a) |
Instances
Monad (DrawColors os s) Source # | |
Defined in Graphics.GPipe.Internal.FrameBuffer (>>=) :: DrawColors os s a -> (a -> DrawColors os s b) -> DrawColors os s b # (>>) :: DrawColors os s a -> DrawColors os s b -> DrawColors os s b # return :: a -> DrawColors os s a # | |
Functor (DrawColors os s) Source # | |
Defined in Graphics.GPipe.Internal.FrameBuffer fmap :: (a -> b) -> DrawColors os s a -> DrawColors os s b # (<$) :: a -> DrawColors os s b -> DrawColors os s a # | |
Applicative (DrawColors os s) Source # | |
Defined in Graphics.GPipe.Internal.FrameBuffer pure :: a -> DrawColors os s a # (<*>) :: DrawColors os s (a -> b) -> DrawColors os s a -> DrawColors os s b # liftA2 :: (a -> b -> c) -> DrawColors os s a -> DrawColors os s b -> DrawColors os s c # (*>) :: DrawColors os s a -> DrawColors os s b -> DrawColors os s b # (<*) :: DrawColors os s a -> DrawColors os s b -> DrawColors os s a # |
runDrawColors :: DrawColors os s a -> (ExprM (), GlobDeclM (), s -> (IO [FBOKey], IO (), IO ())) Source #
drawColor :: forall c s os. ColorRenderable c => (s -> (Image (Format c), ColorMask c, UseBlending)) -> FragColor c -> DrawColors os s () Source #
Draw color values into a color renderable texture image.
draw :: forall a os f s. (s -> Blending) -> FragmentStream a -> (a -> DrawColors os s ()) -> Shader os s () Source #
Draw all fragments in a FragmentStream
using the provided function that
passes each fragment value into a DrawColors
monad. The first argument is
a function that retrieves a Blending
setting from the shader environment,
which will be used for all drawColor
actions in the DrawColors
monad
where UseBlending
is True
. (OpenGL 3.3 unfortunately doesn't support
having different blending settings for different color targets.)
TODO: we're using OpenGL 4.5 now. Is this still true?
drawDepth :: forall a os f s d. DepthRenderable d => (s -> (Blending, Image (Format d), DepthOption)) -> FragmentStream (a, FragDepth) -> (a -> DrawColors os s ()) -> Shader os s () Source #
Like draw
, but performs a depth test on each fragment first. The
DrawColors
monad is then only run for fragments where the depth test
passes.
drawStencil :: forall a os f s st. StencilRenderable st => (s -> (Blending, Image (Format st), StencilOptions)) -> FragmentStream a -> (a -> DrawColors os s ()) -> Shader os s () Source #
Like draw
, but performs a stencil test on each fragment first. The
DrawColors
monad is then only run for fragments where the stencil test
passes.
drawDepthStencil :: forall a os f s d st. (DepthRenderable d, StencilRenderable st) => (s -> (Blending, Image (Format d), Image (Format st), DepthStencilOption)) -> FragmentStream (a, FragDepth) -> (a -> DrawColors os s ()) -> Shader os s () Source #
Like draw
, but performs a stencil test and a depth test (in that order)
on each fragment first. The DrawColors
monad is then only run for
fragments where the stencil and depth test passes.
drawWindowColor :: forall os s c ds. ContextColorFormat c => (s -> (Window os c ds, ContextColorOption c)) -> FragmentStream (FragColor c) -> Shader os s () Source #
Draw color values from a FragmentStream
into the window.
drawWindowDepth :: forall os s c ds. DepthRenderable ds => (s -> (Window os c ds, DepthOption)) -> FragmentStream FragDepth -> Shader os s () Source #
Perform a depth test for each fragment from a FragmentStream
in the
window. This doesn't draw any color values and only affects the depth
buffer.
drawWindowColorDepth :: forall os s c ds. (ContextColorFormat c, DepthRenderable ds) => (s -> (Window os c ds, ContextColorOption c, DepthOption)) -> FragmentStream (FragColor c, FragDepth) -> Shader os s () Source #
Perform a depth test for each fragment from a FragmentStream
and write a
color value from each fragment that passes the test into the window.
drawWindowStencil :: forall os s c ds. StencilRenderable ds => (s -> (Window os c ds, StencilOptions)) -> FragmentStream () -> Shader os s () Source #
Perform a stencil test for each fragment from a FragmentStream
in the
window. This doesn't draw any color values and only affects the stencil buffer.
drawWindowColorStencil :: forall os s c ds. (ContextColorFormat c, StencilRenderable ds) => (s -> (Window os c ds, ContextColorOption c, StencilOptions)) -> FragmentStream (FragColor c) -> Shader os s () Source #
Perform a stencil test for each fragment from a FragmentStream
and write
a color value from each fragment that passes the test into the window.
drawWindowDepthStencil :: forall os s c ds. (DepthRenderable ds, StencilRenderable ds) => (s -> (Window os c ds, DepthStencilOption)) -> FragmentStream FragDepth -> Shader os s () Source #
Perform a stencil test and depth test (in that order) for each fragment
from a FragmentStream
in the window. This doesnt draw any color values
and only affects the depth and stencil buffer.
drawWindowColorDepthStencil :: forall os s c ds. (ContextColorFormat c, DepthRenderable ds, StencilRenderable ds) => (s -> (Window os c ds, ContextColorOption c, DepthStencilOption)) -> FragmentStream (FragColor c, FragDepth) -> Shader os s () Source #
Perform a stencil test and depth test (in that order) for each fragment
from a FragmentStream
and write a color value from each fragment that
passes the tests into the window.
tellDrawcalls :: FragmentStream a -> (a -> (ExprM (), GlobDeclM (), s -> (Either WinId (IO FBOKeys, IO ()), IO ()))) -> ShaderM s () Source #
makeDrawcall :: (ExprM (), GlobDeclM (), s -> (Either WinId (IO FBOKeys, IO ()), IO ())) -> FragmentStreamData -> IO (Drawcall s) Source #
setColor :: forall c. ColorSampleable c => c -> Int -> FragColor c -> (ExprM (), GlobDeclM ()) Source #
setGlColorMask :: ColorSampleable f => f -> GLuint -> Color f Bool -> IO () Source #
setGlContextColorOptions :: ColorSampleable f => f -> ContextColorOption f -> IO () Source #
setGlBlend :: Blending -> IO () Source #
setGlDepthOptions :: DepthOption -> IO () Source #
setGlStencilOptions :: FrontBack StencilOption -> StencilOp -> StencilOp -> IO () Source #
setGlDepthStencilOptions :: DepthStencilOption -> IO () Source #
data ContextColorOption f Source #
type StencilOptions = FrontBack StencilOption Source #
data StencilOption Source #
data DepthStencilOption Source #
type ColorMask f = Color f Bool Source #
True
for each color component that should be written to the target.
type DepthFunction = ComparisonFunction Source #
The function used to compare the fragment's depth and the depth buffers depth with. E.g. Less
means "where fragment's depth is less than the buffers current depth".
type UseBlending = Bool Source #
Denotes how each fragment's color value should be blended with the target value.
NoBlending | The fragment's color will simply replace the target value. |
BlendRgbAlpha (BlendEquation, BlendEquation) (BlendingFactors, BlendingFactors) ConstantColor | The fragment's color will be blended using an equation and a set of factors for the RGB components, and a separate equation and set of factors for the Alpha component (if present), and a |
LogicOp LogicOp | A logical operation that will be done on the bits of the fragment color and the target color. This kind of blending is only done on colors that has a
integral internal representation (e.g. |
type ConstantColor = V4 Float Source #
data BlendingFactors Source #
A set of blending factors used for the source (fragment) and the destination (target).
data BlendEquation Source #
The equation used to combine the source (fragment) and the destination (target) after they have been multiplied with their respective BlendingFactor
s.
data BlendingFactor Source #
A factor that the source (fragment) or the destination (target) will be multiplied with before combined with the other in the BlendEquation
.
A bitwise logical operation that will be used to combine colors that has an integral internal representation.
Denotes the operation that will be performed on the target's stencil value
clearImageColor :: forall c os. ColorRenderable c => Image (Format c) -> Color c (ColorElement c) -> Render os () Source #
Fill a color image with a constant color value
clearImageDepth :: DepthRenderable d => Image (Format d) -> Float -> Render os () Source #
Fill a depth image with a constant depth value (in the range [0,1])
clearImageStencil :: StencilRenderable s => Image (Format s) -> Int -> Render os () Source #
Fill a depth image with a constant stencil value
clearImageDepthStencil :: Image (Format DepthStencil) -> Float -> Int -> Render os () Source #
Fill a combined depth stencil image with a constant depth value (in the range [0,1]) and a constant stencil value
clearWindowColor :: forall os c ds. ContextColorFormat c => Window os c ds -> Color c Float -> Render os () Source #
Fill the window's back buffer with a constant color value
clearWindowDepth :: DepthRenderable ds => Window os c ds -> Float -> Render os () Source #
Fill the window's back depth buffer with a constant depth value (in the range [0,1])
clearWindowStencil :: StencilRenderable ds => Window os c ds -> Int -> Render os () Source #
Fill the window's back stencil buffer with a constant stencil value
clearWindowDepthStencil :: Window os c DepthStencil -> Float -> Int -> Render os () Source #
Fill the window's back depth and stencil buffers with a constant depth value (in the range [0,1]) and a constant stencil value
getGlLogicOp :: LogicOp -> GLenum Source #
getGlStencilOp :: StencilOp -> GLenum Source #