Difference between revisions of "GPipe"

From HaskellWiki
Jump to navigation Jump to search
(Added textures)
 
(25 intermediate revisions by 4 users not shown)
Line 1: Line 1:
  +
== What is GPipe? ==
{{stub}}
 
   
  +
[http://hackage.haskell.org/package/GPipe GPipe] is a library for programming the GPU (graphics processing unit). It is an alternative to using OpenGl, and has the advantage that it is functional and statically typed as opposed to OpenGl's inherently imperative style. Another important difference with OpenGl is that with GPipe you don't need to write shaders in a second shader language such as GLSL or Cg, but instead use regular Haskell functions on the GPU data types. GPipe uses the same conceptual model as OpenGl, so if you already know OpenGl, getting up to speed with GPipe is quick!
This is a wiki stub for the [http://hackage.haskell.org/package/GPipe GPipe package]. If you have any questions, feel free to [mailto:tobias_bexelius@hotmail.com mail] me.
 
   
== Example ==
+
== Version 2 ==
This is a simple GPipe example that animates a textured box. Besides [http://hackage.haskell.org/package/GPipe GPipe], it uses the
 
[http://hackage.haskell.org/package/Vec-Transform Vec-Transform package] for the transformation matrices, and the [http://hackage.haskell.org/package/GPipe-TextureLoad GPipe-TextureLoad package] for loading textures from disc.
 
   
  +
In 2015, a new major version of GPipe was realeased. Read the announcement [http://tobbebex.blogspot.se/2015/09/gpipe-is-dead-long-live-gpipe.html here on the GPipe blog]!
To run this example, you'll also need an image named "myPicture.jpg" in the same directory (as you see, I used a picture of some wooden planks).
 
   
  +
== Examples and tutorials ==
<haskell>
 
module Main where
 
 
import Graphics.GPipe
 
import Graphics.GPipe.Texture.Load
 
import Data.Monoid
 
import Data.IORef
 
import qualified Data.Vec as Vec
 
import Data.Vec.Nat
 
import Data.Vec.LinAlg.Transform3D
 
import Graphics.UI.GLUT
 
(mainLoop,
 
postRedisplay,
 
idleCallback,
 
getArgsAndInitialize,
 
($=))
 
 
uvCoords = [0:.0:.(), 0:.1:.(), 1:.0:.(), 1:.1:.()]
 
sidePosX = toGPUStream TriangleStrip $ zip [1:.0:.0:.(), 1:.1:.0:.(), 1:.0:.1:.(), 1:.1:.1:.()] (map ((,) (1:.0:.0:.())) uvCoords)
 
sideNegX = toGPUStream TriangleStrip $ zip [0:.0:.1:.(), 0:.1:.1:.(), 0:.0:.0:.(), 0:.1:.0:.()] (map ((,) ((-1):.0:.0:.())) uvCoords)
 
sidePosY = toGPUStream TriangleStrip $ zip [0:.1:.1:.(), 1:.1:.1:.(), 0:.1:.0:.(), 1:.1:.0:.()] (map ((,) (0:.1:.0:.())) uvCoords)
 
sideNegY = toGPUStream TriangleStrip $ zip [0:.0:.0:.(), 1:.0:.0:.(), 0:.0:.1:.(), 1:.0:.1:.()] (map ((,) (0:.(-1):.0:.())) uvCoords)
 
sidePosZ = toGPUStream TriangleStrip $ zip [1:.0:.1:.(), 1:.1:.1:.(), 0:.0:.1:.(), 0:.1:.1:.()] (map ((,) (0:.0:.1:.())) uvCoords)
 
sideNegZ = toGPUStream TriangleStrip $ zip [0:.0:.0:.(), 0:.1:.0:.(), 1:.0:.0:.(), 1:.1:.0:.()] (map ((,) (0:.0:.(-1):.())) uvCoords)
 
   
  +
A comprehensive tutorial in five parts is now available for GPipe 2:
cube = mconcat [sidePosX, sideNegX, sidePosY, sideNegY, sidePosZ, sideNegZ]
 
 
transformedCube a = fmap (transform a) cube
 
transform :: Float -> (Vec3 (Vertex Float), (Vec3 (Vertex Float), Vec2 (Vertex Float))) -> (Vec4 (Vertex Float), (Vec3 (Vertex Float), Vec2 (Vertex Float)))
 
transform a (pos, (norm, uv)) = (transformedPos, (transformedNorm, uv))
 
where
 
modelMat = rotationVec (normalize (1:.0.5:.0.3:.())) a `multmm` translation (-0.5)
 
viewMat = translation (-(0:.0:.2:.()))
 
projMat = perspective 1 100 (pi/3) (4/3)
 
viewProjMat = projMat `multmm` viewMat
 
transformedPos = toGPU (viewProjMat `multmm` modelMat) `multmv` homPoint pos
 
transformedNorm = toGPU (Vec.map (Vec.take n3) $ Vec.take n3 $ modelMat) `multmv` norm
 
 
enlight tex (norm, uv) = let RGB c = sample (Sampler Linear Wrap) tex uv
 
in RGB (c * Vec.vec (norm `dot` toGPU (0:.0:.1:.())))
 
 
coloredFragments tex = fmap (enlight tex) . rasterizeFront . transformedCube
 
   
  +
* [http://tobbebex.blogspot.se/2015/09/gpu-programming-in-haskell-using-gpipe.html Part 1 - Hello world]
paintSolid = paintColor NoBlending (RGB $ Vec.vec True)
 
  +
* [http://tobbebex.blogspot.se/2015/09/gpu-programming-in-haskell-using-gpipe_11.html Part 2 - Buffers and arrays]
 
  +
* [http://tobbebex.blogspot.se/2015/10/gpu-programming-in-haskell-using-gpipe.html Part 3 - Shaders and primitive streams]
main = do getArgsAndInitialize
 
  +
* [http://tobbebex.blogspot.se/2015/10/gpu-programming-in-haskell-using-gpipe_21.html Part 4 - Textures and samplers]
texture <- loadTexture RGB8 "myPicture.jpg" :: IO (Texture2D RGBFormat )
 
  +
* [http://tobbebex.blogspot.se/2015/11/gpu-programming-in-haskell-using-gpipe.html Part 5 - Drawing]
angleRef <- newIORef 0.0
 
newWindow "Spinning box" (100:.100:.()) (800:.600:.())
 
(do angle <- readIORef angleRef
 
writeIORef angleRef ((angle + 0.01) `mod'` (2*pi))
 
return $ paintSolid (coloredFragments texture angle) (newFrameBufferColor (RGB 0))
 
)
 
(\ w -> idleCallback $= Just (postRedisplay (Just w)))
 
mainLoop
 
</haskell>
 
   
  +
* Quake 3 map viewer using GPipe 2, sources on [https://github.com/csabahruska/gpipe-quake3 GitHub].
[[Image:box.jpg]]
 
  +
  +
Use at least version 2.1.3 for the examples in these.
  +
  +
== GPipe 1 Examples and tutorials ==
  +
  +
'' Note that these only applies to the older deprecated version of GPipe ''
  +
  +
* Wiki [[/Tutorial/]] that explains the basic principles of GPipe 1.
  +
* [http://hackage.haskell.org/package/GPipe-Examples GPipe-Examples package], by Kree Cole-McLaughlin features a set of four examples with increasing complexity.
  +
* Csaba Hruska has made a Quake 3 map viewer using GPipe 1, sources on [https://github.com/csabahruska/GFXDemo GitHub].
  +
  +
== Sources ==
  +
  +
All my GPipe related library sources are available on [http://github.com/tobbebex Github]. If you have something to contribute with, just send me a patch and I might merge it into the trunk.
  +
  +
== Other resources ==
  +
  +
=== GPipe 2 ===
  +
  +
* [http://hackage.haskell.org/package/GPipe-GLFW GPipe-GLFW] is the first window management package for GPipe 2.
  +
* [http://hackage.haskell.org/package/linear linear] is the vector math package used by GPipe 2.
  +
  +
=== GPipe 1 ===
  +
  +
* [http://hackage.haskell.org/package/GLUT GLUT] is used in GPipe 1 for window management and the main loop.
  +
* [http://hackage.haskell.org/package/Vec Vec package] is the vector math package used by GPipe 1.
  +
* [http://hackage.haskell.org/package/GPipe-TextureLoad GPipe-TextureLoad package] helps loading textures from disc.
  +
* [http://hackage.haskell.org/package/GPipe-Collada GPipe-Collada package] makes it possible to use Collada files with GPipe.
  +
  +
== Questions and feedback ==
  +
  +
If you have any questions or suggestions, feel free to [mailto:tobias_bexelius@hotmail.com mail] me. I'm also interested in seeing some use cases from the community, as complex or trivial they may be.
  +
  +
[[Category:3D]]
  +
[[Category:Graphics]]
  +
[[Category:Libraries]]
  +
[[Category:Packages]]

Latest revision as of 15:27, 6 January 2016

What is GPipe?

GPipe is a library for programming the GPU (graphics processing unit). It is an alternative to using OpenGl, and has the advantage that it is functional and statically typed as opposed to OpenGl's inherently imperative style. Another important difference with OpenGl is that with GPipe you don't need to write shaders in a second shader language such as GLSL or Cg, but instead use regular Haskell functions on the GPU data types. GPipe uses the same conceptual model as OpenGl, so if you already know OpenGl, getting up to speed with GPipe is quick!

Version 2

In 2015, a new major version of GPipe was realeased. Read the announcement here on the GPipe blog!

Examples and tutorials

A comprehensive tutorial in five parts is now available for GPipe 2:

  • Quake 3 map viewer using GPipe 2, sources on GitHub.

Use at least version 2.1.3 for the examples in these.

GPipe 1 Examples and tutorials

Note that these only applies to the older deprecated version of GPipe

  • Wiki Tutorial that explains the basic principles of GPipe 1.
  • GPipe-Examples package, by Kree Cole-McLaughlin features a set of four examples with increasing complexity.
  • Csaba Hruska has made a Quake 3 map viewer using GPipe 1, sources on GitHub.

Sources

All my GPipe related library sources are available on Github. If you have something to contribute with, just send me a patch and I might merge it into the trunk.

Other resources

GPipe 2

  • GPipe-GLFW is the first window management package for GPipe 2.
  • linear is the vector math package used by GPipe 2.

GPipe 1

Questions and feedback

If you have any questions or suggestions, feel free to mail me. I'm also interested in seeing some use cases from the community, as complex or trivial they may be.