Wednesday, December 09, 2015

Existential quantification and GADT in luminance-0.8

luminance 0.8 and existential quantification

It’s been a while I haven’t released anything on my blog. I just wrote a few changes for the latest version of luminance, luminance-0.8.2 and I decided to write about it because I think those changes are interesting on a Haskell level.

The problem

If you haven’t read the changelog yet, I changed the createProgram function and the way it handles uniform interfaces. In luminance < 0.8, you were provided with as many functions as there are uniform kinds. Up to now, luminance supports two uniform kinds:

  • simple uniforms;
    • uniform block (UBO).

So you had two rank-2 functions like forall a. (Uniform a) => Either String Natural -> UniformInterface m (U a) and forall a. (UniformBlock a) => String -> UniformInterface m (U (Region rw (UB a))) to map whichever uniforms you wanted to.

The issue with that is that it requires to break the interface of createProgram each time we want to add a new kind of uniform, and it’s also a pretty hard to read function signature!

So… how does luminance-0.8 solve that?

(Generalized) Algebraic data types, rank-2 and existential quantification

What is the only way we have to select uniforms? Names. Names can either be a String or a Natural for explicit semantics. We could encode such a name using an algebraic data type:

data UniformName
  = UniformName String
    | UniformSemantic Natural
      deriving (Eq,Show)

That’s a good start. Though, we still have the problem of choosing the kind of uniform because we still have several functions – one per kind. We could encode the kind of the uniform directly into the name. After all, when we ask for a uniform mapping through a name, we require to know the kind. So that kind of makes sense. Let’s change our UniformName type:

data UniformName :: * -> * where
  UniformName :: String -> UniformName a
    UniformSemantic :: Natural -> UniformName a
    UniformBlockName :: String -> UniformName (Region rw (UB a))

That’s neat, but with that definition, we won’t go anywhere, because we’re too polymorphic. Indeed, UniformName "foo" :: UniformName a can have any a. We need to put constraints on a. And that’s where GADTs come in so handy! We can hide the constraints in the constructors and bring them into scope when pattern matching. That’s a very neat feature of GADTs. So now, let’s add some constraints to our constructors:

data UniformName :: * -> * where
  UniformName :: (Uniform a) => String -> UniformName a
    UniformSemantic :: (Uniform a) => Natural -> UniformName a
    UniformBlockName :: (UniformBlock a) => String -> UniformName (Region rw (UB a))

Yes! Now, we can write a function that takes a UniformName a, pattern matches it and call the appropriate function regarding the infered shape of a!

However, how do we forward the error? In older version of luminance, we were using ProgramError and more especially two of its constructors: InactiveUniform and InactiveUniformBlock. We need to shrink that to a single InactiveUniform constructor and find a way to store our UniformName… But we can’t yet, because of the a parameter! So the idea is to hide it through existential quantification!

data SomeUniformName = forall a. SomeUniformName (UniformName a)

instance Eq SomeUniformName where
  -- …

instance Show SomeUniformName where
  -- …

And now we can store SomeUniformName in InactiveUniform. We won’t need to recover the type, we just need the constructor and the carried name. By pattern matching, we can recover both those information!

Conclusion

Feel free to have a look at the new createProgram function. As you will see, the type signature is easier to read and to work with! :)

Have fun, and keep the vibe!

Friday, November 13, 2015

OpenGL 3.2 support for luminance!

luminance-0.7

You can’t even imagine how hard it was to release luminance-0.7. I came accross several difficulties I had to spend a lot of time on but finally, here it is. I made a lot of changes for that very special release, and I have a lot to say about it!

Overview

As for all my projects, I always provide people with a changelog. The 0.7 release is a major release (read as: it was a major increment). I think it’s good to tell people what’s new, but it should be mandatory to warn them about what has changed so that they can directly jump to their code and spot the uses of the deprecated / changed interface.

Anyway, you’ll find patch, minor and major changes in luminance-0.7. I’ll describe them in order.

Patch changes

Internal architecture and debugging

A lot of code was reviewed internally. You don’t have to worry about that. However, there’s a new cool thing that was added internally. It could have been marked as a minor change but it’s not supposed to be used by common people – you can use it via a flag if you use cabal or stack though. It’s about debugging the OpenGL part used in luminance. You shouldn’t have to use it but it could be interesting if you spot a bug someday. Anyway, you can enable it with the flag debug-gl.

Uniform Block / Uniform Buffer Objects

The UBO system was buggy and was fixed. You might experience issue with them though. I spotted a bug and reported it – you can find the bug report here. That bug is not Haskell related and is related to the i915 Intel driver.

Minor changes

The minor changes were the most important part of luminance-0.7. luminance now officially supports OpenGL 3.2! When installing luminance, you default to the gl32 backend. You can select the backend you want with flags – gl45 and gl45-bindless-textures – but keep in mind you need the appropriate hardware to be able to use it. Because you need to use flags, you won’t be able to switch to the backend you want at runtime – that’s not the purpose of such a change though.

The performance gap should be minor between gl32 and gl45 but still. Basically, OpenGL 4.5 adds the support for DSA, which is very handy and less ill-designed that previous iterations of OpenGL. So a lot of code had to be rewritten to implement luminance’s stateless interface without breaking performance nor bring them down.

I might add support for other backends later on – like an OpenGL ES backend and WebGL one – but that won’t ship that soon though because I have a ton of work to do, and yet need to provide you with a concrete, beautiful, fast, appealing and eye-blowing demo with luminance! ;)

Feel free to test the gl32 backend and give me back feedback!

However, if I spent so much time on that 0.7 version, it’s because I had issue whilst writing the gl32 backend. Indeed, I spotted several bugs on my Intel HD card. This is my OpenGL version string for my Intel IGP card:

OpenGL core profile version string: 3.3 (Core Profile) Mesa 11.0.4

The architecture is Haswell. And on such a card (i915 linux driver) I’ve found two bugs while trying the gl32 backend with luminance-samples-0.7.

usampler2D

For unknown reason, the Texture sample failed on my Intel IGP but ran smoothly and flawlessly on my nVidia GPU. I spent a lot of time trying to figure out what I was missing, but eventually changed the sampler type – it’s now a sampler2D – and… it worked. I reported the issue to the intel dev team. So if you hit that error too, please leave a message here so that I can have more hindsight about that error and see what I can do.

Uniform block and vec3

This is a very nasty issue that kept me awoken for days trying to fix my code while it was a driver bug. It’s a big technical, so I’ll just leave a link to the bug tracker so that you can read it if you want to.

Breaking changes

Ok, let’s talk.

When creating a new shader stage, you now have to use the function createStage – instead of several functions like createVertexShader. That change is important so that I can add new shader types without changing the interface, and because some shader can fail to be created. For instance, on the gl32 backend, trying to build a tessellation shader will raise an error.

When a shader stage creation fails, the UnsupportedStage error is raised and holds the type of the stage that failed.

Finally, the interface for the cubemaps changed a bit – you don’t have access to width and height anymore, that was error-prone and useless; you’re stick to a size parameter.

I’d like to thank all people supporting me and luminance. I’ll be watching reactions to that major and important release as it will cover more people with cheaper and well-spread GPUs.

Happy hacking! :)

Sunday, October 25, 2015

luminance, episode 0.6: UBO, SSBO, Stackage.

