3

I'm currently writing a configuration for xmonad. I wanted to make a variable color theme config, so I made each color theme a type, eg data Dracula = Dracula, and a Color type class

class ColorTheme a where
  colorWhite::a->String
  colorWhite = const "#ffffff"
  -- rest of the colors

Now I wanted to change color theme then using a dmenu script, the script would write the chosen color theme name into a text file, each name being the string representation of a the theme type name.

Using template haskell I was able to read the string into a constructor name, eg

--theme.txt
Dracula
-- Colors.TH
{-# LANGUAGE TemplateHaskell #-}
module TH.Theme where

import Language.Haskell.TH
import System.IO
import Language.Haskell.TH.Syntax


retrieveThemeName =  
  do
    handle <- openFile "theme.txt" ReadMode
    name <-hGetLine handle
    return $ LitE (StringL name )
-- Colors.Theme
{-# LANGUAGE TemplateHaskell #-}
module Theme(
    module Theme,
    module Colors
) where

import Colors
import Language.Haskell.TH
import TH.Theme
import GHC.IO (unsafePerformIO)
import Language.Haskell.TH.Syntax

theme = $(conE (mkName $(runIO retrieveThemeName )))

The problem is that stack is not recompiling when the theme.txt changes, I read about addDependentFile from the Language.Haskell.TH.Syntax module, but I don't know how to use and did not find any tutorial, also, questions concerning the same problem either where using GHC, or were hinted to use addDependentFile without a written example.

I tried to write something like

--xmonad.hs

main :: IO ()
main = (xmonad . withSB mySB . docks . ewmhFullscreen . ewmh $ defaults) 
 >> (runQ $ addDependentFile "/absolute_path/to/theme.txt")

It throws exception, Q monad cannot be called inside IO monad.

So, If anyone can use addDependentFile, would you provide a simple example on how to use?

GHC version : 9.2.4 Stack version : 2.9.1


A working version of Li-yao Xia's solution

retrieveThemeName :: Q Exp
retrieveThemeName = do
  addDependentFile "/absolute_path/to/theme.txt"
  runIO $ do
    handle <- openFile "theme.txt" ReadMode
    name<-hGetLine handle
    return $ LitE (StringL name )
theme = $(conE (mkName $(retrieveThemeName) ))
duplode
  • 33,731
  • 7
  • 79
  • 150
Kareem Taha
  • 107
  • 1
  • 6

1 Answers1

3

You can call addDependentFile inside a splice ($( ... )). Here's how you can call it next to the action that needs the file:

retrieveThemeName :: Q String
retrieveThemeName = do
  addDependentFile "/absolute_path/to/theme.txt"
  runIO $ do
    handle <- openFile "theme.txt" ReadMode
    name <-hGetLine handle
    return name

I also removed an unnecessary level of quoting. You can call it like this:

theme = $(conE =<< (mkName <$> retrieveThemeName))
Li-yao Xia
  • 31,896
  • 2
  • 33
  • 56
  • Thanks for your help, however the code does not compile, namely `return name` errors with "cannot convert String to Name". – Kareem Taha Jan 18 '23 at 20:17
  • I can of course, either `return $ mkName name` and remove `mkName` call from `theme=..` or change the type of retrieveThemeName to `Q String`, however I cannot get `conE` to work it expects `Name` not `Q Name`. – Kareem Taha Jan 18 '23 at 20:20
  • I got it to work, thanks, I'll edit the question with a corrected version of your solutin. – Kareem Taha Jan 18 '23 at 20:37