πŸ“» About

A zyghost is the essence of a thing before, during and after that thing's existence. It is a thorough description of what a thing is - the instructions needed to create it. A zyghost is a timeless, permanent encoding of a thing that transcends the thing itself.

My name is Schell Scivally and this is my blog. I'm a guy in Northern California New Zealand who likes to bike, skate, build, and write about things I'm working on.

I like the idea of DNA, code, blueprints and plans as the zyghost of things that can exist in the physical world. This blog serves to explore defining a zyghost and summoning it into existence.

πŸ“Ÿ Contact

I primarily talk through the sites listed at my keybase.

You can see links to the social media sites that I sometimes use in the ^header above.

Around the web I'm found with the handles schell, schellsan and efnx.

You can also reach me at:

  • efsubenovex at the gmail dot com

  • schell.scivally at the narrative dot so

πŸ“™ Guides

I have written a few articles that should help operators get up and running with various technologies.

Intro to Rust Web Development, Frontend

Get started writing frontend web applications in Rust and WASM.

Cooking with Mogwai

Patterns and solutions to common user interface problems, written for use with the mogwai Rust/WASM library

A Rust Beginner's Guide to Message Passing

WIP! Build a non-blocking REPL using Sum Types, Pattern Matching, Threads and Channels.

🚧 Projects

I have a number of ongoing projects that you can investigate or contribute to :) These are labors of love and engineering.

Web Applications

todo-mvc-bench

A suite for interactively benchmarking various todomvc implementations.

Software Libraries

mogwai

The Minimal Obvious Graphical Web Application Interface. It's a library for writing frontend web apps in Rust.

steeloverseer

A file watcher and development tool, similar to Ruby's Guard.

The main idea is that you have steeloverseer watch your files and then execute a series of shell commands in response. The first command to fail short circuits the series. The watched files can be selected using regular expressions and the commands may include capture groups.

varying

Continuously varying values, made easy :)

An FRP implementation like netwire, but simpler.

Consulting and Contracting

I have 15 years of experience building apps of all sizes, distributed services and parsers. I enjoy writing in Haskell and Rust but I'm also proficient in C, Objective C, Javascript and AS3.

If I must I can write C++, Java or Go.

I can read Lisp.

I'd like to learn Prolog.

I have a day job at Software Ltd. / Narrative, so my services are limited to after hours (in New Zealand).

Contact me!

Blog

This is where I put my text files that don't seem to fit anywhere else.

Mogwai 0.6

2023/01/09 - Released mogwai-v0.6.0 and mogwai-dom-v0.1.0

I spent some time over the holidays preparing v0.6.0 of mogwai and v0.1.0 of mogwai-dom, which are libraries for writing user interface elements in a declarative style using streams and sinks. I have been reluctant in the past to advertise my progress on these projects as the API was very experimental but I think it's settling down now as they approach 1.0.

mogwai

mogwai is a library that helps define user interface elements using streams and sinks. It is platform agnostic in that it is not tied to any UI implementation. It only provides primitives for constructing the blueprints of a widget, ie what it is initially, what streams it has as input and what event sinks it has as output. The main exported type of mogwai is ViewBuilder.

Here are some design points:

  • Platform agnostic - ViewBuilder definitions can be converted into a platform-specific UI implementation by third party libraries. Currently only mogwai-dom exists publicly as one of these third-party libs but I plan on writing mogwai-tui and I do have a private library mogwai-pxy which does this for my own custom 3d game/app engine pxy which itself is quite a lot like bevy.
  • Provides convenient macros like rsx! and html! to build widgets.
  • Async widget tasks can easily access the raw platform-specific UI view as needed, so you can do what you need to do even if mogwai hasn't thought of it.

mogwai-dom

mogwai-dom is a library that provides a TryFrom<ViewBuilder> implementation for JsDom, which is a thin wrapper around JsValue web-sys crate, allowing the user to create browser DOM widgets that can access the browser's Javascript APIs.

Here are some design points:

  • There is no VDOM, streams patch the DOM directly and asynchronously. This means there is no diff-phase, which cuts down some of the CPU overhead.
  • Easily access the raw web-sys types through JsDom
  • Provides a non-browser DOM node type SsrDom to build DOM server-side for rendering.
  • Provides a target agnostic DOM node type Dom that is JsDom on wasm32 and SsrDom otherwise, as well as hydration from existing DOM for writing "isomorphic" apps.

Ecosystem

The mogwai-* libraries are not fully fledged frameworks like dioxus and yew etc, but they do exist in the same space. mogwai is more like a layer in your frontend stack. It doesn't come with a lot of batteries, but it also doesn't come with much dogma. It's quite a "barebones" wrapper around whatever the underlying UI platform is, but I feel it gets you 80% of the way there for 20% of the effort/lock-in.

Thank you

Thanks for taking the time to read this! Please let me know here or at the repo (or on any of the other channels you may find me) if you have any concerns, bugs, feature requests, etc.

πŸ˜ƒβ˜•πŸ˜ƒβ˜•πŸ˜ƒβ˜•

πŸ—žοΈ Articles

Sometimes I write one-off articles. They are generally about software and hardware.

πŸ’¬ Rendering fonts in Haskell with Freetype2 and OpenGL

