[Xmonad] About binary package and configuration file.

Andrea Rossato mailing_list at istitutocolli.org
Tue Oct 9 04:34:06 EDT 2007


On Mon, Oct 08, 2007 at 12:08:07AM +0900, MATSUYAMA Tomohiro wrote:
> Hi, all.
> 
> I think we should distribute a binary package (x86 at least) to
> make it easy to install xmonad (it's too difficult to install for
> an user who has no experience about Haskell).
> If we should do it, we also have to support an user
> configuration file like ~/.xmonadrc.
> 
> So, I want to realize this propsal, but even I (I am a begginer)
> find it will be hard job (especially about Config.hs).
> 
> Please tell me how to do it smartly or things you think about it.

Well, I have an idea but I don't know it is indeed smart...But you
said you are a beginner (I'm not that far from that too) and wanted
some thought... and there they are...

Just my thoughts.

Attached you'll find a contib module (XMonadContrib.BinaryConfig).

To use:
1. save the attached xmonad.conf in /some/path
2. in Config.hs
import XMonadContrib.BinaryConfig

myConfig = readConfig "/some/path/xmonad.conf"

and change:
workspaces = map show [1 .. (workspaceNumber myConfig) :: Int]
focusedBorderColor = bColor myConfig


then start playing around with BinaryConfig.Config, adding new fields
and modifying accordingly Config.hs

The ugly part obviously, is the unsafePerformIO...

Hope this helps somehow.

Andrea
-------------- next part --------------
module XMonadContrib.BinaryConfig where

import System.Posix.Files
import Foreign (unsafePerformIO)

data Config =
     Config { workspaceNumber :: Int
            , bColor     :: String
            } deriving (Read, Show)

readConfig :: FilePath -> Config
readConfig f = unsafePerformIO $ do
  file <- fileExist f
  s    <- if file then readFile f else error $ f ++ ": file not found!\n"
  case reads s of
    [(conf,_)] -> return conf
    []         -> error $ f ++ ": configuration file contains errors!\n"
    _          -> error ("Some problem occured. Aborting...")
-------------- next part --------------
Config { workspaceNumber = 4 , bColor = "blue" }


More information about the Xmonad mailing list