Up to now, luminance has been lacking two cool features: UBO and SSBO. Both are buffer-backed uniform techniques. That is, a way to pass uniforms to shader stages through buffers.

The latest version of luminance has one of the two features. UBO were added and SSBO will follow for the next version, I guess.

What is UBO?

UBO stands for Uniform Bbuffer Object. Basically, it enables you to create uniform blocks in GLSL in feed them with buffers. Instead of passing values directly to the uniform interface, you just write whatever values you want to to buffers, and then pass the buffer as a source for the uniform block.

Such a technique has a lot of advantages. Among them, you can pass a lot of values. It’s also cool when you want to pass values instances of a structure (in the GLSL source code). You can also use them to share uniforms between several shader programs as well as quickly change all the uniforms to use.

In luminance, you need several things. First thing first, you need… a buffer! More specifically, you need a buffer Region to store values in. However, you cannot use any kind of region. You have to use a region that can hold values that will be fetched from shaders. This is done with a type called UB a. A buffer of UB a can be used as UBO.

Let’s say you want to store colors in a buffer, so that you can use them in your fragment shader. We’ll want three colors to shade a triangle. We need to create the buffer and get the region:

colorBuffer :: Region RW (UB (V3 Float)) <- createBuffer (newRegion 3)

The explicit type is there so that GHC can infer the correct types for the Region. As you can see, nothing fancy, except that we just don’t want a Region RW (V3 Float but Region RW (UB (V3 Float)). Why RW?

Then, we’ll want to store colors in the buffer. Easy peasy:

writeWhole colorBuffer (map UB colors)

colors :: [V3 Float]
colors = [V3 1 0 0,V3 0 1 0,V3 0 0 1] -- red, green, blue

At this point, colorBuffer represents a GPU buffer that holds three colors: red, green and blue. The next part is to get the uniform interface. That part is experimental in terms of exposed interface, but the core idea will remain the same. You’re given a function to build UBO uniforms as you also have a function to build simple and plain uniforms in createProgram:

createProgram shaderList $ \uni uniBlock -> {- … -}

Don’t spend too much time reading the signature of that function. You just have to know that uni is a function that takes Either String Natural – either a uniform’s name or its integral semantic – and gives you mapped U in return and that uniBlock does the same thing, but for uniform blocks instead.

Here’s our vertex shader:

in vec2 co;
out vec4 vertexColor;

// This is the uniform block, called "Colors" and storing three colors
// as an array of three vec3 (RGB).
uniform Colors {
  vec3 colors[3];
};

void main() {
  gl_Position = vec4(co, 0., 1.);
  vertexColor = vec4(colors[gl_VertexID], 1.);
}"

So we want to get a U a mapped to that "Colors" uniform block. Easy!

(program,colorsU) <- createProgram shaderStages $ \_ uniBlock -> uniBlock "Colors"

And that’s all! The type of colorsU is U (Region rw (UB (V3 Float))). You can then gather colorBuffer and colorsU in a uniform interface to send colorBuffer to colorsU!

You can find the complete sample here.

Finally, you can augment the type you can use UB with by implementing the UniformBlock typeclass. You can derive the Generic typeclass and then use a default instance:

data MyType = {- … -} deriving (Generic)

instance UniformBlock MyTpe -- we’re good to go with buffer of MyType!

luminance, luminance-samples and Stackage

I added luminance and luminance-samples into Stackage. You can then find them in the nightly snapshots and the future LTS ones.

What’s next?

I plan to add stencil support for the framebuffer, because it’s missing and people might like it included. I will of course add support for *SSBO** as soon as I can. I also need to work on cheddar but that project is complex and I’m still stuck with design decisions.

Thanks for reading my and for your feedback. Have you great week!

Sunday, October 18, 2015

luminance-0.5.1 and wavefront-0.4.0.1

It’s been a few days I haven’t talked about luminance. I’ve been working on it a lot those days along with wavefront. In order that you keep up to date, I’ll describe the changes I made in those packages you have a talk about the future directions of those packages.

I’ll also give a snippet you can use to load geometries with wavefront and adapt them to embed into luminance so that you can actually render them! A package might come up from that kind of snippet – luminance-wavefront? We’ll see that!

wavefront

This package has received several changes among two major increments and several fixes. In the first place, I removed some code from the interface that was useless and used only for test purposes. I removed the Ctxt object – it’s a type used by the internal lexer anyways, so you don’t have to know about it – and exposed a type called WavefrontOBJ. That type reprents the parsed Wavefront data and is the main type used by the library in the interface.

Then, I also removed most of the modules, because they’re re-exported by the main module – Codec.Wavefront. I think the documentation is pretty straight-forward, but you think something is missing, please shoot a PM or an email! ;)

On the bugs level, I fixed a few things. Among them, there was a nasty bug in the implementation of an internal recursive parser that caused the last wavefront statement to be silently ignored.

I’d also like to point out that I performed some benchmarks – I will provide the data later on with a heap profile and graphs – and I’m pretty astonished with the results! The parser/lexer is insanely fast! It only takes a few milliseconds (between 7ms and 8ms) to load 50k faces (a 2MB .obj file). The code is not yet optimized, so I guess the package could go even faster!

You can find the changelog here.

luminance

I made a lot of work on luminance lately. First, the V type – used to represent vertex components – is not anymore defined by luminance but by linear. You can find the type here. You’ll need the DataKinds extension to write types like V 3 Float.

That change is due to the fact linear is a mature library with a lot of interesting functions and types everyone might use when doing graphics. Its V type has several interesting instances – Storable, Ord, etc. – that are required in luminance. Because it’s not simple to build such V, luminance provides you with three functions to build the 1D, 2D and 3D versions – vec2, vec3 and vec4. Currently, that type is the only one you can use to build vertex components. I might add V2, V3 and V4 as well later.

An interesting change: the Uniform typeclass has a lot of new instances! Basically, all vector types from linear, their array version and the 4x4 floating matrix – M44 Float. You can find the list of all instances here.

A new function was added to the Graphics.Lumimance.Geometry module called nubDirect. That function performs in linear logarithmic time and is used to turn a direct representation of vertices into a pair of data used to represent indexed vertices. The new list of vertices stores only unique vertices and the list of integral values stores the indices. You can then use both the information to build indexed geometries – see createGeometry for further details.

The interface to transfer texels to textures has changed. It doesn’t depend on Foldable anymore but on Data.Vector.Storable.Vector. That change is due to the fact that the Foldable solution uses toList behind the hood, which causes bad performance for the simple reason that we send the list to the GPU through the FFI. It’s then more efficient to use a Storable version. Furthermore, th most known package for textures loading – JuicyPixels – already uses that type of Vector. So you just have to enjoy the new performance boost! ;)

About bugs… I fixed a few ones. First, the implementation of the Storable instance for (:.) had an error for sizeOf. The implementation must be lazy in its argument, and the old one was not, causing undefined crashes when using that type. The strictness was removed and now everything works just fine!

Two bugs that were also fixed: the indexed render and the render of geometries with several vertex components. Those bugs were easy to fix and now you won’t experience those issues anymore.

Interfacing luminance with wavefront to render geometries from artists!

I thought it would be a hard task but I’m pretty proud of how easy it was to interface both the packages! The idea was to provide a function that would turn a WavefrontOBJ into a direct representation of luminance vertices. Here’s the function that implements such a conversion:

