λ Fun With Functions

Haskell WebAssembly for Browser Interaction

Posted on September 30, 2025

The Goal

I wanted to test out the WASM support that GHC now offers in the very recent versions. Since this blog has very little JS itself, I thought it would serve as a good testbed by building a little theme toggle with the following requirements:

  • The logic should be written in Haskell, it can’t just be a value-less shim that just wraps around some JavaScript logic.
  • If possible it would make use of at least one dependency that isn’t part of the standard library, because it would be nice to use helpful libraries and not have to reimplement them badly.

The Setup

From what I found (at the time of writing) this appeared to be the best starting point to work from: ghc-wasm-meta. As it’s a nix flake and my blog code includes some nix to provide the tooling that drives it, then I should be hopefully off to a good start. It’s worth pointing out however that this is using a bleeding edge version of GHC 9.14, so the usual Danger Will Robinson warning applies with something like that.

The Build

This was a little fiddly in the end and a fair chunk of the options originated from my assistant Claude.

wasm32-wasi-cabal update

wasm32-wasi-cabal configure \
  --ghc-options="-no-hs-main -O2 -optl-mexec-model=reactor -optl-Wl,--export=hs_init,--export=hs_initializeThemeToggle -optl-Wl,--strip-all -optl-Wl,--gc-sections" \
  --enable-library-vanilla \
  --disable-library-profiling \
  --disable-shared

wasm32-wasi-cabal build

cp $(wasm32-wasi-cabal list-bin exe:haskell-wasm) output/haskell-wasm.wasm

$(wasm32-wasi-ghc --print-libdir)/post-link.mjs -i output/haskell-wasm.wasm -o output/ghc_wasm_jsffi.js

The highlights are the following:

  • -optl-mexec-model=reactor - This is a WASM option which makes it setup so that the exports can be invoked multiple times after it is instantiated.
  • --export=hs_init,--export=hs_initializeThemeToggle - Export the general Haskell initialisation and the function which actually does the part we’re interested in.
  • post-link.mjs - This produces a special file used when hooking the WASM into the JavaScript that fires it up.

Most of the rest are oriented around getting the size of the compiled WASM bundle down.

Along with this there’s some additional use of wasm-opt to shrink the WASM even further but it’s irrelevant to getting things actually working.

The JavaScript

This is the part which took the longest in the end, I wish this was just a one-liner and really should be but this appears to be the state of the art right now:

// Import the FFI bindings and WASI shim
import createGhcWasmJsffi from '/js/ghc_wasm_jsffi.js';
import { WASI, File, OpenFile, ConsoleStdout } from 'https://cdn.jsdelivr.net/npm/@bjorn3/browser_wasi_shim@0.4.2/dist/index.js';

let wasmInstance = null;
let wasmExports = null;

// Fetch the WASM file
const wasmResponse = await fetch('/js/haskell-wasm.wasm');
if (!wasmResponse.ok) {
  throw new Error('Failed to fetch WASM: ' + wasmResponse.status + ' ' + wasmResponse.statusText);
}

const wasmBuffer = await wasmResponse.arrayBuffer();

// Set up exports proxy for FFI
let exportedFunctions = null;
const exportsProxy = new Proxy({}, {
  get: (_, property) => {
    if (!exportedFunctions) {
      throw new Error('WASM exports not initialized when accessing ' + String(property));
    }
    return exportedFunctions[property];
  }
});

// Create GHC WASM FFI bindings
const ghcWasmJsffi = createGhcWasmJsffi(exportsProxy);

// Create WASI instance with console stdout
const fds = [
  new OpenFile(new File([])), // stdin (fd 0)
  ConsoleStdout.lineBuffered(msg => console.log(msg)), // stdout (fd 1)
  ConsoleStdout.lineBuffered(msg => console.error(msg)), // stderr (fd 2)
];
const wasi = new WASI([], [], fds);
const wasiImports = wasi.wasiImport;

// Instantiate the WASM module
const wasmInstantiation = await WebAssembly.instantiate(wasmBuffer, {
  "wasi_snapshot_preview1": wasiImports,
  "ghc_wasm_jsffi": ghcWasmJsffi
});

