Marshall Bowers

Conjurer of code. Devourer of art. Pursuer of æsthetics.

Implementing a Case Conversion Library in F# and Haskell

Friday, November 8, 2019
1357 words
7 minute read

At work I recently implemented a small library in F# for performing case conversion. The library is inspired by heck, a case conversion library for Rust.

After completing the initial implementation I thought it would be a fun exercise to implement the library in Haskell.

Creating a Module

The first thing we'll need to do is create a module for the library.

In F# this is just a few lines:

module Casing

open System

We have slightly more work to do in the Haskell version since we're going to explicitly state which functions we want to export. In F# we can use visibility keywords to govern which functions are exposed outside of the module.

Here's what the top of our Haskell module looks like:

{-# OPTIONS -Wall #-}

module Casing
  ( toCamelCase
  , toPascalCase
  , toSnakeCase
  , toScreamingSnakeCase
  , toKebabCase
  , toTitleCase
  ) where

import qualified Data.Char as Char
import Data.List (intercalate)
import Data.Maybe (catMaybes)

Getting Some Help

Now that we have our module setup, it's time to declare some helper functions.

Not all of these helper functions are strictly needed for the F# version, but I think that they make things a little more ergonomic.

Side note, if you're wondering about what (^) is, it's an operator that performs function application, much like ($) in Haskell.

let (^) = (<|)

module private List =
    let mapHead mapping list =
        match list with
        | [] -> []
        | head :: tail ->
            mapping head :: tail

    let mapTail mapping list =
        match list with
        | [] -> []
        | head :: tail ->
            let tail = tail |> List.map mapping
            head :: tail

module private Option =
    let ofString (value: string) =
        match value |> String.IsNullOrWhiteSpace with
        | true -> None
        | false -> Some value

module private String =
    let inline toUpper (value: string) =
        value.ToUpperInvariant()

    let inline toLower (value: string) =
        value.ToLowerInvariant()

let private capitalize (value: string) =
    value
    |> List.ofSeq
    |> List.mapHead Char.ToUpper
    |> List.mapTail Char.ToLower
    |> String.concat ""

We're going to need some helper functions in Haskell as well:

stringToMaybe :: String -> Maybe String
stringToMaybe [] = Nothing
stringToMaybe value = Just value

mapHead :: (a -> a) -> [a] -> [a]
mapHead _mapping [] = []
mapHead mapping (x:xs) = mapping x : xs

mapTail :: (a -> a) -> [a] -> [a]
mapTail _mapping [] = []
mapTail mapping (x:xs) = x : map mapping xs

capitalize :: String -> String
capitalize = mapHead Char.toUpper . mapTail Char.toLower

The Core Algorithm

With all of the setup done we can now move on to implementing the core library logic.

Our core algorithm is implemented in getWords, which we use to break a string up into a series of words.

let private isSeparator char =
    match char with
    | '_'
    | '-'
    | ' ' -> true
    | _ -> false

let private isBoundary currentChar nextChar =
    let isCasingBoundary () = Char.IsLower currentChar && Char.IsUpper nextChar

    isSeparator nextChar || isCasingBoundary ()

let private getWords (value: string) =
    let rec getWords' currentWord words chars =
        match chars with
        | [] -> currentWord :: words
        | singleChar :: [] ->
            currentWord + string singleChar :: words
        | currentChar :: nextChar :: remainingChars ->
            let appendCurrentChar word =
                match currentChar |> isSeparator with
                | true -> word
                | false -> word + string currentChar

            let currentWord, words =
                if isBoundary currentChar nextChar then
                    "", appendCurrentChar currentWord :: words
                elif currentWord |> Seq.forall Char.IsUpper && Char.IsUpper currentChar && Char.IsLower nextChar then
                    "" |> appendCurrentChar, currentWord :: words
                else
                    currentWord |> appendCurrentChar, words

            let remainingChars =
                if not ^ isSeparator nextChar then nextChar :: remainingChars
                else remainingChars

            getWords' currentWord words remainingChars

    let characters =
        value.ToCharArray()
        |> List.ofArray

    getWords' "" [] characters
    |> List.choose Option.ofString
    |> List.rev

Our getWords implementation looks roughly the same in Haskell:

isSeparator :: Char -> Bool
isSeparator '_' = True
isSeparator '-' = True
isSeparator ' ' = True
isSeparator _ = False

isBoundary :: Char -> Char -> Bool
isBoundary _currentChar nextChar
  | isSeparator nextChar = True
isBoundary currentChar nextChar =
  Char.isLower currentChar && Char.isUpper nextChar

getWords :: String -> [String]
getWords value = reverse $ catMaybes $ map stringToMaybe $ getWords' "" [] value
  where
    getWords' currentWord acc [] = currentWord : acc
    getWords' currentWord acc (singleChar:[]) =
      (currentWord ++ [singleChar]) : acc
    getWords' currentWord acc (currentChar:nextChar:remainingChars) =
      let appendCurrentChar word =
            if isSeparator currentChar
              then word
              else word ++ [currentChar]
          (currentWord', acc') =
            if isBoundary currentChar nextChar
              then ("", appendCurrentChar currentWord : acc)
              else if all Char.isUpper currentWord &&
                      Char.isUpper currentChar && Char.isLower nextChar
                     then (appendCurrentChar "", currentWord : acc)
                     else (appendCurrentChar currentWord, acc)
          remainingChars' =
            if not $ isSeparator nextChar
              then nextChar : remainingChars
              else remainingChars
       in getWords' currentWord' acc' remainingChars'

I personally find the Haskell version a bit cleaner, especially with Haskell's support for pattern matching in the function definition.

The Public API

Now that the hard part is done we can finally move onto the actual API of the library itself! This is probably the simplest part of the library, as we just have to define what the casing rules are for each of our desired cases. The beauty of this approach is that if we ever wanted to add a new case it would be super simple to do so.

Here's what our public API looks like in F#:

let toCamelCase value =
    value
    |> getWords
    |> List.mapHead String.toLower
    |> List.mapTail capitalize
    |> String.concat ""

let toPascalCase value =
    value
    |> getWords
    |> List.map capitalize
    |> String.concat ""

let toSnakeCase value =
    value
    |> getWords
    |> List.map String.toLower
    |> String.concat "_"

let toScreamingSnakeCase value =
    value
    |> getWords
    |> List.map String.toUpper
    |> String.concat "_"

let toKebabCase value =
    value
    |> getWords
    |> List.map String.toLower
    |> String.concat "-"

let toTitleCase value =
    value
    |> getWords
    |> List.map capitalize
    |> String.concat " "

And here's the public API in Haskell:

toCamelCase :: String -> String
toCamelCase =
  intercalate "" . mapTail capitalize . mapHead (map Char.toLower) . getWords

toPascalCase :: String -> String
toPascalCase = intercalate "" . map capitalize . getWords

toSnakeCase :: String -> String
toSnakeCase = intercalate "_" . map (map Char.toLower) . getWords

toScreamingSnakeCase :: String -> String
toScreamingSnakeCase = intercalate "_" . map (map Char.toUpper) . getWords

toKebabCase :: String -> String
toKebabCase = intercalate "-" . map (map Char.toLower) . getWords

toTitleCase :: String -> String
toTitleCase = intercalate " " . map capitalize . getWords

The one major difference between the F# and Haskell implementations is that the Haskell casing functions are implemented completely in point-free style.

It is possible to implement the F# version in point-free style, or the Haskell version using a pipeline operator, but I wanted to keep the implementations as idiomatic as possible for their respective languages.

Writing Some Tests

What kind of developers would we be if we didn't add some unit tests to ensure that everything is working as expected?

For F# we'll be using FsUnit and xUnit to write our tests.

One thing that I really like about xUnit is their support for data-driven tests. In this case we're able to leverage the Theory and InlineData attributes to easily add new test cases without needing to duplicate a bunch of code.

namespace Tests.Casing

open FsUnit.Xunit
open Xunit

module ``toCamelCase`` =
    [<Theory>]
    [<InlineData("camelCase", "camelCase")>]
    [<InlineData("PascalCase", "pascalCase")>]
    let ``it correctly converts casing to camelCase`` value expected =
        value
        |> Casing.toCamelCase
        |> should equal expected

module ``toPascalCase`` =
    [<Theory>]
    [<InlineData("camelCase", "CamelCase")>]
    [<InlineData("PascalCase", "PascalCase")>]
    let ``it correctly converts casing to PascalCase`` value expected =
        value
        |> Casing.toPascalCase
        |> should equal expected

For our Haskell tests we'll be using Hspec.

Hspec doesn't have anything like xUnit's Theory attribute, but as it turns out, we don't need it! Instead we can use a higher-order function and achieve the same result.

Below you'll see that we've defined a function called makeTest that takes a casing function, an input string, and the expected output string, and uses that to build a test case. The end result is the same—we can write our tests without having to duplicate a bunch of code—only this time we didn't need anything other than the built-in language constructs to do it.

import Casing as Casing
import Test.Hspec

makeTest transform value expected =
  it ("properly converts \"" ++ value ++ "\" to \"" ++ expected ++ "\"") $ do
    transform value `shouldBe` expected

main :: IO ()
main =
  hspec $ do
    describe "Casing.toCamelCase" $ do
      let test = makeTest Casing.toCamelCase
      test "camelCase" "camelCase"
      test "PascalCase" "pascalCase"
    describe "Casing.toPascalCase" $ do
      let test = makeTest Casing.toPascalCase
      test "camelCase" "CamelCase"
      test "PascalCase" "PascalCase"

Wrapping Up

And that's it! We've implemented our library and added some unit tests to ensure everything is working. Now we can sit back and convert between various cases to our hearts' content.

Interestingly enough, calling our conversion functions looks exactly the same in both F# and Haskell:

open Casing

toCamelCase "Hello World" // "helloWorld"
toSnakeCase "XMLHttpRequest" // xml_http_request
import Casing

toCamelCase "Hello World" -- "helloWorld"
toSnakeCase "XMLHttpRequest" -- xml_http_request

I hope you enjoyed this side-by-side tour of implementing a case conversion library in both F# and Haskell!

The Haskell version—affectionality named "heckin", after its namesake, heck— is available on Hackage. So if you find yourself wanting to do case conversion in Haskell, look no further!

I'm still very much a Haskell beginner, so please let me know if you have any tips for how to improve heckin's Haskell implementation.