type Vtx = V 3 Float :. V 3 Float -- location :. normal

objToDirect :: WavefrontOBJ -> Maybe [Vtx]
objToDirect obj = traverse faceToVtx (toList faces)
  where
    locations = objLocations obj
    normals = objNormals obj
    faces = objFaces obj
    faceToVtx face = do
      let face' = elValue face
      vni <- faceNorIndex face'
      v <- locations !? (faceLocIndex face' - 1)
      vn <- normals !? (vni - 1)
      let loc = vec3 (locX v) (locY v) (locZ v)
          nor = vec3 (norX vn) (norY vn) (norZ vn)
      pure (loc :. nor)

As you can see, that function is pure and will eventually turn a WavefrontOBJ into a list of Vtx. Vtx is our own vertex type, encoding the location and the normal of the vertex. You can add texture coordinates if you want to. The function fails if a face’s index has no normal associated with or if an index is out-of-bound.

And… and that’s all! You can already have your Geometry with that – direct one:

  x <- fmap (fmap objToDirect) (fromFile "./ubercool-mesh.obj")
  case x of
    Right (Just vertices) -> createGeometry vertices Nothing Triangle
    _ -> throwError {- whatever you need as error there -}

You want an indexed version? Well, you already have everything to do that:

  x <- fmap (fmap (nubDirect . objToDirect) (fromFile "./ubercool-mesh.obj")
  case x of
    Right (Just (vertices,indices)) -> createGeometry vertices (Just indices) Triangle
    _ -> throwError {- whatever you need as error there -}

Even though the nubDirect performs in a pretty good complexity, it takes time. Don’t be surprised to see the “loading” time longer then.

I might package those snippets and helpers around them into a luminance-wavefront package, but that’s not trivial as the vertex format should be free.

Future directions and thank you

I received a lot of warm feedback from people about what I do in the Haskell community, and I’m just amazed. I’d like to thank each and everyone of you for your support – I even got support from non-Haskellers!

What’s next then… Well, I need to add a few more textures to luminance – texture arrays are not supported yet, and the framebuffers have to be altered to support all kind of textures. I will also try to write a cheddar interpreter directly into luminance to dump the String type of shader stages and replace it with cheddar’s whatever will be. For the long terms, I’ll add UBO and SSBO to luminance, and… compatibility with older OpenGL versions.

Once again, thank you, and keep the vibe!

Sunday, October 11, 2015

Load geometries with wavefront-0.1!

I’ve been away from luminance for a few days because I wanted to enhance the graphics world of Haskell. luminance might be interesting, if you can’t use the art works of your artists, you won’t go any further for a real-world application. I decided that I to write a parser/lexer to load 3D geometries from files. The Wavefront OBJ is an old yet simple and efficient way of encoding such objects. It supports materials, surfaces and a lot of other cool stuff – I don’t cover them yet, though.

There’s a package out there to do that, but it hasn’t been updated since 2008 and has a lot of dependencies I don’t like (InfixApplicative, OpenGL, OpenGLCheck, graphicsFormats, Codec-Image-Devil, and so on…). I like to keep things ultra simple and lightweight. So here we go. wavefront.

Currently, my package only builds up a pure value you can do whatever you want with. Upload it to the GPU, modify it, pretty print it, perform some physics on it. Whatever you want. The interface is not frozen yet and I need to perform some benchmarks to see if I have to improve the performance – the lexer is very simple and naive, I’d be amazed if the performance were that good yet.

As always, feel free to contribute, and keep in mind that the package will move quickly along the performance axis.

Tuesday, October 06, 2015

luminance-0.3 – Adding more texture kinds to the equation…

Unleashing the power of textures!

From luminance-0.1 to luminance-0.2 included, it was not possible to use any texture types different than two-dimensional textures. This blog entry tags the new release, luminance-0.3, which adds support for several kinds of texture.

A bit more dimensions

Texture1D, Texture2D and Texture3D are all part of the new release. The interface has changed – hence the breaking changes yield a major version increment – and I’ll explain how it has.

Basically, textures are now fully polymorphic and are constrained by a typeclass: Texture. That typeclass enables ad hoc polymorphism. It is then possible to add more texture types without having to change the interface, which is cool. Like everything else in luminance, you just have to ask the typesystem which kind of texture you want, and everything will be taken care of for you.

Basically, you have three functions to know:

  • createTexture, which is used to create a new texture ;
  • uploadSub, used to upload texels to a subpart of the texture ;
  • fillSub, used to fill – clear – a subpart of the texture with a given value.

All those functions work on (Texture t) => t, so it will work with all kinds of texture.

Cubemaps

Cubemaps are also included. They work like other textures but add the concept of faces. Feel free to dig in the documentation for further details.

What’s next?

I need to find a way to wrap texture arrays, which are very nice and useful for layered rendering. After that, I’ll try to expose the change to the framebuffers so that we can create framebuffers with cubemaps or that kind of cool feature.

In the waiting, have a good a week!

Thursday, September 24, 2015

luminance first tutorial

Woah!

I’m very happy about people getting interested about my luminance graphics framework. I haven’t received use case feedback yet, but I’m pretty confident I will sooner or later.

In the waiting, I decided to write an embedded tutorial. It can be found here.

That tutorial explains all the basic types of luminance – not all though, you’ll have to dig in the documentation ;) – and describes how you should use it. I will try to add more documentation for each modules in order to end up with a very well documented piece of software!

Let’s sum up what you need

People on reddit complain – they are right to – about the fact the samples just “didn’t work. They actually did, but the errors were muted. I released luminance-0.1.1 to fix that issue. Now you’ll get the proper error messages.

The most common issue is when you try to run a sample without having the required hardware implementation. luminance requires OpenGL 4.5. On Linux, you might need to use primusrun or optirun if you have the Optimus technology. On Windows, I guess you have to allow the samples to run on the dedicated GPU. And on Mac OSX… I have no idea; primusrun / optirun, I’d go.

Anyways, I’d like to thank all people who have/will tried/try the package. As always, I’ll keep you informed about all the big steps I take about luminance. Keep the vibe!

Tuesday, September 22, 2015

luminance 0.1 released!

Here we are

luminance-0.1 was released yesterday night, along with luminance-samples-0.1! I’ll need to enhance the documentation and add directions so that people don’t feel too overwhelmed.

I’m also going to write a wiki to help people get their mind wrapped around luminance.

If you think something is missing; if you think something could be enhanced; or if you’ve found a bug, please, feel free to fill in an issue on the issues tracker.

Next big steps

I need to test the framework. I need a lot of tests. I’ll write a demoscene production with it so that I can give a good feedback to the community and prove that luminance can be used and works.

In the waiting, keep the vibe!

Sunday, September 13, 2015

Thoughts about software meta-design

I’ve been thinking of writing such an article for a while. A few weeks ago, I got contacted by people who wanted to know more about my experience with luminance so that they can have more hindsight about their own APIs and products.

I came to the realization that I could write a blog entry to discuss designs decisions and, at some extent, what a good design entails. Keep in mind it’s only personal thoughts and that I won’t talk for someone else.

Elegancy

I love mathematics because they’re elegant. Elegancy implies several traits, among simplicity, flexibility and transparency. They solve problems with very nice abstractions. In mathematics, we have a concept that is – astonishingly – not very spread and barely known outside of math geeks circles: free objects.

The concept of free is a bit overwhelming at first, because people are used to put labels and examples on everything. For instance, if I say that an object is free, you might already have associated some kind of lock to that object, so that you can get why it’s free. But we’re mistaken. We don’t need locks to define what free implies. In mathematic, a free object is an object that can’t be defined in terms of others. It’s a bit like a core object. It’s free because it can be there, no matter what other objects are around. It has no dependency, it doesn’t require no other interaction. You can also say that such an object is free of extra features that wouldn’t be linked to its nature.

This free property is a very interesting property in mathematics, because it’s surprisingly simple! We can leverage that mathematic abstraction to software design. I like keeping my softwares as much free as possible. That is – with a more human language to say it – constraining them to keep low responsibilities about what they’re doing.

Responsibility domains

The important thing to keep in mind is that you should, at first, define what the responsibility domain is all about. Let’s say you’d like to create a library to implement audio effects, like the Doppler effect – that effect actually exists for any kind of wave, but it’s interesting to synthetize it for a sound-related application. If you end up writing functions or routines to play sound or to load audio samples, you’re already doing it wrong! You’d have violated your reponsibility domain, which is, “audio effects”. Unfortunately, a lot of libraries do that. Adding extra stuff – and sometimes, worse; relying on them!

A lot of people tend to disagree with that – or they just ignore / don’t know. There’re plenty of examples of libraries and softwares that can do everything and nothing. For instance, take Qt – pronounce cute or cutie. At first, Qt is a library and an API to build up GUIs – Graphical User Interfaces – and handle windows, events and so on. Let’s have a look at the documentation of modules, here.

You can see how the responsibility domain is huge! GUI, radio, audio, video, camera, network, database, printing, concurrency and multithreading… Qt isn’t a library anymore; it’s a whole new language!

People tend to like that. “Yeah, I just have to use Qt, and I can do everything!”. Well, that’s a point. But you can also think it another way. Qt is a very massive “library” you’ll spend hours reading the documentation and will use a lot of different classes / functions from different aspects. That doesn’t compose at all. What happens when you want to – or when you don’t have the choice? – use something else? For instance, if you want to use a smaller–but–dedicated threading library? What happens if you want to use a database service you wrote or that you know it’s great? Do you wipeout your Qt use? Do you… try to make both work in harmony? If so, do you have to write a lot of boilerplate code? Do you forget about those technologies and fallback on Qt? Do the concepts map to each others?

The problem with massive libraries is the tight bound it creates between the libraries and the developers. It’s very hard with such libraries to say that you can use it whenever you want because you perfectly know them. You could even just need a few things from it; like, the SQL part. You’ll then have to install a lot of code you’ll perhaps use 10% of.

KISS

I love how the free objects from mathematics can be leveraged to build simpler libraries here. The good part about free objects is the fact that they don’t have any extra features embedded. That’s very cool, because thanks to that, you can reason in terms of such objects as-is. For instance, OpenAL is a very free audio library. Its responsibility domain is to be able to play sound and apply simple effects on them – raw and primary effects. You won’t find anything to load music from files nor samples. And that’s very nice, because the API is small, simple and straight-forward.

Those adjectives are the base of the KISS principle. The ideas behind KISS are simple: keep it simple and stupid. Keep it simple, because the simpler the better. A too complex architecture is bloated and ends up unmaintainable. Simplicity implies elegancy and then, flexibility and composability.

That’s why I think a good architecture is a small – in terms of responsibility – and simple one. If you need complexity, that’s because your responsibility domain is already a bit more complex than the common ones. And even though the design is complex for someone outside of the domain, for the domain itself, it should stay simple and as most straight-forward as possible.

API

I think a good API design is to pick a domain, and stick to it. Whatever extra features you won’t provide, you’ll be able to create other libraries to add those features. Because those features will also be free, they will be useful in other projects that you don’t even have any idea they exist! That’s a very cool aspect of free objects!

There’s also a case in which you have to make sacrifices – and crucial choices. For instance, event-driven programming can be implemented via several techniques. A popular one in the functional programming world nowadays is FRP. Such a library is an architectural codebase. If you end up adding FRP-related code lines in your networking-oriented library, you might be doing it wrong. Because, eh, what if I just want to use imperative event-driven idioms, like observers? You shouldn’t integrate such architectural design choices in specific libraries. Keep them free, so that everyone can quickly learn them, and enjoy them!

I like to see good-designed libraries as a set of very powerful, tiny tools I can compose and move around freely. If a tool gets broken or if it has wrong performances, I can switch to a new one or write my very own. Achieving such a flexibility without following the KISS principle is harder or may be impossible to reach.

So, in my opinion, we should keep things simple and stupid. They’re simpler to reason about, they compose and scale greatly and they of course are easier to maintain. Compose them with architectural or whatever designs in the actual final executable project. Don’t make premature important choices!

Tuesday, September 08, 2015

Luminance – ASAP

We’re almost there!

luminance, the Haskell graphics framework I’ve been working on for a month and a half, will be released very soon as 0.1 on hackage. I’m still working actively on several parts of it, especially the embedded documentation, wikis and main interface.

Keep in mind that the internal design is 80% done, but the end-user interface might change a lot in the future. Because I’m a demoscener, I’ll be using luminance for the next months to release a demoscene production in Germany and provide you with a nice feedback about how usable it is, so that I can make it more mature later on.

What to expect?

Currently, luminance works. You can create buffers, shaders, framebuffers, textures and blend the whole thing to create nice (animated) images. Everything is strongly and (almost) dependently typed, so that you have an extra type safety.

As I was developing the interface, I also wrote a new package that will be released on hackage as well: luminance-samples. As you might have guessed, that package contains several executables you can launch to test luminance. Those are just features sets. There’s an Hello, World! executable, a depth test executable, a blending one, a texture one, and so on and so forth. I’ll refactor them to make the code cleaner, but you should have a look to see what it entails to use luminance! ;)