wasmInstance = wasmInstantiation.instance;
exportedFunctions = wasmInstance.exports;
wasmExports = wasmInstance.exports;

// Initialize WASI with the instantiated module
wasi.inst = wasmInstance;

// Initialize the Haskell runtime
wasmExports.hs_init();

// Initialize the theme toggle
wasmExports.hs_initializeThemeToggle();

Even with a shim for the WASI side of things this feels like a lot of needless yak shaving. Getting any of this wrong often resulted in weird errors that aren’t at all very clear, especially when you’re only 2 hours into actually looking at WebAssembly.

The long and the short of this is that it’s loading and instantiating the WASM, somewhat akin to a weird linker and then via the exports property of the instance makes available to the caller the exported API.

The Haskell

Here’s the interesting bit:

{-# LANGUAGE ForeignFunctionInterface #-}

module HaskellWasm
  ( initializeThemeToggle
  ) where

import GHC.Wasm.Prim
import Data.Enum.Circular

-- Create a JavaScript callback from a Haskell IO action
foreign import javascript "wrapper"
  makeCallback :: IO () -> IO JSVal

-- DOM element access
foreign import javascript unsafe "document.getElementById($1)"
  js_getElementById :: JSString -> IO JSVal

-- Element property access
foreign import javascript unsafe "$1.classList"
  js_getClassList :: JSVal -> IO JSVal

foreign import javascript unsafe "$1.querySelector($2)"
  js_elementQuerySelector :: JSVal -> JSString -> IO JSVal

-- Element property setters
foreign import javascript unsafe "$1.textContent = $2"
  js_setTextContent :: JSVal -> JSString -> IO ()

-- ClassList operations
foreign import javascript unsafe "$1.remove($2)"
  js_classListRemove :: JSVal -> JSString -> IO ()

foreign import javascript unsafe "$1.add($2)"
  js_classListAdd :: JSVal -> JSString -> IO ()

-- Event handling
foreign import javascript unsafe "$1.addEventListener($2, $3)"
  js_elementAddEventListener :: JSVal -> JSString -> JSVal -> IO ()

-- LocalStorage operations
foreign import javascript unsafe "localStorage.getItem($1)"
  js_localStorageGetItem :: JSString -> IO JSString

foreign import javascript unsafe "localStorage.setItem($1, $2)"
  js_localStorageSetItem :: JSString -> JSString -> IO ()

-- Media query
foreign import javascript unsafe "window.matchMedia($1).matches"
  js_windowMatchMediaMatches :: JSString -> IO Bool

-- Document operations
foreign import javascript unsafe "document.documentElement"
  js_getDocumentElement :: IO JSVal

foreign import javascript unsafe "$1.setAttribute($2, $3)"
  js_elementSetAttribute :: JSVal -> JSString -> JSString -> IO ()

foreign import javascript unsafe "$1 === null"
  js_stringIsNull :: JSString -> Bool

-- Theme data type
data Theme = Light | Dark
  deriving (Show, Eq, Enum, Bounded)

-- Convert theme to string for storage/attributes
themeToString :: Theme -> JSString
themeToString Light = toJSString "light"
themeToString Dark = toJSString "dark"

-- Convert string to theme
stringToTheme :: JSString -> Maybe Theme
stringToTheme s
  | js_stringIsNull s = Nothing
  | fromJSString s == "light" = Just Light
  | fromJSString s == "dark" = Just Dark
  | otherwise = Nothing

-- Convert theme to icon
themeToIcon :: Theme -> JSString
themeToIcon Light = toJSString "🌞"
themeToIcon Dark = toJSString "🌙"

-- Apply theme to the page
applyTheme :: Theme -> IO ()
applyTheme theme = do
  -- Set data-theme attribute on document element
  docElement <- js_getDocumentElement
  js_elementSetAttribute docElement (toJSString "data-theme") (themeToString theme)

  -- Update button icon to show the NEXT theme (what you'll switch to)
  button <- js_getElementById (toJSString "theme-toggle-button")
  iconElement <- js_elementQuerySelector button (toJSString ".theme-icon")
  js_setTextContent iconElement (themeToIcon (csucc theme))

  -- Store theme in localStorage
  js_localStorageSetItem (toJSString "theme") (themeToString theme)

-- Get current theme from localStorage or media query
getCurrentTheme :: IO Theme
getCurrentTheme = do
  stored <- js_localStorageGetItem (toJSString "theme")
  case stringToTheme stored of
    Just theme -> pure theme
    Nothing -> do
      prefersDark <- js_windowMatchMediaMatches (toJSString "(prefers-color-scheme: dark)")
      pure $ if prefersDark then Dark else Light

-- Toggle theme to the next value using circular enum
toggleTheme :: IO ()
toggleTheme = do
  currentTheme <- getCurrentTheme
  let nextTheme = csucc currentTheme
  applyTheme nextTheme

-- Initialize the theme toggle functionality
initializeThemeToggle :: IO ()
initializeThemeToggle = do
  -- Get and apply initial theme
  currentTheme <- getCurrentTheme
  applyTheme currentTheme

  -- Get the button element
  button <- js_getElementById (toJSString "theme-toggle-button")

  -- Get the classList and manipulate it
  classList <- js_getClassList button
  js_classListRemove classList (toJSString "hidden")
  js_classListAdd classList (toJSString "theme-toggle")

  -- Create a JavaScript callback for the toggle function
  callback <- makeCallback toggleTheme

  -- Add click handler to the button
  js_elementAddEventListener button (toJSString "click") callback

-- Foreign exports for WASM - makes functions callable from JavaScript
foreign export ccall "hs_initializeThemeToggle" initializeThemeToggle :: IO ()

There’s clearly 3 parts to this:

  • Special functions that call JavaScript so that we can interact with the web page.
  • Regular old Haskell code.
  • A special export that makes a Haskell function available to the calling JavaScript.

The "wrapper" calling convention is special - it tells GHC to generate JavaScript code that properly marshals between JavaScript function calls and Haskell IO actions. The generated FFI binding looks like:

(...args) => __exports.ghc_wasm_jsffi_callback($1, ...args)

This wrapper handles Haskell runtime context, threading, and ensures the callback can be called from JavaScript as a normal function.

It makes use of the csucc function from the circular-enum package, which satisfies our requirement for an additional package but also makes handling the toggling very simple and everything would continue to work if I added a third theme.

Wait A Second

If it wasn’t clear by now that little icon up in the top right of this very page is what I implemented, with that logic powering the toggling and defaulting of the theme.

Conclusion

Going back to the goals, while it does have a lot of shim JS, it is just that and all the logic is in the Haskell code. Plus it made use of a non-standard library, so that part is proved out as well. Plus it “just works”, once all of those tedious bits are put into place.

The output after all the shrinking is a 791KB WASM file and 3KB of FFI bindings to make this all work, which isn’t that crazy given how much is packed in there but the stock JavaScript approach to this would be probably less than the FFI bindings in size.

One thing that crossed my mind once I had all the workings up and running was that it would be fairly easy to create a rudimentary React-like library and the entire page would be controlled by Haskell that way. I’m not sure if I’d particularly want to, but the important part is that it’s totally possible.

Either way, this was a fun (albeit at times frustrating getting it to work) little experiment and I hope that it becomes even easier in the future.


What Are Lenses For?

Posted on July 11, 2023

What Are Lenses?

First we need to do a little (or more) scene setting, if we want to represent a bunch of achievements for a bunch of users in some games a super simple representation of that in JavaScript might involve some code like this:

users[userIDToUpdate]
  .games['bestgameever']
  .achievements['completedthegame']
  .completedDate = new Date()

This code sets the completed date for the achievement 'completedthegame' for the game 'bestgameever' for the user with some identifier userIDToUpdate. There’s two kinds of access going on here, that of known fields like .games and .achievements, as well as the object key indexing done with square brackets which might address values that don’t exist (for example ['bestgameever']). That’s problem no. 1 though, if any of these ids are wrong the code blows out with a nasty looking exception.

This becomes a lot harder if the goal is to immutably update these values:

const user = users[userIDToUpdate]
const game = user.games['bestgameever']
const achievement = game.achievements['completedthegame']
const updatedAchievement = {
  ...achievement,
  completedDate: new Date()
}
const updatedGame = {
  ...game,
  achievements: {
    ...game.achievements,
    ['completedthegame']: updatedAchievement
  }
}
const updatedUser = {
  ...user,
  games: {
    ...user.games,
    ['bestgameever']: updatedGame
  }
}
const updatedUsers = {
  ...users,
  [userIDToUpdate]: updatedUser
}

We’ve still got the problem of invalid values throwing exceptions but also about 10 times the code.

Lets move this to Haskell where we still have the same kind of problem.

Here’s some setup for language options and imports upfront:

{-# LANGUAGE TypeApplications #-}
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE GADTs #-}
{-# LANGUAGE FlexibleContexts #-}
import GHC.Generics
import qualified Data.HashMap.Strict as M
import Data.Time.Clock
import Control.Lens
import Data.Generics.Product
import Data.Generics.Sum

Our basic data types to represent everything:

data Achievement = Achievement { completedDate :: Maybe UTCTime } deriving (Eq, Show, Generic)
data Game = Game { achievements :: M.HashMap String Achievement } deriving (Eq, Show, Generic)
data User = User { games :: M.HashMap String Game } deriving (Eq, Show, Generic)
type Users = M.HashMap String User

Now the starting values:

defaultAchievement = Achievement Nothing
defaultGame = Game (M.singleton "completedthegame" defaultAchievement)
defaultUser = User (M.singleton "bestgameever" defaultGame)
defaultUsers = M.singleton "sean" defaultUser

Updating this is a whole mess of pain:

updateAchievement completedAt achievement =
  achievement { completedDate = Just completedAt }
updateGame completedAt game = game { achievements =
  M.adjust (updateAchievement completedAt) "completedthegame" (achievements game) }
updateUser completedAt user = user { games =
  M.adjust (updateGame completedAt) "bestgameever" (games user) }
getManuallyUpdatedUsers completedAt =
  M.adjust (updateUser completedAt) "sean" defaultUsers

That’s quite verbose and just not very pleasant to read, it wont throw any exceptions if a value is missing however and will instead return the original value. Which is a little bit better but not that great overall.

With lenses though it’s possible to split apart the “targeting” from the operation being performed, first we create a lens which handles the former:

updateCompletedDateLens = at "sean"
                        . _Just
                        . field @"games"
                        . at "bestgameever"
                        . _Just
                        . field @"achievements"
                        . at "completedthegame"
                        . _Just
                        . field @"completedDate"

In this case we’re chaining lenses and there’s a lot of clarity as to what is going on, at is used to peer into the HashMap values and field peers into the the fields of the records.

To update this we use one of the utility functions from the lens library itself:

getLensUpdatedUsers completedAt = set updateCompletedDateLens (Just completedAt) defaultUsers

This snippet runs the Haskell of this post:

main = do
  print defaultUsers
  completedAt <- getCurrentTime
  print $ getManuallyUpdatedUsers completedAt 
  print $ getLensUpdatedUsers completedAt

Update Everything

Posted on May 24, 2020

The Problem.

In the project I’m working on there is some logic which assigns a UUID to a field in a bunch of values which make up an AST structure representing a user’s code. For testing purposes there are a series of functions which take a value in that structure and wipe out the unique ID so that we can use an equality check against it. Those are manually written functions which we have to update as the structure changes, leading to the odd “Wait, why has that still got a unique ID?” moment when we make changes. I had an inkling that if this was written in Haskell (the code I’m referring to is written in TypeScript) this manually written code, along with the maintenance cost, would be unnecessary.

First Steps.

I’ll be using nix-shell to get myself a REPL to work with the code, using this command:

nix-shell
  -p "haskellPackages.ghcWithPackages (p: with p; [ghc uniplate pretty-simple])"
  --command ghci

Turn on an option that we’ll be needing for an easy life:

GHCi> :set -XDeriveDataTypeable

Add an import related to that option, don’t worry about these for now:

GHCi> import Data.Data

Next we’ll use the multi-line input support in GHCi to input this (put :{ on an empty line first and on an empty line after write :} to finish the multi-line editing):

newtype UniqueID = UniqueID { uid :: String }
                   deriving (Eq, Show, Data)

data JSObject = JSObject { objectParts :: [(String, JSValue)] }
                deriving (Eq, Show, Data)

data JSArray = JSArray { arrayParts :: [JSValue] }
               deriving (Eq, Show, Data)

data JSString = JSString { stringValue :: String }
                deriving (Eq, Show, Data)

data JSBool = JSBool { boolValue :: Bool }
              deriving (Eq, Show, Data)

data JSNumber = JSNumber { numberValue :: Double }
                deriving (Eq, Show, Data)

data JSNull = JSNull deriving (Eq, Show, Data)

data JSUndefined = JSUndefined deriving (Eq, Show, Data)

data JSCode = JSCode { code :: String, codeUniqueID :: UniqueID }
              deriving (Eq, Show, Data)

data JSValue = JSValueObject JSObject
             | JSValueArray JSArray
             | JSValueString JSString
             | JSValueBool JSBool
             | JSValueNumber JSNumber
             | JSValueNull JSNull
             | JSValueUndefined JSUndefined
             | JSValueCode JSCode
             deriving (Eq, Show, Data)

What we have above is something that approximates the definition of JSON in most libraries but with the addition of the JSCode type which represents a chunk of arbitrary JavaScript and is where we hold our UniqueID value. As we can have one of those buried 9 layers down, we need to walk the tree to update those wherever we might find them.

Building The Parts.

We’ll start with a function to clear unique ID values, which just throws away the original value and gives us an empty one (use the multi-line support again for this):

clearUniqueID :: UniqueID -> UniqueID
clearUniqueID _ = UniqueID ""

Now build up a value to play with:

GHCi> exampleCode = JSCode "5 + 10" (UniqueID "ABC")
GHCi> exampleArray = JSArray [JSValueCode exampleCode]
GHCi> exampleString = JSString "Good News"
GHCi> exampleFirstValue = ("first", JSValueString exampleString)
GHCi> exampleSecondValue = ("second", JSValueArray exampleArray)
GHCi> exampleObject = JSValueObject (JSObject [exampleFirstValue, exampleSecondValue])

We can use the pretty-simple package to see the structure more clearly:

GHCi> import Text.Pretty.Simple
GHCi> pPrintNoColor exampleObject
JSValueObject
    ( JSObject
        { objectParts =
            [
                ( "first"
                , JSValueString
                    ( JSString { stringValue = "Good News" } )
                )
            ,
                ( "second"
                , JSValueArray
                    ( JSArray
                        { arrayParts =
                            [ JSValueCode
                                ( JSCode
                                    { code = "5 + 10"
                                    , codeUniqueID = UniqueID { uid = "ABC" }
                                    }
                                )
                            ]
                        }
                    )
                )
            ]
        }
    )

The Good Stuff.

With the Uniplate library we just need a couple of imports:

GHCi> import Data.Generics.Uniplate.Data
GHCi> import Data.Generics.SYB

Then with the everywhere function we apply our transformation from earlier:

GHCi> updatedExample = everywhere clearUniqueID exampleObject

Lets see the result.

GHCi> pPrintNoColor updatedExample
JSValueObject
    ( JSObject
        { objectParts =
            [
                ( "first"
                , JSValueString
                    ( JSString { stringValue = "Good News" } )
                )
            ,
                ( "second"
                , JSValueArray
                    ( JSArray
                        { arrayParts =
                            [ JSValueCode
                                ( JSCode
                                    { code = "5 + 10"
                                    , codeUniqueID = UniqueID { uid = "" }
                                    }
                                )
                            ]
                        }
                    )
                )
            ]
        }
    )

…that’s it! All done, see you next time!

A Deeper Look.

First off, lets have a look at the type of that everywhere function, because that was the most mysterious part.

everywhere :: Biplate b a => (a -> a) -> b -> b

So our clearUniqueID function slotted into the first parameter and then we get a function that transforms from JSValue to JSValue. But this is only if we have an instance of Biplate JSValue UniqueID.

Looking up Biplate we want a Biplate JSValue UniqueID, there’s an instance for (Data a, Data b, Uniplate b) => Biplate a b. So a Data JSValue, a Data UniqueID and a Uniplate UniqueID gives us that Biplate JSValue UniqueID.

Following that chain along to Uniplate, if we look at the instances for it we can see there’s this one: Data a => Uniplate a. So Data a gives us a Uniplate a for every Data a that exists.

Since everything ends up with Data JSValue and Data UniqueID, which GHC has graciously derived automatically for us, we don’t have to write all of that code for walking the various types.

So What Does This Give Us?

The benefits of this are as follows:

  • No manually written pile of code that needs regular maintenance.
  • Reflection or similar runtime introspection is avoided, which might drill into the wrong thing and possibly throw an exception.
  • The types guide the behaviour, so we can guarantee that it’ll be applied to everything it should be and nothing else.

That last point is part of a bigger pattern, not using types as validation but as a building block for behaviour. Having the compiler do work which is repetitive and/or error prone and to the first point which then needs keeping up to date after it is first implemented.

Bonus Round.

There are other wonders to be found in the uniplate library too, like childrenBi which will get all the values matching a particular type from the hierarchy.

GHCi> childrenBi exampleObject :: [UniqueID]
[UniqueID "ABC"]

Maybe Versus Nullable

Posted on November 21, 2017

Select All The Things

Recently I was faced with the task of updating our product to support multiple selection, so that for example a user can move multiple elements together with one mouse drag. As the codebase is written in TypeScript it meant taking this field:

selectedThing: ThingTarget | null;

and changing it to this:

selectedThings: Array<ThingTarget>;

On the surface this isn’t a huge change, but the code operating on these values has to change quite dramatically because of their different concrete structures. Taking the display of the indicators that show something is selected in the designer as an example:

if (selectedThing == null) {
  return [buildSelectedControl(selectedThing)];
} else {
  return [];
}

Now becomes:

return selectedThings.map(buildSelectedControl);

Make All The Changes

These are the simplest examples but fundamentally the logic always needed changing along these lines. As this felt a little unsatisfactory to me I pondered how this would’ve panned out with Haskell (or PureScript/Scala/etc). So we would’ve started with code that looked like:

selectedThing :: Maybe ThingTarget

That would’ve turned into:

selectedThings :: [ThingTarget]

However, in either of these cases the logic is the same and looks like:

fmap buildSelectedControl selectedThings
-- The type of fmap being:
-- fmap :: Functor f => (a -> b) -> f a -> f b

Similarly to check if something has been selected we’d use:

elem thing selectedThings
-- The type of elem being:
-- elem :: (Foldable t, Eq a) => a -> t a -> Bool

When people talk of abstraction it’s often in terms of things close to concrete use cases like a SelectionManager (let’s ignore that nonsense name) class which then doesn’t end up being very re-usable. However with abstractions like Foldable or Functor we have much less specific but just as if not more strict ones which tend more towards general purpose use cases. But also because the language lacks as many special case features (like null and undefined are in JavaScript, even if we don’t think of them traditionally as such) there are fewer hitches to the user of this kind of abstraction.

One Step Further

This extends beyond the functions that can be used to the functions that can be built too:

selectedControls :: (Functor f) = (Editor -> f Thing) -> Editor -> f Control
selectedControls getSelected editor = fmap buildSelectedControl $ getSelected editor

In this case the function is as general as fmap allows, if the accessor function has a type of Editor -> Maybe Thing, then the above function returns a Maybe Control. If no type was supplied, this is what GHC would determined the type of selectedControls would be.

GHCi> data Thing = Thing
GHCi> data Control = Control
GHCi> data Editor = Editor
GHCi> :{
Prelude| buildSelectedControl :: Thing -> Control
Prelude| buildSelectedControl _ = Control
Prelude| :}
GHCi> selectedControls getSelected editor = fmap buildSelectedControl $ getSelected editor
GHCi> :t selectedControls
selectedControls :: Functor f => (t -> f Thing) -> t -> f Control

It turns out this is more flexible that the version further above, as there’s no need (or even way) to constrain the function to the Editor type the compiler makes it polymorphic to any value t.

So What?

I posit that nullable values interfere with code reuse as they’re a disjoint union of the value type and null (undefined as well), but none of the common abstractions can be applied to a disjoint union. Simple types and simple abstractions lead to code reuse and less destructive refactors and if used, more flexible implementations.