Splitting function definitions across modules

Have you ever been annoyed that you have to define your functions all at once? Me neither, but nevertheless, I have been thinking about a way of solving this issue with Template Haskell.

The end goal of this project is to integrate the Utrecht University Attribute Grammar Compiler (UUAGC) more tightly into Haskell using Template Haskell (see this GitHub issue). Currently users are required to set up a custom cabal plugin or run uuagc manually like a preprocessor. Implementing UUAGC on via Template Haskell should reduce friction for new users and improve stability. Additionally it could allow us to use Haskell’s module system, which means that UUAG attribute grammars could be published to Hackage and reused by other people.

One of the most important features of UUAGC is that it allows defining tree traversals in a modular way. Users can define functions that are evaluated at each node separately and in the end UUAGC will combine all these functions into one big tree traversal.

As a first step I have reduced this problem down to the problem of defining a normal Haskell function over multiple modules. E.g. so that you would be able to write fac 0 = 1 in one module and fac n = n * fac (n - 1) in another module, which can then be combined into a complete function definition.

I have been able to implement this functionality in this repository: https://github.com/noughtmare/splitfuns (Abandon hope, all ye who enter here). This example shows how you can define the base case of the factorial function in one module:

-- Base.hs
{-# LANGUAGE TemplateHaskell, QuasiQuotes, DataKinds #-}
module Base (base) where

import Splitfuns (define, sfModule)

define [d|fac 0 = 1|]

base = $(sfModule)

And the recursive case can be defined in a separate module:

-- Recursive.hs
{-# LANGUAGE TemplateHaskell, QuasiQuotes, DataKinds #-}
module Recursive (recursive) where

import Splitfuns (define, sfModule)

define [d|fac n = n * fac (n - 1)|]

recursive = $(sfModule)

Those base and recursive cases can then be imported and collected to define the final function:

-- Main.hs
{-# LANGUAGE TemplateHaskell, QuasiQuotes #-}
module Main where

import Splitfuns (sfImport, collect)
import Base (base)
import Recursive (recursive)

sfImport 'base
sfImport 'recursive

fac :: Int -> Int
fac = $(collect "fac")

main :: IO ()
main = print (fac 5)

A big challenge was passing information from one module to another. The approach I have settled on is to serialize the data into integer which can then be used as a type literal in the type of a variable. That variable can then be imported, the type can be inspected and the integer can be deserialized into the original data type. I have implemented this approach in this file.

I had a lot of fun trying to implement this. This was my first real Template Haskell project, so feedback is very welcome!

Edit: I have found out that I don’t have to use the ugly serialization hack and I can instead use the Lift type class. I have updated the code on GitHub.

3 Likes

A bit late but: would this help us with the dreaded «circular imports» errors?

1 Like

I don’t think so, because this technique only allows you to move code from a module A to another module B that imports A. So, you will still run into circular imports if you then want to use the definitions from module B in module A again.

Maybe you can do something with Template Haskell that does solve the circular imports problems, but I don’t see a direct way to use my technique to do it.

1 Like