I’ll be very open-minded about what you guys think of luminance once it gets released. Even though I’ve started writing it for my own purposes, I clearly understand that a lot of people are interested in that project. I’ve been contacted by the developers of waylandmonad to explain them the choices I made with luminance so that they can do the same thing when migrating xmonad from the Xorg technology to Wayland. If I can help in any ways, even if it’s not about luminance directly, don’t hesitate then contact me!

I can’t give you a 0.1 release milestone yet, but you should be able to install it from hackage and stackage very soon! I’ll write an article when it gets released, I promise.

In the waiting, keep the vibe. Happy hacking around!

Sunday, August 23, 2015

Contravariance and luminance to add safety to uniforms

It’s been a few days I haven’t posted about luminance. I’m on holidays, thus I can’t be as involved in the development of the graphics framework as I’m used to on a daily basis. Although I’ve been producing less in the past few days, I’ve been actively thinking about something very important: uniform.

What people usually do

Uniforms are a way to pass data to shaders. I won’t talk about uniform blocks nor uniform buffers – I’ll make a dedicated post for that purpose. The common OpenGL uniform flow is the following:

  1. you ask OpenGL to retrieve the location of a GLSL uniform through the function glGetUniformLocation, or you can use an explicit location if you want to handle the semantics on your own ;
  2. you use that location, the identifier of your shader program and send the actual values with the proper glProgramUniform.