Intro

My last adventure in programming was using Haskell to hook up freetype2 to OpenGL. Freetype is a font rasterization library. The idea is that you use freetype to load a font and render it into an opengl texture, then render some font textured geometry in order to display strings of characters on the screen. The idea is simple enough but like many graphics projects there a a couple of gotchas that I bumped up against and dumped a significant amount of time into. I'm including code below to load a character into an OpenGL texture but I'm not including the surrounding code to render that texture. You should be able to use the loaded texture to draw a quad to see the character.

Setup

So what I would like is a function that given a path to a ttf font file, a character and a pixel size - returns an opengl texture object that I can use to render a quad representing the character.

loadCharacter :: FilePath -> Char -> Int -> IO TextureObject
loadCharacter path char px = undefined

Freetype

The first step was to find some freetype2 bindings. Jason Dagit (lispy on #haskell irc) wrote some raw bindings that are on hackage. It works quite well and he has also posted an example of rendering a string of characters as ascii images in a terminal. Between that and the freetype2 tutorial you should be able to get a good idea of the process behind rendering a font glyph into a freetype bitmap.

Helpers

Here we have some convenience functions. The first unboxes an IO FT_Error and fails if the FT_Error is non zero.

runFreeType :: IO FT_Error -> IO ()
runFreeType m = do
    r <- m
    unless (r == 0) $ fail $ "FreeType Error:" ++ show r

This code is simple enough. It arises from having to check almost every freetype operation for an error. None the less, I borrowed it from a package on hackage I found by checking the reverse package dependencies on the freetype2 bindings and looking at the source of the defunct free-game package. This is one of the things that I love about Haskell. There are lots of high quality tools, resources and people to help you find the answers you need.

The next helper function allocs a c pointer for a FT_Library handle. This handle is needed for about half of the Freetype calls.

freeType :: IO FT_Library
freeType = alloca $ \p -> do
    runFreeType $ ft_Init_FreeType p
    peek p

Then we have a helper that given the FT_Library and a FilePath returns a loaded font face as a FT_Face.

fontFace :: FT_Library -> FilePath -> IO FT_Face
fontFace ft fp = withCString fp $ \str ->
    alloca $ \ptr -> do
        runFreeType $ ft_New_Face ft str 0 ptr
        peek ptr

Lastly this function just gives us a string from a glyph format, FT_Glyph_Format, which we use when we output our glyph info.

glyphFormatString :: FT_Glyph_Format -> String
glyphFormatString fmt
    | fmt == ft_GLYPH_FORMAT_COMPOSITE = "ft_GLYPH_FORMAT_COMPOSITE"
    | fmt == ft_GLYPH_FORMAT_OUTLINE = "ft_GLYPH_FORMAT_OUTLINE"
    | fmt == ft_GLYPH_FORMAT_PLOTTER = "ft_GLYPH_FORMAT_PLOTTER"
    | fmt == ft_GLYPH_FORMAT_BITMAP = "ft_GLYPH_FORMAT_BITMAP"
    | otherwise = "ft_GLYPH_FORMAT_NONE"

###Loading a Freetype bitmap Here we have our loadCharacter function above - fleshed out for loading a glyph, rendering it into a Freetype bitmap and then printing some info about it to the console.

loadCharacter :: FilePath -> Char -> Int -> IO TextureObject
loadCharacter path char px = do
    -- FreeType (http://freetype.org/freetype2/docs/tutorial/step1.html)
    ft <- freeType

    -- Get the Ubuntu Mono fontface.
    ff <- fontFace ft path
    runFreeType $ ft_Set_Pixel_Sizes ff (fromIntegral px) 0

    -- Get the unicode char index.
    chNdx <- ft_Get_Char_Index ff $ fromIntegral $ fromEnum char

    -- Load the glyph into freetype memory.
    runFreeType $ ft_Load_Glyph ff chNdx 0

    -- Get the GlyphSlot.
    slot <- peek $ glyph ff

    -- Number of glyphs
    n <- peek $ num_glyphs ff
    putStrLn $ "glyphs:" ++ show n

    fmt <- peek $ format slot
    putStrLn $ "glyph format:" ++ glyphFormatString fmt

    -- This is [] for Ubuntu Mono, but I'm guessing for bitmap
    -- fonts this would be populated with the different font
    -- sizes.
    putStr "Sizes:"
    numSizes <- peek $ num_fixed_sizes ff
    sizesPtr <- peek $ available_sizes ff
    sizes <- forM [0 .. numSizes-1] $ \i ->
        peek $ sizesPtr `plusPtr` fromIntegral i :: IO BS.FT_Bitmap_Size
    print sizes

    l <- peek $ bitmap_left slot
    t <- peek $ bitmap_top slot
    putStrLn $ concat [ "left:"
                      , show l
                      , "\ntop:"
                      , show t
                      ]

    runFreeType $ ft_Render_Glyph slot ft_RENDER_MODE_NORMAL

    -- Get the char bitmap.
    bmp <- peek $ bitmap slot
    putStrLn $ concat ["width:"
                      , show $ width bmp
                      , " rows:"
                      , show $ rows bmp
                      , " pitch:"
                      , show $ pitch bmp
                      , " num_grays:"
                      , show $ num_grays bmp
                      , " pixel_mode:"
                      , show $ pixel_mode bmp
                      , " palette_mode:"
                      , show $ palette_mode bmp
                      ]
    -- ...continued in the next section...

Then the next problem is getting that bitmap into an OpenGL texture.

OpenGL

First try

Now that we have our glyph rendering into a freetype bitmap we can take that bitmap and buffer it into an OpenGL texture. The first step is to generate our texture name, activate it, etc - all the normal texture stuff.

    -- Generate an opengl texture.
    [tex] <- genObjectNames 1
    texture Texture2D $= Enabled
    activeTexture     $= TextureUnit 0
    textureBinding Texture2D $= Just tex
    printError

Next we need buffer the data into the texture. We know from the freetype tutorial that the bitmap buffer is an array of 8bit chars representing a single channel of grayscale levels 0-255. We also already have a pointer to the data with buffer bmp. So we can use that info to set up our texImage2D to take the bitmap buffer from freetype directly.

    putStrLn "Buffering glyph bitmap into texture."
    texImage2D
        Texture2D
        NoProxy
        0
        R8
        (TextureSize2D w' h')
        0
        (PixelData Red UnsignedByte $ buffer bmp)
    printError

    putStrLn "Texture loaded."

Then we need to complete the texture by setting some filter parameters and return the texture name to end our function.

    -- Complete the texture by setting some filtering parameters.
    textureFilter   Texture2D   $= ((Linear', Nothing), Linear')
    textureWrapMode Texture2D S $= (Repeated, ClampToEdge)
    textureWrapMode Texture2D T $= (Repeated, ClampToEdge)

    return tex

When you run that code you can either inspect your running OpenGL instance to see the buffered texture or you can draw a quad with it. If you set these filter parameters incorrectly or at the wrong time you'll still be able to see your texture in a profiler but OpenGL will consider it incomplete and will not render it. I found out that I was originally running into this problem because I was setting these params before I bound and buffered my texture. This OpenGL wiki entry about incomplete textures helped me out. After I figured that out my program spat out something that looked like

a torn glyph

If you look closely you can see that there seems to be some noise at the bottom of the texture, which made me think that maybe OpenGL is reading past the end of the freetype buffer and getting some trash input. You can also see that the texture is obviously torn. With my settings of using Ubuntu Mono to render a Z at 251 pixels my loadCharacter function outputs

glyphs:1296
glyph format:ft_GLYPH_FORMAT_OUTLINE
Sizes:[]
left:0
top:0
width:101 rows:155 pitch:101 num_grays:256 pixel_mode:2 palette_mode:0
Buffering glyph bitmap into texture.
Texture loaded.

Fixing the tearing with padding

I got stuck for a while trying to figure out what was causing the tearing. I thought it may be the pixel format, OpenGL's texture storage or whatever. I ended up just playing with the input to the loadCharacter function for a while to see how the tearing changed and eventually figured out that some of them rendered perfectly - like Ubuntu Mono at 270 pixels.

a perfect glyph

glyphs:1296
glyph format:ft_GLYPH_FORMAT_OUTLINE
Sizes:[]
left:0
top:0
width:108 rows:167 pitch:108 num_grays:256 pixel_mode:2 palette_mode:0
Buffering glyph bitmap into texture.
Texture loaded.

The only difference I could see in the output info was that the width, rows and pitch were different, which makes sense because the bitmaps are different sizes. What I eventually figured out is that the latter's pitch is a multiple of four while the former's is not. Apparently (and forgive me if I'm wrong) but OpenGL likes texture widths that are divisible by four. So what I did was to change the buffering portion of loadCharacter to pad the texture every width pixels with some number of blank pixels to make the width a multiple of four.

First we need a pure padding function.

addPadding :: Int -> Int -> a -> [a] -> [a]
addPadding _ _ _ [] = []
addPadding amt w val xs = a ++ b ++ c
    where a = take w xs
          b = replicate amt val
          c = addPadding amt w val (drop w xs)

Then we need to get our bitmap data into Haskell and pad it, then buffer that data into OpenGL.

    let w  = fromIntegral $ width bmp
        h  = fromIntegral $ rows bmp
        w' = fromIntegral w :: Integer
        h' = fromIntegral h
        p  = 4 - w `mod` 4
        nw = p + fromIntegral w'

    putStrLn $ "padding by " ++ show p

    -- Get the raw bitmap data.
    bmpData <- peekArray (w*h) $ buffer bmp

    let data' = addPadding p w 0 bmpData

    -- Generate an opengl texture.
    [tex] <- genObjectNames 1
    texture Texture2D $= Enabled
    activeTexture     $= TextureUnit 0
    textureBinding Texture2D $= Just tex
    printError

    putStrLn "Buffering glyph bitmap into texture."
    withArray data' $ \ptr -> texImage2D
        Texture2D
        NoProxy
        0
        R8
        (TextureSize2D (fromIntegral nw) h')
        0
        (PixelData Red UnsignedByte ptr)
    printError

    putStrLn "Texture loaded."
    textureFilter   Texture2D   $= ((Linear', Nothing), Linear')
    textureWrapMode Texture2D S $= (Repeated, ClampToEdge)
    textureWrapMode Texture2D T $= (Repeated, ClampToEdge)

    return tex

Which gives us a perfectly rendered anti-aliased glyph.

a perfect glyph

Fixing it with row alignment

Later thanks to reddit I found out that you can reset the row alignment in OpenGL with one call.

rowAlignment Unpack $= 1

This will change the default unpacking row alignment from 4 to 1 and fix our tearing issue.

Finally

Altogether the code will look something like

module Graphics.Text.Font where

import           Control.Monad
import           Graphics.Rendering.OpenGL hiding (bitmap)
import           Graphics.Rendering.OpenGL.GL.PixelRectangles.PixelStorage
import           Graphics.Rendering.FreeType.Internal
import           Graphics.Rendering.FreeType.Internal.PrimitiveTypes
import           Graphics.Rendering.FreeType.Internal.Library
import           Graphics.Rendering.FreeType.Internal.FaceType
import           Graphics.Rendering.FreeType.Internal.Face
import           Graphics.Rendering.FreeType.Internal.GlyphSlot
import           Foreign
import           Foreign.C.String
import           Graphics.Rendering.FreeType.Internal.Bitmap
import           Graphics.Texture.Load
import           Graphics.Utils
import qualified Graphics.Rendering.FreeType.Internal.BitmapSize as BS

loadCharacter :: FilePath -> Char -> Int -> Int -> IO TextureObject
loadCharacter path char px texUnit = do
    -- FreeType (http://freetype.org/freetype2/docs/tutorial/step1.html)
    ft <- freeType

    -- Get the Ubuntu Mono fontface.
    ff <- fontFace ft path
    runFreeType $ ft_Set_Pixel_Sizes ff (fromIntegral px) 0

    -- Get the unicode char index.
    chNdx <- ft_Get_Char_Index ff $ fromIntegral $ fromEnum char

    -- Load the glyph into freetype memory.
    runFreeType $ ft_Load_Glyph ff chNdx 0

    -- Get the GlyphSlot.
    slot <- peek $ glyph ff

    -- Number of glyphs
    n <- peek $ num_glyphs ff
    putStrLn $ "glyphs:" ++ show n

    fmt <- peek $ format slot
    putStrLn $ "glyph format:" ++ glyphFormatString fmt

    -- This is [] for Ubuntu Mono, but I'm guessing for bitmap
    -- fonts this would be populated with the different font
    -- sizes.
    putStr "Sizes:"
    numSizes <- peek $ num_fixed_sizes ff
    sizesPtr <- peek $ available_sizes ff
    sizes <- forM [0 .. numSizes-1] $ \i ->
        peek $ sizesPtr `plusPtr` fromIntegral i :: IO BS.FT_Bitmap_Size
    print sizes

    l <- peek $ bitmap_left slot
    t <- peek $ bitmap_top slot
    putStrLn $ concat [ "left:"
                      , show l
                      , "\ntop:"
                      , show t
                      ]

    runFreeType $ ft_Render_Glyph slot ft_RENDER_MODE_NORMAL

    -- Get the char bitmap.
    bmp <- peek $ bitmap slot
    putStrLn $ concat ["width:"
                      , show $ width bmp
                      , " rows:"
                      , show $ rows bmp
                      , " pitch:"
                      , show $ pitch bmp
                      , " num_grays:"
                      , show $ num_grays bmp
                      , " pixel_mode:"
                      , show $ pixel_mode bmp
                      , " palette_mode:"
                      , show $ palette_mode bmp
                      ]

    let w  = fromIntegral $ width bmp
        h  = fromIntegral $ rows bmp
        w' = fromIntegral w
        h' = fromIntegral h

    -- Set the texture params on our bound texture.
    texture Texture2D $= Enabled

    -- Set the alignment to 1 byte.
    rowAlignment Unpack $= 1

    -- Generate an opengl texture.
    tex <- newBoundTexUnit texUnit
    printError

    putStrLn "Buffering glyph bitmap into texture."
    texImage2D
        Texture2D
        NoProxy
        0
        R8
        (TextureSize2D w' h')
        0
        (PixelData Red UnsignedByte $ buffer bmp)
    printError

    putStrLn "Texture loaded."
    textureFilter   Texture2D   $= ((Linear', Nothing), Linear')
    textureWrapMode Texture2D S $= (Repeated, ClampToEdge)
    textureWrapMode Texture2D T $= (Repeated, ClampToEdge)

    return tex


addPadding :: Int -> Int -> a -> [a] -> [a]
addPadding _ _ _ [] = []
addPadding amt w val xs = a ++ b ++ c
    where a = take w xs
          b = replicate amt val
          c = addPadding amt w val (drop w xs)


glyphFormatString :: FT_Glyph_Format -> String
glyphFormatString fmt
    | fmt == ft_GLYPH_FORMAT_COMPOSITE = "ft_GLYPH_FORMAT_COMPOSITE"
    | fmt == ft_GLYPH_FORMAT_OUTLINE = "ft_GLYPH_FORMAT_OUTLINE"
    | fmt == ft_GLYPH_FORMAT_PLOTTER = "ft_GLYPH_FORMAT_PLOTTER"
    | fmt == ft_GLYPH_FORMAT_BITMAP = "ft_GLYPH_FORMAT_BITMAP"
    | otherwise = "ft_GLYPH_FORMAT_NONE"


runFreeType :: IO FT_Error -> IO ()
runFreeType m = do
    r <- m
    unless (r == 0) $ fail $ "FreeType Error:" ++ show r


freeType :: IO FT_Library
freeType = alloca $ \p -> do
    runFreeType $ ft_Init_FreeType p
    peek p


fontFace :: FT_Library -> FilePath -> IO FT_Face
fontFace ft fp = withCString fp $ \str ->
    alloca $ \ptr -> do
        runFreeType $ ft_New_Face ft str 0 ptr
        peek ptr

The code above contains some other helper functions that I haven't mentioned. You can find them in their respective modules at my github.

Links I wish I had before I wrote this

2014/08/01

⌨️ My Keyboard

2015/09/05 - Beginning the dream of replicating my datahand keyboard

2018/10/06 - I've picked this project back up and am working on new designs

I use a Datahand keyboard. It's the best thing that's happened to my fingers and wrists since... It's the best thing that has ever happened to my fingers and wrists. I see a lot of parallels between the Datahand and pure functional programming (lol). They both take lots of commitment. They change the entire way you think about their domain, but what they offer in return is a big improvement in experience and productivity. I have found that I really love programming in Haskell, and I really love typing on my Datahand. The combination is like a drug.

Unfortunately the company that produces the Datahand went out of business years ago due to shady dealings and mismanagement. I got the inside scoop from one of Datahand's ex-excutives, but that's a different story all together. I realized that if anything were to happen to even one key on my keyboard I'd be up poop creek trying to find a replacement. No other keyboard comes close to the Datahand with the effortless, clicky waves my hands perform in order to make characters appear on the screen. I have a Happy Hacking Pro 2 (which I keep close to my heart) and previously a blank Das Keyboard. Neither keyboard comes close. I would have procured a Kinesis Advantage if I hadn't had an oppurtunity to skip that level entirely and warp straight to the Datahand. I'd love to hear about the comparison between the two from someone who owns both but the Datahand is becoming exceedingly rare, making that situation rather uncommon.

Something has to be done - the alternate future that never was (in which er'body typing well) must live again. Now is the time. The 90's are back and people are finally ready to revisit odd looking hardware (as well as clunky boots, trench coats, dreadlocks and AI).

Some other folks agree with me and have made some really great strides toward recreating the Datahand. I'd love to get in a group buy of that project if it ever comes to fruition. In the meantime I've bought a 3d printer and started designing my own take on the old Datahand with a few twists. I can't wait to show you. Here's a picture of my desktop real quick:

prototyping a new keyboard

Pictured here are three prototype magnetic switches, some refuse, tools, a teensy++ (my board of choice) and a small circuit involving a unipolar hall effect switch.

This is going to be a very fun project.

Comments on Hacker News

πŸ•ΉοΈ reflex-sdl2 is FRP for Haskell SDL2 applications

This past weekend I had a few moments to spend writing a reflex host for sdl applications. I expected the task to be much harder - a testament to the two libraries' authors! So - standing on the shoulders of giants is a new barebones package for starting game and multimedia projects (in Haskell) called reflex-sdl2.

The hackage docs contain a link to a small sample that compiles into a desktop app. If everything works, you should see some 1980's stlye neon colored squares appear whenever you click or release your mouse :)

Thanks to Ryan Trinkle for helping me brainstorm and letting me bug him about types at odd hours of the night and for giving this new library an official place to live.

Reddit r/haskell comments

2017-08-21

πŸ“Ί Datatypes can be rendered

I've been working on a purely functional GUI and I realized that the structures I've been using for rendering could be easily abstracted out into a library. The ideas are simple enough.

The main idea behind renderable is that all graphics can be broken down into primitives.

Rendering

A rendering is simply an effectful value that draws something on the screen in a specific place. Also needed is an effectful value that releases any resources allocated when creating the rendering. Since both values are created at the same time from here on out a "rendering" will be a tuple of the two. So let's dive into what we'll be rendering.

Primitive

First off we have the typeclass Primitive. A primitive is an atomic unit of "graphics". In my current project I've chosen to render boxes, polylines and text. Each of these are a primitive that I'll use in different combinations to create my interface. Primitive has three associated types - a monad, a transform type and a resource type. The monad represents the context of the primitive rendering calls themselves and in most cases will be the IO monad. If you're using OpenGL you'll probably use IO. The transform represents the kind of transformations you will apply to your primitives. I'm using a two dimensional affine transformation but you can use anything. It just represents how a rendering can be changed without having to alter the underlying resources.

Lastly the resource type is whatever datatype holds the resources needed to render primitives. This may be a record that holds shaders or references to windows, fonts, etc. For my current project I'm using a Rez

data Rez = Rez { rezGeom      :: GeomRenderSource
               , rezBez       :: BezRenderSource
               , rezMask      :: MaskRenderSource
               , rezWindow    :: Window
               , rezFont      :: Font
               , rezIcons     :: Font
               } deriving (Typeable)

Primitives must have Hashable instances - this is so they can be cached after being allocated. If you're using OpenGL like I am then 'allocation' means making some IO calls in order to send geometry and other data to the GPU. The compilePrimitive function is where we run the initial IO calls to allocate resources for the datatype's rendering and then return a tuple of the cleanup function and the draw function. Since all Primitive instances are also instances of Hashable the renderable package will automatically look up any needed renderings in the cache, create new ones and release stale ones without you having to think about it.

Here are some Primitive instances to give you an example - they use another (very) experimental project of mine called gelatin, which at this point is a thin wrapper around gl that provides some very specific things I need for my programs


-- Unit for fun
instance Primitive () where
    type PrimM () = IO
    type PrimR  () = Rez
    type PrimT  () = Transform
    compilePrimitive _ _ = return (return (), const $ return ())

-- Polyline
instance Primitive Polyline where
    type PrimM Polyline = IO
    type PrimR  Polyline = Rez
    type PrimT  Polyline = Transform
    compilePrimitive (Rez geom _ _ win _ _) Polyline{..} = do
        let fill = solid polylineColor
            p = polyline EndCapSquare LineJoinMiter polylineWidth polylinePath
        Rendering f c <- filledTriangleRendering win geom p fill
        return (c, f)

instance Hashable Polyline where
    hashWithSalt s Polyline{..} =
        s `hashWithSalt` polylineWidth
            `hashWithSalt` polylineColor
                `hashWithSalt` polylinePath

data Polyline = Polyline { polylineWidth     :: Float
                         , polylineColor     :: Color
                         , polylinePath      :: [V2 Float]
                         } deriving (Show, Eq, Typeable, Generic)

path2Polyline :: Float -> Color -> Path -> Polyline
path2Polyline = Polyline

-- Box
boxPath :: Box -> Path
boxPath Box{..} = poly
    where poly = [V2 x1 y1, V2 x2 y1, V2 x2 y2, V2 x1 y2, V2 x1 y1]
          (V2 w h) = boxSize
          x1 = 0
          x2 = w
          y1 = 0
          y2 = h

boxPolyline :: Float -> Box -> Polyline
boxPolyline lw Box{..} = Polyline lw boxColor path
    where path = [V2 x1 y1, V2 x2 y1, V2 x2 y2, V2 x1 y2, V2 x1 y1]
          (V2 w h) = boxSize
          x1 = -hw
          x2 = w + hw
          y1 = -hw
          y2 = h + hw
          hw = lw/2

data Box = Box { boxSize      :: Size
               , boxColor     :: Color
               } deriving (Show, Eq, Typeable, Generic)

instance Hashable Box where
    hashWithSalt s (Box sz c) = s `hashWithSalt` sz `hashWithSalt` c

instance Primitive Box where
    type PrimM Box = IO
    type PrimR Box  = Rez
    type PrimT Box  = Transform
    compilePrimitive (Rez geom _ _ win _ _) (Box (V2 w h) c) = do
        let [tl, tr, br, bl] = [zero, V2 w 0, V2 w h, V2 0 h]
            vs = [tl, tr, br, tl, br, bl]
            cs = replicate 6 c
        Rendering f c' <- colorRendering win geom GL_TRIANGLES vs cs
        return (c',f)

-- PlainText
instance Primitive PlainText where
    type PrimM PlainText = IO
    type PrimR PlainText = Rez
    type PrimT PlainText = Transform
    compilePrimitive (Rez geom bz _ win font _) (PlainText str fc) = do
        Rendering f c <- stringRendering win geom bz font str fc (0,0)
        return (c,f)

instance Hashable PlainText where
    hashWithSalt s PlainText{..} =
        s `hashWithSalt` plainTxtString `hashWithSalt` plainTxtColor

data PlainText = PlainText { plainTxtString :: String
                           , plainTxtColor  :: Color
                           } deriving (Show, Eq, Generic)

Composite

The next step up in abstraction applies when you have described some adequate number of primitive types. From here on up you can graphically represent new types as a heterogeneous list of those more primitive types. Element is used to package those primitive types in a list. composite simply takes your type and "decomposes" it into transformed Primitive elements.

This is where making new renderings gets really easy


-- TextInput
data TextInput = TextInput { textInputTransform :: Transform
                           , textInputText      :: PlainText
                           , textInputBox       :: Box
                           , textInputActive    :: Bool
                           } deriving (Show, Eq, Typeable)

localTextInputPath :: TextInput -> Path
localTextInputPath = boxPath . textInputBox

globalTextInputPath :: TextInput -> Path
globalTextInputPath t@TextInput{..} =
    transformPoly textInputTransform $ localTextInputPath t

textInputOutline :: TextInput -> Polyline
textInputOutline t@TextInput{..} = path2Polyline 1 white $ localTextInputPath t

instance Composite TextInput IO Rez Transform where
    composite txt@TextInput{..} =
        [ (textInputTransform, Element textInputBox)
        , (textInputTransform, Element textInputText)
        ] ++ [(textInputTransform, Element poly) | textInputActive]
            where poly = textInputOutline txt

Rendering a frame

After you have some datatypes to render from primitives it's dead simple to get them on the screen. All your loop has to keep around is the current data to render and the last rendering cache. Then you can use renderData to render your data to the screen. Here is an example of the function I'm using to render to the screen. There's only three relevant lines and the rest is GLFW noise

renderFrame :: Workspace -> UI -> IO Workspace
renderFrame ws ui = do
        -- Get the Rez (resource type)
    let rz  = wsRez ws
        -- Get the rendering cache from last
        old = wsCache ws

    (fbw,fbh) <- getFramebufferSize $ rezWindow rz
    glViewport 0 0 (fromIntegral fbw) (fromIntegral fbh)
    glClear $ GL_COLOR_BUFFER_BIT .|. GL_DEPTH_BUFFER_BIT

    new <- renderData rz old ui

    pollEvents
    swapBuffers $ rezWindow rz
    shouldClose <- windowShouldClose $ rezWindow rz
    if shouldClose
    then exitSuccess
    else threadDelay 100

    return $ ws { wsCache = new }

As you can see renderData pulls out the renderings we need from the old cache, creates the new ones, cleans the stale ones, renders your data and returns your new cache that you can use to render the next frame. This way if your interface never changes you don't have to allocate any new resources - you shouldn't even have to think about it.

2015-10-03

Schell Carl Scivally

πŸ“ž +64 021 420 471

efsubenovex at gmail dot com

I'm passionate about functional programming, real time graphics and sound synthesis. In my free time I like to build things and play games with my kids. In the past I've made music with my friends and played shows, toured the US with a band, drove forklifts in a chemical plant and bailed hay in three states. Technically I'm an international dancer.

This resume lives permanently at https://zyghost.com/resume.html.

🏠 Current Location

I am a US citizen living in The Wood, Nelson, New Zealand.

Experience

narrative.so logo Narrative.so

Senior Rust Software Engineer

Building and maintaining a cross-platform consumer application that performs AI inference on the edge.

  • performance profiling and optimization
  • shipping new AI models and features
  • refactored build system using Rust xtask

formation.ai logo Formation.ai

Senior Software Engineer

Full stack engineering in Haskell using reflex. Rust, Go, AWS.

Formation.ai was acquired by BCG and was formerly Takt.com.

  • single-handedly authored, deployed, and maintained a cloud-based template language interpreter in Rust that ran 24 million+ Starbucks req/day for 6 months bug free!
  • built a fullstack application in Haskell to author Starbucks' Star Program offers.

syndeca.com logo Syndeca.com

Senior Developer

Full stack engineering in Objective-C, Flash, Javascript and Haskell.

  • single-handedly authored, deployed and maintained SDK and applications for clients including:
    • Nordstrom
    • Home Depot
    • Lowes
    • Bass Pro
    • Sears
  • internal productivity tools in Haskell

🀝 Freelancing

Flash game development, interactive displays, website design and implementation.

Clients include:

  • Viddyou.com (acquired by Motionbox in 2013)
    • authored Viddyou's HD streaming video player
  • Opsworks, Inc.
    • authored the Larchmont Charter School auction and payment system
  • Synapse Group, Inc. (digital agency)
    • completed many projects for Fortune-500 clients like:
      • IBM
      • 3M
      • Sears
      • Lowes
      • Nordstrom
  • Sonoma State University

SSU NASA Education and Public Outreach NASA Education and Public Outreach

Flash game development.

  • Designed and authored the "Solar Supernova" Space Mysteries game
  • Authored, deployed and maintained many of the program's various websites

🎞️ Honors and Awards

creative Cultural Award - Embrace Creative Freedom

Narrative.so

For shipping consistenly and quickly, with an eye for creative solutions.

We walk in artists’ shoes and embrace creative freedom. We’re curious, passionate and hunt for the deeper meaning.

truth Cultural Award - Seek Truth

Narrative.so

For work on integrating TVM tuning into AI model pipelines and revamping build systems.

We seek out our strengths and weaknesses and accept them – at all times being authentically true to ourselves, and each other.

Mcquillen Summer Research Award

Sonoma State University

Selected to refurbish a thin film sputter coating machine and work on various high vacuum projects in the physics department.

πŸ—οΈ WIPs

These articles are works in progress. I reckon it's better to have them available for search instead of hiding them completely. Somebody may get some good use out of them even if they are incomplete.

🌯 Introducing Functional Reactive Programming

Contents

Discovery

FRP has been around for a long time. Originally discovered and coined by Conal Elliot and Paul Hudak in the late 90's it represented a new approach to writing dynamic systems, wherein the programmer describes how the system changes over time using continuous semantics. What this meant practically is that FRP code tended to look more like interelated equations and less like a list of steps to achieve a goal.

As time went on more implementations were made and the term got thrown around freely, eventually even being applied to other technologies like Javascript's React framework. These days when folks talk about React, bacon.js, etc. they tend to drop the "functional" part of FRP in favor of "reactive", which suits the nature of those frameworks better. Check out the wikipedia article on FRP for more info on what it is, specifically

Prep Work

An FRP system deals in terms of continuous values and discrete events. Continuous values are often referred to as Behaviors while discrete events are simply ... you guessed it ... Events! What this means is that your values always come wrapped in these contexts. For this reason I've been known to call writing FRP code as "advanced burrito making". The newly popular (as of the first writing of this article) reflex package adds another context - one that combines Behaviors and Events, called Dynamics. Reflex's brand of FRP is "very advanced burrito making" ;)

In any implementation there are lots of functions for turning a value in one context into a value in another context ... so if you are going to write in FRP I would recommend being really, really familiar with the basic typeclasses:

and if you've got the time it would really help to get these more advanced topics in as well -

The haskell wiki has more info on how FRP libs use these typeclasses.

Then once you have a grasp on the supporting machinery we can talk a bit about Behaviors and Events.

Behaviors

A behavior is a value that changes over some domain. In most reactive settings like games and simulations a behavior is likely to be a value that changes over time, but it could just as easily be a value that changes over user input, database notifications or any other input.

I find it beneficial to think of a Behavior as a function - a mathematical function.

Let's use Newton's law of gravitation, f = g * (m1 * m2) / r ** 2, where f is the force between two bodies of mass m1 and m2 respectively, g is a gravitational constant, which is just a number, and r is the distance between the centers of the two bodies. In a Behavioral context we can express this equation quite simply and quite literally by saying that if each term (g, m1, m2 and r) are Behaviors themselves, then f is also a Behavior. Even better, if the FRP lib you choose defines Num and Fractional instances for its Behavior type then we can define f as the equation itself:

f g m1 m2 r = g * (m1 * m2) / r ** 2

In this case g is a constant, and due to Fractional's fromRational we should be able to construct a Behavior for g simply using a float literal:

f m1 m2 r = 6.674eβˆ’11 * (m1 * m2) / r ** 2

This is one of Haskell's (and FRP's) killer apps: the ability to write code that reads like mathematics, or like written language. In this case we have embedded a pure physics equation into our FRP system verbatim. In my opinion this is very elegant.

So let's say the bodies we're finding the force between are planets. Then let us exclaim "we have a type for that!":

data Planet = Planet { planetMass     :: Float
                     -- ^ Simple mass of the planet in kg
                     , planetPosition :: V2 Float
                     -- ^ Position vector like (Float, Float), see the linear package
                     }

planetA = Planet 10 $ V2 0 0
planetB = Planet 100 $ V2 250 250

POOF! Planetary formation. Now we need to know how these planets change over time. Oooor we can assume they don't. Either way we need a planet in a Behavioral context. Behaviors are often (always?) Applicatives. They have a first order kind (or more) like * -> *. In plain terms the Behavior type takes another type and wraps it in its context. This is Functor and Applicative stuff. So a planet in a Behavioral context would be something like Behavior Planet. Up until now I've left off the type variable in Behavior, but it should really be Behavior a, where a is any type.

Now, since many (all?) FRP implementations provide an Applicative instance for their Behavior a type, we can construct some Behavior Planets:

planetBehaviorA = pure planetA
planetBehaviorB = pure planetB

These planet's don't change over time. These rocks just sit. Which reminds me of a poem:

Nobody sits like this rock sits.

You rock, rock.

The rock just sits - and is.

You show us how to just sit here,

and that's what we need.

-- Albert Markovski, I :heart: Huckabees

Now that we have what we need (a couple of sitty rocks) we can write the other Behaviors we need, using Functor to great lengths ... and masses.

posBehaviorA  = fmap planetPos planetBehaviorA
posBehaviorB  = fmap planetPos planetBehaviorB
massBehaviorA = fmap planetMass planetBehaviorA
massBehaviorB = fmap planetMass planetBehaviorB

Great! Now, we have Behavior (V2 Float)s for the planet's positions over time, but what we need is the vector between them. We're going to assume that V2 has a Num instance (and it does, if we're talking about this V2). Assuming this means we can treat it just like any other number because remember Behavior a also has a Num instance, at least for as that have a Num instance (in this case V2) ... so:

vectorAB = posBehaviorA - posBehaviorB

And that's enough to get us the rest of the way:

gForceAB = f massBehaviorA massBehaviorB vectorAB

Events

Events are values at a specific domain input. Again, in most cases the domain is time, but it doesn't have to be.

For me it's easiest to think about operating over time because it's quite close to my human experience.

Events in FRP are just like your intuition about the word "event". Each event is a thing that happens at an exact moment. Unlike behaviors, which describe how things change - events describe how things are right now. Or maybe in three seconds. Or possibly in a couple months.

Events & Behaviors

Events and behaviors are bound to each other by a couple of novel ideas. The first is that given an input like a time (or whatever the domain is) we can "sample" a behavior and get a result value. In math this is just evaluating a function with an input. Combining the input value with the result value gives us an event:

makeEvent :: input -> output -> (input, output)
makeEvent domain range = (domain, range)

Using both events and behaviors we can define complicated systems and relationships succinctly.

A tour of FRP flavors

Evan Czaplicki of Elm fame did a great talk on the different flavors of FRP:

Conclusion

Hopefully that gives a little background to the situation. FRP has come a long way since 1997 but it's really still an area of active research.

advanced burrito making

Schellsan 🐚 🐒 🐌 πŸ¦ͺ

I make music, code and do yard work.

CutestEP out now!

CutestEP is a re-release of material from 2005, available at the music places.

CutestEP

Business as usual

You can also contact me