11

I've got a situation where I need to compile some Haskell code on different machines. At least one of these machines has a rather old version of Control.Concurrent.STM, that doesn't know modifyTVar. My current workaround is to copy the code for modifyTVar from a newer version of the package. This got me wondering, if it would be possible to use template Haskell to check if a function is already defined and only define it, if it's missing. I'm aware that the proper solution would probably be to get more recent packages, but the situation got me curious.

Jakob Runge
  • 2,287
  • 7
  • 36
  • 47

2 Answers2

8

It seems to be possible as follows. First a helper module:

{-# LANGUAGE TemplateHaskell #-}

module AddFn where

import Language.Haskell.TH

-- | Add a function if it doesn't exist.
addFn :: String -> Q [Dec] -> Q [Dec]
addFn name decl = do
    r <- lookupValueName name
    case r of
        Just l -> return []
        Nothing -> report False ("adding missing " ++ name) >> decl

and use it as in

{-# LANGUAGE TemplateHaskell #-}

module Main where

import AddFn
import qualified Data.Traversable as T

$(addFn "mapM"
    [d| mapM :: (Monad m) => (a -> m b) -> [a] -> m [b]
        mapM = T.mapM
    |])

$(addFn "mapM1"
    [d| mapM1 :: (Monad m) => (a -> m b) -> [a] -> m [b]
        mapM1 = T.mapM
    |])

The drawback is that it's using lookupValueName, which is only in the recent versions of TH, so when dealing with old installations, this probably won't help. Perhaps a possible solution would be to instead call reify on a given name, and use recover to handle the case when the name is missing.

Update: The version using reify instead of lookupValueName works:

-- | Add a function if it doesn't exist.
addFn :: String -> Q [Dec] -> Q [Dec]
addFn name decl = recover decl (reify (mkName name) >> return [])
Petr
  • 62,528
  • 13
  • 153
  • 317
3

Template Haskell is somewhat overkill for this - you can use CPP instead, using the MIN_VERSION macros that Cabal will define:

{-# LANGUAGE CPP #-}

#if MIN_VERSION_stm(2, 3, 0)
-- nothing
#else
modifyTVar = ...
#endif
Ganesh Sittampalam
  • 28,821
  • 4
  • 79
  • 98
  • I've got this running now, but I had to make two small adjustments, to get it working nicely with ghci as well. It was necessary to get ghci to include the cabal_macros.h. To do this I followed instructions from https://stackoverflow.com/questions/19622537/running-ghci-on-a-module-that-needs-language-cpp and https://stackoverflow.com/questions/3388261/ghci-configuration-file – Jakob Runge Jun 17 '14 at 11:31
  • 1
    With recent cabals, I think you can just use `cabal repl` – Ganesh Sittampalam Jun 17 '14 at 12:44