You typically don’t retrieve the location each time you need to send values to the GPU – you only retrieve them once, while initializing.

The first thing to make uniforms more elegant and safer is to provide a typeclass to provide a shared interface. Instead of using several functions for each type of uniform – glProgramUniform1i for Int32, glProgramUniform1f for Float and so on – we can just provide a function that will call the right OpenGL function for the type:

class Uniform a where
  sendUniform :: GLuint -> GLint -> a -> IO ()

instance Uniform Int32 where
  sendUniform = glProgramUniform1i

instance Uniform Float where
  sendUniform = glProgramUniform1f

-- and so on…

That’s the first step, and I think everyone should do that. However, that way of doing has several drawbacks:

  • it still relies on side-effects; that is, we can call sendUniform pretty much everywhere ;
  • imagine we have a shader program that requires several uniforms to be passed each time we draw something; what happens if we forget to call a sendUniform? If we haven’t sent the uniform yet, we might have an undefined behavior. If we already have, we will override all future draws with that value, which is very wrong… ;
  • with that way of representing uniforms, we have a very imperative interface; we can have a more composable and pure approach than that, hence enabling us to gain in power and flexibility.

What luminance used to do

In my luminance package, I used to represent uniforms as values.

newtype U a = U { runU :: a -> IO () }

We can then alter the Uniform typeclass to make it simpler:

class Uniform a where
  toU :: GLuint -> GLint -> U a

instance Uniform Int32 where
  toU prog l = U $ glProgramUniform1i prog l

instance Uniform Float where
  toU prog l = U $ glProgramUniform1f prog l

We also have a pure interface now. I used to provide another type, Uniformed, to be able to send uniforms without exposing IO, and an operator to accumulate uniforms settings, (@=):

newtype Uniformed a = Uniformed { runUniformed :: IO a } deriving (Applicative,Functor,Monad)

(@=) :: U a -> a -> Uniformed ()
U f @= a = Uniformed $ f a

Pretty simple.

The new uniform interface

The problem with that is that we still have the completion problem and the side-effects, because we just wrap them without adding anything special – Uniformed is isomorphic to IO. We have no way to create a type and ensure that all uniforms have been sent down to the GPU…

Contravariance to save us!

If you’re an advanced Haskell programmer, you might have noticed something very interesting about our U type. It’s contravariant in its argument. What’s cool about that is that we could then create new uniform types – new U – by contramapping over those types! That means we can enrich the scope of the hardcoded Uniform instances, because the single way we have to get a U is to use Uniform.toU. With contravariance, we can – in theory – extend those types to all types.

Sounds handy eh? First thing first, contravariant functor. A contravariant functor is a functor that flips the direction of the morphism:

class Contravariant f where
  contramap :: (a -> b) -> f b -> f a
  (>$) :: b -> f b -> f a

contramap is the contravariant version of fmap and (>$) is the contravariant version of (<$). If you’re not used to contravariance or if it’s the first time you see such a type signature, it might seem confusing or even magic. Well, that’s the mathematic magic in the place! But you’ll see just below that there’s no magic no trick in the implementation.

Because U is contravariant in its argument, we can define a Contravariant instance:

instance Contravariant U where
  contramap f u = U $ runU u . f

As you can see, nothing tricky here. We just apply the (a -> b) function on the input of the resulting U a so that we can pass it to u, and we just runU the whole thing.

A few friends of mine – not Haskeller though – told me things like “That’s just theory bullshit, no one needs to know what a contravariant thingy stuff is!”. Well, here’s an example:

newtype Color = Color {
    colorName :: String
  , colorValue :: (Float,Float,Float,Float)
  }

Even though we have an instance of Uniform for (Float,Float,Float,Float), there will never be an instance of Uniform for Color, so we can’t have a U Color… Or can we?

uColor = contramap colorValue float4U

The type of uColor is… U Color! That works because contravariance enabled us to adapt the Color structure so that we end up on (Float,Float,Float,Float). The contravariance property is then a very great ally in such situations!

More contravariance

We can even dig in deeper! Something cool would be to do the same thing, but for several fields. Imagine a mouse:

data Mouse = Mouse {
    mouseX :: Float
  , mouseY :: Float
  }

We’d like to find a cool way to have U Mouse, so that we can send the mouse cursor to shaders. We’d like to contramap over mouseX and mouseY. A bit like with Functor + Applicative:

getMouseX :: IO Float
getMouseY :: IO Float

getMouse :: IO Mouse
getMouse = Mouse <$> getMouseX <*> getMouseY

We could have the same thing for contravariance… And guess what. That exists, and that’s called divisible contravariant functors! A Divisible contravariant functor is the exact contravariant version of Applicative!

class (Contravariant f) => Divisible f where
  divide :: (a -> (b,c)) -> f b -> f c -> f a
  conquer :: f a

divide is the contravariant version of (<*>) and conquer is the contravariant version of pure. You know that pure’s type is a -> f a, which is isomorphic to (() -> a) -> f a. Take the contravariant version of (() -> a) -> f a, you end up with (a -> ()) -> f a. (a -> ()) is isomorphic to (), so we can simplify the whole thing to f a. Here you have conquer. Thank you to Edward Kmett for helping me understand that!

Let’s see how we can implement Divisible for U!

instance Divisible U where
  divide f p q = U $ \a -> do
    let (b,c) = f a
    runU p b
    runU q c
  conquer = U . const $ pure ()

And now let’s use it to get a U Mouse!

let uMouse = divide (\(Mouse mx my) -> (mx,my)) mouseXU mouseYU

And here we have uMouse :: U Mouse! As you can see, if you have several uniforms – for each fields of the type, you can divide your type and map all fields to the uniforms by applying several times divide.

The current implementation is almost the one shown here. There’s also a Decidable instance, but I won’t talk about that for now.

The cool thing about that is that I can lose the Uniformed monadic type and rely only on U. Thanks to the Divisible typeclass, we have completion, and we can’t override future uniforms then!


I hope you’ve learnt something cool and useful through this. Keep in mind that category abstractions are powerful and are useful in some contexts.

Keep hacking around, keep being curious. A Haskeller never stops learning! And that’s what so cool about Haskell! Keep the vibe, and see you another luminance post soon!

Sunday, August 16, 2015

Never forget your git stashes again!

It’s been a while I’m experiencing issues with git stash. If you don’t know that command yet, git stash is used to move all the changes living in your staging area into a special place: the stash.

The stash is a temporary area working like a stack. You can push changes onto it via git stash or git stash save; you can pop changes from top with git stash pop. You can also apply a very specific part of the stack with git stash apply <stash id>. Finally you can get the list of all the stashes with git stash list.

We often use the git stash command to stash changes in order to make the working directory clear again so that we can apply a patch, pull some changes, change branch, and so on. For those purposes, the stash is pretty great.

However, I often forget about my stashes – I know I’m not the only one. Sometimes, I stash something and go to cook something or just go out, and when I’m back again, I might have forgotten about what I had stashed, especially if it was a very small change.

My current prompt for my shell, zsh, is in two parts. I set the PS1 environnment variable to set the regular prompt, and the RPROMPT environnment variable to set a reversed prompt, starting from the right of the terminal. My reversed prompt just performs a git command to check whether we’re actually in a git project, and get the current branch. Simple, but nice.

