[Xmonad] [ot] [xmobar-related] existentials for plugin-ing (?)
Andrea Rossato
mailing_list at istitutocolli.org
Tue Jul 10 12:34:19 EDT 2007
Hi,
I had this crazy idea a couple of nights ago. I didn't dare to ask in
the haskell-cafe because I fear it could be too stupid. The xmonad
community is smaller (even though the greatest haskeller I know about
read and write xmonad code: so posting here could be even worse...;-)
so I'm posting here. It is vaguely related to XMonad after all.
XMobar, the status bar I'm writing for XMonad, now runs monitors
internally. You set monitors and external commands in the
configuration file. I'm thinking of writing also command line options,
but the possibility of using a readable data type for reading a
configuration file can make users' life easier, I think, even though
there are no debugging messages and that can be confusing (but you can
test the configuration with ghc!).
Now, in the configuration there is this commands option, a list of
tuples: the data type for commands and an Int, the interval for each
successive runs.
The data type for the commands was suggested by Spencer. Very simply:
data Command = Exec ProgramName Args
| Network Interface Args
etc., where Network is a constructor to be used for running the
network interface monitor.
Then there is a class (Exec - not much fantasy, I know) for which a
method (run :: e -> IO String) must be defined.
So there are all the needed instances for running, showing, etc, etc.
Now, I though that writing a plugin should just mean creating a type
and making it an instance of Exec. XMobar takes the list of the
commands to be run from the configuration "commands" option, so that's
easy: just a polymorphic list of commands to be run and I don't need
anything else for supporting plugins...;-)
Cool I though, it's just a matter of creating the needed polymorphic
list. With one more constrain: Config, that has that list inside, must
be readable!
Ok, this is not an easy task, since existentially qualified types are
not derivable, and reading them seemed not even possible.[1] Writing a
too complicated parser for a Read instance is not an option.
Now, thanks to the help of Claus Reinke I came up with a solution for
that too.[2]
The code[3] works! You can feed readConfig with a file like this:
MD {rec1 = "Ciao", rec2 = "Ciao Ciao", rec3 = [MT (T3a,1),MT (T2b,3),MT (T1b,3),MT (T1a,3)]}
and it reads it!
Now I would like to ask you if such an approach could be tried or is
just insane.
I mean, would you run a status bar that, to configure with you
favorite plugin (type HelloWorld = HelloWorld [] []), requires you to
write in Config.hs something like:
hidden = undefined :: (Commands,(HelloWorld,()))
I don't know if I would.
Let me know your thoughts please, in exchange I'll chase and try to
fix as many XMobar bugs as I possibly can ...;-)
All the best
Andrea
[1] According to this thread:
http://www.haskell.org/pipermail/haskell-cafe/2004-April/006092.html
[2] Look here:
http://www.haskell.org/pipermail/haskell-cafe/2007-July/028205.html
http://www.haskell.org/pipermail/haskell-cafe/2007-July/028227.html
[3] the code
{-# OPTIONS -fglasgow-exts #-}
module Test where
import Control.Monad
import Text.Read
import Text.ParserCombinators.ReadPrec
data MyData =
MD { rec1 :: String
, rec2 :: String
, rec3 :: [MyType]
} deriving (Read,Show)
data MyType = forall e . (MyClass e,Show e, Read e) => MT (e,Int)
instance Show MyType where
show (MT a) = "MT " ++ show a
class MyClass c where
myShow :: c -> String
data TipoA = T1a
| T2a
| T3a
deriving(Show,Read,Eq)
instance MyClass TipoA where
myShow T1a = "t1a"
myShow T2a = "t2a"
myShow T3a = "t3a"
data TipoB = T1b
| T2b
| T3b
deriving(Show,Read,Eq)
instance MyClass TipoB where
myShow T1b = "t1b"
myShow T2b = "t2b"
myShow T3b = "t3b"
-- tricky part starts here
-- the solution comes from Claus Reinke
class ReadAsAnyOf ts ex where -- read an existential as any of hidden types ts
readAsAnyOf :: ts -> ReadPrec ex
instance ReadAsAnyOf () ex where
readAsAnyOf ~() = mzero
instance (Read t, Show t, MyClass t, ReadAsAnyOf ts MyType) => ReadAsAnyOf (t,ts) MyType where
readAsAnyOf ~(t,ts) = r t `mplus` readAsAnyOf ts
where r t = do { m <- readPrec; return (MT (m `asTypeOf` (t,0))) }
instance Read MyType where
readPrec = readMT
readMT :: ReadPrec MyType
readMT = prec 10 $ do
Ident "MT" <- lexP
parens $ readAsAnyOf hidden -- r T1a `mplus` r T1b
hidden = undefined :: (TipoA,(TipoB,()))
readConfig :: FilePath -> IO MyData
readConfig f =
do s <- readFile f
case reads s of
[(config,_)] -> return config
[] -> error ("Corrupt config file: " ++ f)
_ -> error ("Some problem occured. Aborting...")
More information about the Xmonad
mailing list