I came up to the realization that I could use the exact same idea to know whether I have stashed changes so that I never forget them! Here’s a screenshot to explain that:

As you can see, my prompt now shows me how many stashed changes there are around!

The code

I share the code I wrote with you. Feel free to use it, modify it and share it as well!

# …

function gitPrompt() {
  # git current branch
  currentBranch=`git rev-parse --abbrev-ref HEAD 2> /dev/null`
  if (($? == 0))
  then
    echo -n "%F{green}$currentBranch%f"
  fi

  # git stash
  stashNb=`git stash list 2> /dev/null | wc -l`
  if [ "$stashNb" != "0" ]
  then
    echo -n " %F{blue}($stashNb)%f"
  fi

  echo ''
}

PS1="%F{red}%n%F{cyan}@%F{magenta}%M %F{cyan}%~ %F{yellow}%% %f"
RPROMPT='$(gitPrompt)'

# …

Have fun!

Tuesday, August 11, 2015

Luminance – what was that alignment stuff already?

Yesterday, I released a new article about how I implement vertex arrays in luminance. In that article, I told you that the memory was packed with alignment set to 1.

Well, I’ve changed my mind. Some people pointed out that the good thing to do for most GPU is to align on 32-bit. That is, 4 bytes. The alignment should be 4 bytes, then, not 1.

There might be an issue with that. If you store a structure with attributes which sizes are not a multiple of 4 bytes, it’s likely you need to add padding.

However, I just reviewed my code, and found this:

instance (GPU a,KnownNat n,Storable a) => Vertex (V n a) where
instance (Vertex a,Vertex b) => Vertex (a :. b) where

Those are the single instances for Vertex. That means you can only use V and (:.) to build up vertices. Look at the V instance. You’ll find a GPU typeclass constraint. Let’s look at its definition and instances:

class GPU a where
  glType :: Proxy a -> GLenum

instance GPU Float where
  glType _ = GL_FLOAT

instance GPU Int32 where
  glType _ = GL_INT

instance GPU Word32 where
  glType _ = GL_UNSIGNED_INT

Woah. How did I forget that?! Let me translate those information to you. That means we can only have 32-bit vertex component! So the memory inside vertex buffers will always be aligned on 4 bytes! No need to worry about padding then!

The first implication is the fact you won’t be able to use Word16, for instance. You’ll need to stick to the three types that have a GPU instance.

Note: that doesn’t prevent us from adding Double later on, because a Double is a 64-bit type, which is a multiple of 4 bytes!

That’s all I have for today. I’m working on something very exciting linked to render batching. I’ll talk about that when it’s cooked. ;)

Keep the vibe; keep building awesome things, and as always, thank you for reading me!

Monday, August 10, 2015

Luminance – Vertex Arrays

I’ve been up working on vertex arrays in my work-in-progress graphics framework, luminance, for several days. I’m a bit slow, because I’ve been through a very hard breakup and have been struggling to recover and focus. But here I am!

So, what’s new?

OpenGL allows programmers to send vertices to the GPU through what is called a vertex array. Vertex specification is performed through several functions, operating on several objects. You need, for instance, a vertex buffer object, an index buffer object and a vertex array object. The vertex buffer stores the vertices data.

Teapot

Teapot

For instance, you could imagine a teapot as a set of vertices. Those vertices have several attributes. We could use, for instance, a position, a normal and a bone index. The vertex buffer would be responsible of storing those positions, normals and bone indices. There’re two ways to store them:

  1. interleaved arrays ;
  2. deinterleaved arrays.

I’ll explain those later on. The index buffer stores integral numbers – mainly set to unsigned int – that index the vertices, so that we can connect them and create lines, triangles or more complex shapes.

Finally, the vertex array object is a state object that stores links to the two buffers and makes a connection between pointers in the buffer and attribute indices. Once everything is set up, we might only use the vertex array object. The exception is when we need to change the geometry of an object. We need to access the vertex buffer and the index buffer and upload new data. However, for now, that feature is disabled so that the buffers are not exposed to the programmer. If people think that feature should be implemented, I’ll create specialized code for that very purpose.

Interleaved and deinterleaved arrays

Interleaved arrays might be the most simple to picture, because you use such arrays every day when programming. Let’s imagine you have the following type in Haskell:

data Vertex = Vertex {
    vertPos    :: X
  , vertNor    :: Y
  , vertBoneID :: Z
  } deriving (Eq,Show)

Now, the teapot would have several vertices. Approximately, let’s state the teapot has five vertices – yeah, ugly teapot. We can represent such vertices in an interleaved array by simply recording them in a list or an array:

Interleaved

Interleaved

As you can see, the attributes are interleaved in memory, and the whole pattern is cycling. That’s the common way to represent an array of struct in a lot of languages, and it’s very natural for a machine to do things like that.

The deinterleaved version is:

Deinterleaved

Deinterleaved

As you can see, with deinterleaved arrays, all attributes are extracted and grouped. If you want to access the third vertex, you need to read the third X, the third Y and the third Z.

Both the methods have advantages and drawbacks. The cool thing about deinterleaved arrays is that we can copy huge regions of typed memory at once whilst we cannot with interleaved arrays. However, interleaved arrays store continuous structures, so writing and reading a structure back might be faster.

An important point to keep in mind: because we plan to pass those arrays to OpenGL, there’s no alignment restriction on the structure. That is, everything is packed, and we’ll have to pass extra information to OpenGL to tell it how to advance in memory to correctly build vertices back.

Generalized tuple

I think I haven’t told you yet. I have a cool type in luminance: the (:.) type. No, you don’t have to know how to pronounce that. I like to call it the gtuple type, because it’s a generalized tuple. You can encode (a,b), (a,b,c) and all kind of tuples with (:.). You can even encode single-typed infinite tuple! – a very special kind of list, indeed.

data a :. b = a :. b

infixr 6 :.

-- a :. b is isomorphic to (a,b)
-- a :. b :. c is isomorphic to (a,b,c)

newtype Fix f = Fix (f (Fix f)) -- from Control.Monad.Fix
type Inf a = Fix ((:.) a) -- infinite tuple!

Pretty simple, but way more powerful than the regular, monomorphic tuples. As you can see, (:.) is a right-associative. That means that a :. b :. c = a :. (b :. c).

That type will be heavily used in luminance, thus you should get your fet wet with it. There’s actually nothing much to know about it. It’s a Functor. I might add other features to it later on.

The Storable trick

The cool thing about (:.) is that we can provide a Storable instance for packed memory, as OpenGL requires it. Currently, the Storable instance is implemented like this:

instance (Storable a,Storable b) => Storable (a :. b) where
  sizeOf (a :. b) = sizeOf a + sizeOf b
  alignment _ = 1 -- packed data
  peek p = do
    a <- peek $ castPtr p
    b <- peek . castPtr $ p `plusPtr` sizeOf (undefined :: a)
    pure $ a :. b
  poke p (a :. b) = do
    poke (castPtr p) a
    poke (castPtr $ p `plusPtr` sizeOf (undefined :: a)) b

As you can see, the alignment is set to 1 to express the fact the memory is packed. The peek and poke functions use the size of the head of the tuple to advance the pointer so that we effectively write the whole tuple in packed memory.

Then, let’s rewrite our Vertex type in terms of (:.) to see how it’s going on:

type Vertex = X :. Y :. Z

If X, Y and Z are in Storable, we can directly poke one of our Vertex into a luminance buffer! That is, directly into the GPU buffer!

Keep in mind that the Storable instance implements packed-memory uploads and reads, and won’t work with special kinds of buffers, like shader storage ones, which require specific memory alignment. To cover them, I’ll create specific typeclasses instances. No worries.

Creating a vertex array

Creating a vertex array is done through the function createVertexArray. I might change the name of that object – it’s ugly, right? Maybe Shape, or something cooler!

createVertexArray :: (Foldable f,MonadIO m,MonadResource m,Storable v,Traversable t,Vertex v)
                  => t v
                  -> f Word32
                  -> m VertexArray

As you can see, the type signature is highly polymorphic. t and f represent foldable structures storing the vertices and the indices. And that’s all. Nothing else to feed the function with! As you can see, there’s a typeclass constraint on v, the inner vertex type, Vertex. That constraint ensures the vertex type is representable on the OpenGL side and has a known vertex format.

Disclaimer: the Traversable constraint might be relaxed to be Foldable very soon.

Once tested, I’ll move all that code from the unstable branch to the master branch so that you guys can test it. :)

About OpenGL…

I eventually came to the realization that I needed to inform you about the OpenGL prerequisites. Because I want the framework to be as modern and well-designed as possible, you’ll need… OpenGL 4.5. The latest version, indeed. You might also need an extension, ARB_bindless_texture. That would enable the framework to pass textures to shader in a very stateless way, which is our objective!

I’ll let you know what I decide about that. I don’t want to use an extension that is not implemented almost everywhere.

What’s next?

Well, tests! I need to be sure everything is correctly done on the GPU side, especially the vertex format specification. I’m pretty confident though.

Once the vertex arrays are tested, I’ll start defining a render interface as stateless as I can. As always, I’ll keep you informed!

Saturday, August 01, 2015

Luminance – framebuffers and textures

I’m happily suprised that so many Haskell people follow luminance! First thing first, let’s tell you about how it grows.

Well, pretty quickly! There’s – yet – no method to make actual renders, because I’m still working on how to implement some stuff (I’ll detail that below), but it’s going toward the right direction!

Framebuffers

Something that is almost done is the framebuffer part. The main idea of framebuffers – in OpenGL – is supporting offscreen renders, so that we can render to several framebuffers and combine them in several fancy ways. Framebuffers are often bound textures, used to pass the rendered information around, especially to shaders, or to get the pixels through texture reads CPU-side.

The thing is… OpenGL’s framebuffers are tedious. You can have incomplete framebuffers if you don’t attach textures with the right format, or to the wrong attachment point. That’s why the framebuffer layer of luminance is there to solve that.

In luminance, a Framebuffer rw c d is a framebuffer with two formats. A color format, c, and a depth format, d. If c = (), then no color will be recorded. If d = (), then no depth will be recorded. That enables the use of color-only or depth-only renders, which are often optimized by GPU. It also includes a rw type variable, which has the same role as for Buffer. That is, you can have read-only, write-only or read-write framebuffers.

And of course, all those features – having a write-only depth-only framebuffer for instance – are set through… types! And that’s what is so cool about how things are handled in luminance. You just tell it what you want, and it’ll create the required state and manage it for you GPU-side.

Textures

The format types are used to know which textures to create and how to attach them internally. The textures are hidden from the interface so that you can’t mess with them. I still need to find a way to provide some kind of access to the information they hold, in order to use them in shaders for instance. I’d love to provide some kind of monoidal properties between framebuffers – to mimick gloss Monoid instance for its Picture type, basically.

You can create textures, of course, by using the createTexture w h mipmaps function. w is the width, h the height of the texture. mipmaps is the number of mipmaps you want for the texture.

You can then upload texels to the texture through several functions. The basic form is uploadWhole tex autolvl texels. It takes a texture tex and the texels to upload to the whole texture region. It’s your responsibility to ensure that you pass the correct number of texels. The texels are represented with a polymorphic type. You’re not bound to any kind of textures. You can pass a list of texels, a Vector of texels, or whatever you want, as long as it’s Foldable.

It’s also possible to fill the whole texture with a single value. In OpenGL slang, such an operation is often called clearing – clearing a buffer, clearing a texture, clearing the back buffer, and so on. You can do that with fillWhole.

There’re two over functions to work with subparts of textures, but it’s not interesting for the purpose of that blog entry.

Pixel format

The cool thing is the fact I’ve unified pixel formats. Textures and framebuffers share the same pixel format type (Format t c). Currently, they’re all phantom types, but I might unify them further and use DataKinds to promote them to the type-level. A format has two type variables, t and c.

t is the underlying type. Currently, it can be either Int32, Word32 or Float. I might add support for Double as well later on.

c is the channel type. There’re basically five channel types:

  • CR r, a red channel ;
  • CRG r g, red and green channels ;
  • CRGB r g b, red, green and blue channels ;
  • CRGBA r g b a, red, green, blue and alpha channels ;
  • CDepth d, a depth channel (special case of CR; for depths only).

The type variables r, g, b, a and d represent channel sizes. There’re currently three kind of channel sizes:

  • C8, for 8-bit ;
  • C16, for 16-bit ;
  • C32, for 32-bit.

Then, Format Float (CR C32) is a red channel, 32-bit float – the OpenGL equivalent is R32F. Format Word32 (CRGB C8 C8 C16) is a RGB channel with red and green 8-bit unsigned integer channels and the blue one is a 16-bit unsigned integer channel.

Of course, if a pixel format doesn’t exist on the OpenGL part, you won’t be able to use it. Typeclasses are there to enforce the fact pixel format can be represented on the OpenGL side.

Next steps

Currently, I’m working hard on how to represent vertex formats. That’s not a trivial task, because we can send vertices to OpenGL as interleaved – or not – arrays. I’m trying to design something elegant and safe, and I’ll keep you informed when I finally get something. I’ll need to find an interface for the actual render command, and I should be able to release something we can actually use!

By the way, some people already tried it (Git HEAD), and that’s amazing! I’ve created the unstable branch so that I can push unstable things, and keep the master branch as clean as possible.

Keep the vibe, and have fun hacking around!

Friday, July 24, 2015

Introducing Luminance, a safer OpenGL API

A few weeks ago, I was writing Haskell lines for a project I had been working on for a very long time. That project was a 3D engine. There are several posts about it on my blog, feel free to check out.

The thing is… Times change. The more it passes, the more I become mature in what I do in the Haskell community. I’m a demoscener, and I need to be productive. Writing a whole 3D engine for such a purpose is a good thing, but I was going round and round in circles, changing the whole architecture every now and then. I couldn’t make my mind and help it. So I decided to stop working on that, and move on.

If you are a Haskell developer, you might already know Edward Kmett. Each talk with him is always interesting and I always end up with new ideas and new knowledge. Sometimes, we talk about graphics, and sometimes, he tells me that writing a 3D engine from scratch and release it to the community is not a very good move.

I’ve been thinking about that, and in the end, I agree with Edward. There’re two reasons making such a project hard and not interesting for a community:

  1. a good “3D engine” is a specialized one – for FPS games, for simulations, for sport games, for animation, etc. If we know what the player will do, we can optimize a lot of stuff, and put less details into not-important part of the visuals. For instance, some games don’t really care about skies, so they can use simple skyboxes with nice textures to bring a nice touch of atmosphere, without destroying performance. In a game like a flight simulator, skyboxes have to be avoided to go with other techniques to provide a correct experience to players. Even though an engine could provide both techniques, apply that problem to almost everything – i.e. space partitionning for instance – and you end up with a nightmare to code ;
  2. an engine can be a very bloated piece of software – because of point 1. It’s very hard to keep an engine up to date regarding technologies, and make every one happy, especially if the engine targets a large audience of people – i.e. hackage.

Point 2 might be strange to you, but that’s often the case. Building a flexible 3D engine is a very hard and non-trivial task. Because of point 1, you utterly need to restrict things in order to get the required level of performance or design. There are people out there – especially in the demoscene world – who can build up 3D engines quickly. But keep in mind those engines are limited to demoscene applications, and enhancing them to support something else is not a trivial task. In the end, you might end up with a lot of bloated code you’ll eventually zap later on to build something different for another purpose – eh, demoscene is about going dirty, right?! ;)

Basics

So… Let’s go back to the basics. In order to include everyone, we need to provide something that everyone can download, install, learn and use. Something like OpenGL. For Haskell, I highly recommend using gl. It’s built against the gl.xml file – released by Khronos. If you need sound, you can use the complementary library I wrote, using the same name convention, al.

The problem with that is the fact that OpenGL is a low-level API. Especially for new comers or people who need to get things done quickly. The part that bothers – wait, no, annoys – me the most is the fact that OpenGL is a very old library which was designed two decades ago. And we suffer from that. A lot.

OpenGL is a stateful graphics library. That means it maintains a state, a context, in order to work properly. Maintaining a context or state is a legit need, don’t get it twisted. However, if the design of the API doesn’t fit such a way of dealing with the state, we come accross a lot of problems. Is there one programmer who hasn’t experienced black screens yet? I don’t think so.

The OpenGL’s API exposes a lot of functions that perform side-effects. Because OpenGL is weakly typed – almost all objects you can create in OpenGL share the same GL(u)int type, which is very wrong – you might end up doing nasty things. Worse, it uses an internal binding system to select the objects you want to operate on. For instance, if you want to upload data to a texture object, you need to bind the texture before calling the texture upload function. If you don’t, well, that’s bad for you. There’s no way to verify code safety at compile-time.

You’re not convinced yet? OpenGL doesn’t tell you directly how to change things on the GPU side. For instance, do you think you have to bind your vertex buffer before performing a render, or is it sufficient to bind the vertex array object only? All those questions don’t have direct answers, and you’ll need to dig in several wikis and forums to get your answers – the answer to that question is “Just bind the VAO, pal.”

What can we do about it?

Several attempts to enhance that safety have come up. The first thing we have to do is to wrap all OpenGL object types into proper types. For instance, we need several types for Texture and Framebuffer.

Then, we need a way to ensure that we cannot call a function if the context is not setup for. There are a few ways to do that. For instance, indexed monads can be a good start. However, I tried that, and I can tell you it’s way too complicated. You end up with very long types that make things barely unreadable. See this and this for excerpts.

Luminance

In my desperate quest of providing a safer OpenGL’s API, I decided to create a library from scratch called luminance. That library is not really an OpenGL safe wrapper, but it’s very close to being that.

luminance provides the same objects than OpenGL does, but via a safer way to create, access and use them. It’s an effort for providing safe abstractions without destroying performance down and suited for graphics applications. It’s not a 3D engine. It’s a rendering framework. There’s no light, asset managers or that kind of features. It’s just a tiny and simple powerful API.

Example

luminance is still a huge work in progress. However, I can already show an example. The following example opens a window but doesn’t render anything. Instead, it creates a buffer on the GPU and perform several simple operations onto it.

-- Several imports.
import Control.Monad.IO.Class ( MonadIO(..) )
import Control.Monad.Trans.Resource -- from the resourcet package
import Data.Foldable ( traverse_ )
import Graphics.Luminance.Buffer
import Graphics.Luminance.RW
import Graphics.UI.GLFW -- from the GLFW-b package
import Prelude hiding ( init ) -- clash with GLFW-b’s init function

windowW,windowH :: Int
windowW = 800
windowH = 600

windowTitle :: String
windowTitle = "Test"

main :: IO ()
main = do
  init
  -- Initiate the OpenGL context with GLFW.
  windowHint (WindowHint'Resizable False)
  windowHint (WindowHint'ContextVersionMajor 3)
  windowHint (WindowHint'ContextVersionMinor 3)
  windowHint (WindowHint'OpenGLForwardCompat False)
  windowHint (WindowHint'OpenGLProfile OpenGLProfile'Core)
  window <- createWindow windowW windowH windowTitle Nothing Nothing
  makeContextCurrent window
  -- Run our application, which needs a (MonadIO m,MonadResource m) => m
  -- we traverse_ so that we just terminate if we’ve failed to create the
  -- window.
  traverse_ (runResourceT . app) window
  terminate

-- GPU regions. For this example, we’ll just create two regions. One of floats
-- and the other of ints. We’re using read/write (RW) regions so that we can
-- send values to the GPU and read them back.
data MyRegions = MyRegions {
    floats :: Region RW Float
  , ints   :: Region RW Int
  }

-- Our logic.
app :: (MonadIO m,MonadResource m) => Window -> m ()
app window = do
  -- We create a new buffer on the GPU, getting back regions of typed data
  -- inside of it. For that purpose, we provide a monadic type used to build
  -- regions through the 'newRegion' function.
  region <- createBuffer $
    MyRegions
      <$> newRegion 10
      <*> newRegion 5
  clear (floats region) pi -- clear the floats region with pi
  clear (ints region) 10 -- clear the ints region with 10
  readWhole (floats region) >>= liftIO . print -- print the floats as an array
  readWhole (ints region) >>= liftIO . print -- print the ints as an array
  floats region `writeAt` 7 $ 42 -- write 42 at index=7 in the floats region
  floats region @? 7 >>= traverse_ (liftIO . print) -- safe getter (Maybe)
  floats region @! 7 >>= liftIO . print -- unsafe getter
  readWhole (floats region) >>= liftIO . print -- print the floats as an array

Those read/write regions could also have been made read-only or write-only. For such regions, some functions can’t be called, and trying to do so will make your compiler angry and throw errors at you.

Up to now, the buffers are created persistently and coherently. That might cause issues with OpenGL synchronization, but I’ll wait for benchmarks before changing that part. If benchmarking spots performance bottlenecks, I’ll introduce more buffers and regions to deal with special cases.

luminance doesn’t force you to use a specific windowing library. You can then embed it into any kind of host libraries.

What’s to come?

luminance is very young. At the moment of writing this article, it’s only 26 commits old. I just wanted to present it so that people know it exists will be released as soon as possible. The idea is to provide a library that, if you use it, won’t create black screens because of framebuffers incorrectness or buffers issues. It’ll ease debugging OpenGL applications and prevent from making nasty mistakes.

I’ll keep posting about luminance as I get new features implemented.

As always, keep the vibe, and happy hacking!