Defining ExtensionClass (Maybe a) instance in xmonad.

Hi. I've tried to define (Maybe a) instance for ExtensionClass from XMonad/Core.hs in such way, that extensionType value would use the same data constructor as was used for the type a itself. But the code below typechecks only, if i add (Show a) and (Read a) constraints to (Maybe a) instance definition, what makes such definition useless for types, which do not have these instances and do not want to use PersistentExtension . How can i define (Maybe a) instance without (Show a) and (Read a) constraints?
{-# LANGUAGE ExistentialQuantification #-} import Data.Typeable
-- This one does not typecheck --instance ExtensionClass a => ExtensionClass (Maybe a) where instance (Show a, Read a, ExtensionClass a) => ExtensionClass (Maybe a) where initialValue = Nothing extensionType x = let Just i = (Just initialValue) `asTypeOf` x in case extensionType i of PersistentExtension _ -> PersistentExtension x StateExtension _ -> StateExtension x
Here is class definition from XMonad/Core.hs:
class Typeable a => ExtensionClass a where initialValue :: a extensionType :: a -> StateExtension extensionType = StateExtension
data StateExtension = forall a. ExtensionClass a => StateExtension a | forall a. (Read a, Show a, ExtensionClass a) => PersistentExtension a
-- Dmitriy Matrosov

On Mon, Jan 19, 2015 at 8:01 AM, Dmitriy Matrosov
I've tried to define (Maybe a) instance for ExtensionClass from XMonad/Core.hs in such way, that extensionType value would use the same data constructor as was used for the type a itself. But the code below typechecks only, if i add (Show a) and (Read a) constraints to (Maybe a) instance definition, what makes such definition useless for types, which do not have these instances and do not want to use PersistentExtension .
ExtensionClass data is stored in the layout and therefore requires those constraints. No, there is no magic to cause non-persistent ExtensionClass data to be stored in some other place different from where the rest of it is stored. I'm also wondering how much trouble you can get into by conflicting with some other ExtensionClass that already uses Maybe. -- brandon s allbery kf8nh sine nomine associates allbery.b@gmail.com ballbery@sinenomine.net unix, openafs, kerberos, infrastructure, xmonad http://sinenomine.net

On 2015年01月19日 17:55, Brandon Allbery wrote:
ExtensionClass data is stored in the layout and therefore requires those constraints. No, there is no magic to cause non-persistent ExtensionClass data to be stored in some other place different from where the rest of it is stored.
Thanks for answer, but i don't understand why it should be stored differently (i don't know how Typeable and ExtensionClass works, so may be this is the reason): if i define instance (ExtensionClass a) => ExtensionClass (Maybe a) where initialValue = Nothing extensionType = StateExtension then there is no (Show a, Read a) constraint. It will come up only, when i mention PersistentExtension in one of case branches, but, on the other hand, may be i can avoid pattern-matching on StateExtension constructor and somehow use data constructor from (extensionType :: a -> StateExtension) directly? I'm already have (ExtensibleState a) constraint, so does type a has Show and Read instances or not, i think, this is correct (at least theoretically) to define extensionType for (Maybe a) to use the same data constructor.
I'm also wondering how much trouble you can get into by conflicting with some other ExtensionClass that already uses Maybe.
Well, i've just tried to restart xmobar properly, when i reload xmonad. I've noticed, that xmobar restarts with xmonad only, when it uses StdinReader (in template), otherwise new (another) xmobar instance spawned. I want to define generic way for restarting something, spawned by xmonad.
{-# LANGUAGE MultiParamTypeClasses , FunctionalDependencies , FlexibleInstances , FlexibleContexts , DeriveDataTypeable #-}
import XMonad import qualified XMonad.Util.ExtensibleState as XS import System.Posix.Process import System.IO import System.Posix.IO import System.Posix.Types
I may define a data type containing required start/stop functions and depending on some identifier (ProcessID actually):
data Restartable a = Restartable { killP :: a -> X () , runP :: X a }
or i can define interface, which all identifiers should support:
class RestartClass a where killP' :: a -> X () runP' :: X a
Then i may store (Maybe a) in extensible state and write generic restart functions:
restartP :: (ExtensionClass (Maybe a)) => Restartable a -> X () restartP r = do mp <- XS.get whenJust mp (killP r) p' <- runP r XS.put (Just p')
restartP' :: (ExtensionClass (Maybe a), RestartClass a) => X a restartP' = do mp <- XS.get whenJust mp killP' p' <- runP' XS.put (Just p' `asTypeOf` mp) return p'
and, finally, i may define Restartable value and RestartClass instance for xmobar, and define restart function for xmobar:
newtype XmobarPID = XmobarPID ProcessID deriving (Show, Read, Typeable)
newtype XmobarHandle = XmobarHandle (Maybe Handle) deriving (Typeable)
instance ExtensionClass XmobarHandle where initialValue = XmobarHandle Nothing
instance (Show a, Read a, Typeable a) => ExtensionClass (Maybe a) where initialValue = Nothing extensionType = PersistentExtension
-- For data type approach.. xmobarP :: Restartable XmobarPID xmobarP = Restartable killXmobar runXmobar where killXmobar :: XmobarPID -> X () killXmobar (XmobarPID p) = io $ spawn ("kill " ++ show p) runXmobar :: X XmobarPID runXmobar = do (h, p) <- spawnPipe' ["/usr/bin/xmobar", "/home/sgf/.xmobarrc"] XS.put (XmobarHandle (Just h)) return (XmobarPID p)
restartXmobar :: X () restartXmobar = restartP xmobarP
-- For type-class approach.. instance RestartClass XmobarPID where killP' (XmobarPID p) = io $ spawn ("kill " ++ show p) runP' = do (h, p) <- spawnPipe' ["/usr/bin/xmobar", "/home/sgf/.xmobarrc"] XS.put (XmobarHandle (Just h)) return (XmobarPID p)
restartXmobar' :: X () restartXmobar' = do p <- restartP' let _ = p `asTypeOf` XmobarPID undefined return ()
-- Rewritten version from XMonad.Util.Run: do not run shell and return -- ProcessID . spawnPipe' :: [String] -> X (Handle, ProcessID) spawnPipe' (x : xs) = io $ do (rd, wr) <- createPipe setFdOption wr CloseOnExec True h <- fdToHandle wr hSetBuffering h LineBuffering p <- xfork $ do _ <- dupTo rd stdInput executeFile x False xs Nothing closeFd rd return (h, p)
but here i can't reuse ExtensionClass (Maybe a) instance for XmobarHandle, because Handle does not have Read instance and can't have extensionType = PersistentExtension . So i've added Maybe in XmobarHandle newtype. Also, i may go the other way: add Maybe to XmobarPID value, and then define ExtensionClass instance for XmobarPID. Then i won't need ExtensionClass (Maybe a) instance.
newtype XmobarPID2 = XmobarPID2 (Maybe ProcessID) deriving (Typeable, Show, Read)
instance ExtensionClass XmobarPID2 where initialValue = XmobarPID2 Nothing extensionType = PersistentExtension
In this case i need a way to convert value of some type into Maybe:
class Lens a b | a -> b where view :: a -> b set :: b -> a -> a
instance Lens XmobarPID2 (Maybe XmobarPID) where view (XmobarPID2 x) = fmap XmobarPID x set (Just (XmobarPID x)) _ = XmobarPID2 (Just x) set Nothing z = z
then restartP and restartP' should be adjusted to use view/set from Lens class
-- Why ghc can't infer type a from b here? I.e. i need to return X a, not -- X () as before. Is it because of functional dependency a -> b in Lens -- definition ? restartP2 :: (ExtensionClass a, Lens a (Maybe b)) => Restartable b -> X a restartP2 r = do mp <- XS.get whenJust (view mp) (killP r) p' <- runP r let mp' = set (Just p') mp XS.put mp' return mp'
restartP2' :: (ExtensionClass a, Lens a (Maybe b), RestartClass b) => X a restartP2' = do mp <- XS.get whenJust (view mp) killP' p' <- runP' let mp' = set (Just p') mp XS.put mp' return mp'
but now restartXmobar with Restartable value will not be that simple as before:
restartXmobar2 :: X () restartXmobar2 = do p <- restartP2 xmobarP let _ = p `asTypeOf` XmobarPID2 undefined return ()
restartXmobar2' :: X () restartXmobar2' = do p <- restartP2' let _ = p `asTypeOf` XmobarPID2 undefined return ()
So, i end up with two start/stop interface implementations: - Restartable data type - or RestartClass. and with two extensible state implementations: - store identifier in Maybe - or add Maybe to identifier itself. I don't like `asTypeOf` in restartXmobar variants . And i don't like, that i can't reuse ExtensionClass (Maybe a) instance for XmobarHandle .. What implementation will be more idiomatic? Or, may be, something completely different?

On Tue, Jan 20, 2015 at 2:51 PM, Dmitriy Matrosov
then there is no (Show a, Read a) constraint. It will come up only, when i mention PersistentExtension in one of case branches, but, on the other hand, may be i can avoid
That would be expected, I believe; if you mentioned it, it must apply to the whole instance, not just one case branch. But I'm not quite clear on what you are saying here.
Well, i've just tried to restart xmobar properly, when i reload xmonad. I've noticed, that xmobar restarts with xmonad only, when it uses StdinReader (in template), otherwise new (another) xmobar instance spawned.
That is expected. You are expecting some kind of magic happening where we track every pipe and forcibly terminate all of them, when all we are doing is using normal POSIX semantics where pipes get closed automatically but the process on the other side will only find out if it is reading from the pipe (i.e. xmobar's StdinReader). Doing the magic that you and others seem to expect would be in one way or another very expensive --- either we make xmonad only work on one particular OS family, or we accept that we can only spawn so many pipes because of child process limits, or we have to make spawnPipe spawn a backchannel to report the ultimate child *and* we must restrict what kinds of things you can run on the other end so we can keep track and kill it. (You probably want to consider the above with respect to your proposed extension; the POSIX subprocess model has many dark corners. In particular, remember that the child process "closest" to xmonad in a spawnPipe is a shell, *not* the program you ran. And that shell has the same problem, so killing it will not kill the xmobar it starts!) -- brandon s allbery kf8nh sine nomine associates allbery.b@gmail.com ballbery@sinenomine.net unix, openafs, kerberos, infrastructure, xmonad http://sinenomine.net

Hi,
sadly, I don't have an answer to all your technical
question. Furthermore, I consider myself to be a Haskell starter so I
cannot answer your questions concerning idiomatic code properly. But
here is an answer anyway. :)
Dmitriy Matrosov
On 2015年01月19日 17:55, Brandon Allbery wrote: […]
I want to define generic way for restarting something, spawned by xmonad.
[…]
I may define a data type containing required start/stop functions and depending on some identifier (ProcessID actually):
I had kind of the same problem and went for the this option, i.e. defining a data type. But I implemented this via a pid file which gets saved on xmonad start up. This way these program can even survive a restart of the XServer properly. https://github.com/fuzzy-id/my-xmonad/blob/master/My/PidProg.hs (see Config.hs in the same repo for an example of how I use them.) However, I don't see the point in defining the data type to contain start/stop functions. These will be the same for most of the programs, won't they?
[…]
or i can define interface, which all identifiers should support:
This makes sense if you want to prepare to have a whole group of different instances. We cannot know whether or not this is your case. If you want to be prepared for this – i.e. over-engineer the whole thing – I'd probably go this path. Define a class which asks its instances to have a start/stop function and so on. Then you can define an instance which xmobar and probably a whole lot of other programs will nicely fit. Hope this helps Thomas.

Hi. Sorry for big delay, rewriting my previous solution takes a lot of time. On 2015年01月20日 23:14, Brandon Allbery wrote:
then there is no (Show a, Read a) constraint. It will come up only, when i mention PersistentExtension in one of case branches, but, on the other hand, may be i can avoid
That would be expected, I believe; if you mentioned it, it must apply to the whole instance, not just one case branch. But I'm not quite clear on what you are saying here.
I mean, that i already have contraint (ExtensionClass a) in e.g. instance (ExtensionClass a) => ExtensionClass (Maybe a) where initialValue = Nothing then if type a had Show and Read instances, then (Maybe a) will had them too and i may define 'extensionType = PersistentExtension' in (Maybe a) instance. If type a had no Show and Read instances, then i may only define (Maybe a) to be a StateExtension . Thus, theoretically, (ExtensionClass a) contraint is enough, and i want to express above condition on (Maybe a) extensionType value with only that contraint. I can't express it by pattern-matching on type a's StateExtension data contructor, because that will bring up (Show a, Read a) constraint on (Maybe a) instance. I.e. i, probably, can't do it with condition at data level. Then, may be, i can make a condition at type level somehow?
In particular, remember that the child process "closest" to xmonad in a spawnPipe is a shell, *not* the program you ran. And that shell has the same problem, so killing it will not kill the xmobar it starts!)
Yes, i've noticed that, and that's why i modify spawnPipe from XMonad.Util.Run to run specified process directly, not through the shell. But, perhaps, i also may add 'exec ' before command executed by shell too. On 2015年01月21日 01:17, Thomas Bach wrote:
I had kind of the same problem and went for the this option, i.e. defining a data type. But I implemented this via a pid file which gets saved on xmonad start up. This way these program can even survive a restart of the XServer properly.
Thanks for answer, i've tried to integrate your solution with my (below). But i don't understand, why may i need to know pid of processes after restarting X server? They all will die anyway, won't they?
However, I don't see the point in defining the data type to contain start/stop functions. These will be the same for most of the programs,
Not exactly. Let's consider three of them: xmobar, trayer and feh . For xmobar i need to create a pipe and save Handle in extensible state, so i can access it later from dynamicLogWithPP . For trayer i just need to start a program with arguments. And for feh i need to check existence of '~/.fehbg' file and evaluate its content through shell. If file does not exist, i need to use some fallback, like `xsetroot -grey`. Though, feh finishes right after setting background and is not very good exameple, still start/stop functions may not be the same: they may open pipes, check existence of different files, etc. - all that you usually do in shell scripts :) Your PidProg-s implement only "trayer" case. xmobar in your Config.hs started using `xmobar` function from XMonad.Hooks.DynamicLog , and, i guess, it restarts correctly with xmonad only, because you have StdinReader in template in your xmobarrc (in other words, your Config.hs has the same problem with xmobar, as i try to solve here, you just don't see it). However, it turns out, that your PidProg and my per-program newtype-s has one more difference: you have names for ProcessID-s (e.g. command record may be thought as such), but i have not. So, let's start from the beginning. I may just store all ProcessID-s in list - [ProcessID]. But then i don't even know which ProcessID belongs to which process. Then, i may add names for ProcessID-s, so i can distinguish them later - e.g. [(String, ProcessID)]. This is essentially your solution: pid file (and PidProg value) binds process name and pid together. But now all ProcessID-s have the same start/stop functions. Finally, i may store start/stop functions in data type as well, but such type can't have Show and Read instance, so it can't be stored in extensible state persistently with 'extensionType = PersistentExtension'. Then i may try to store in extensible state only ProcessID and name and find start/stop function for them using type-class . Moreover, i even does not need name - i can use Eq instance for this and compare any fields (not only e.g. command names) there. So, here is my rewritten implementation of that ideas:
{-# LANGUAGE FlexibleContexts , DeriveDataTypeable , GeneralizedNewtypeDeriving #-}
import Data.Monoid import XMonad import qualified XMonad.Util.ExtensibleState as XS import System.Posix.Process import System.IO import System.Posix.IO import System.Posix.Types import System.Posix.Signals import System.Directory import System.FilePath import Control.Exception import Control.Monad
spawnPipe' :: [String] -> X (Handle, ProcessID) spawnPipe' (x : xs) = io $ do (rd, wr) <- createPipe setFdOption wr CloseOnExec True h <- fdToHandle wr hSetBuffering h LineBuffering p <- xfork $ do _ <- dupTo rd stdInput --executeFile "/bin/sh" False ["-c", encodeString x] Nothing executeFile x True xs Nothing closeFd rd return (h, p)
spawnPID' :: MonadIO m => [String] -> m ProcessID spawnPID' (x : xs) = xfork $ executeFile x True xs Nothing
I've defined XmobarPID3 newtype allowing to launching several xmobar's
data XmobarPID3 = XmobarPID3 { xmobarPID :: First ProcessID , xmobarConf :: FilePath } deriving (Show, Read, Typeable) instance Eq XmobarPID3 where XmobarPID3 {xmobarConf = xcf} == XmobarPID3 {xmobarConf = ycf} | xcf == ycf = True | otherwise = False instance Monoid XmobarPID3 where mempty = XmobarPID3 { xmobarPID = First Nothing , xmobarConf = "" } x `mappend` y = XmobarPID3 { xmobarPID = xmobarPID x `mappend` xmobarPID y , xmobarConf = xmobarConf x }
newtype XmobarHandle = XmobarHandle (Maybe Handle) deriving (Typeable) instance ExtensionClass XmobarHandle where initialValue = XmobarHandle Nothing
and TrayerPID3 and FehPID3 designed for one program instance only (because all values of these types are equal):
newtype TrayerPID3 = TrayerPID3 {trayerPID :: First ProcessID} deriving (Show, Read, Typeable, Monoid) instance Eq TrayerPID3 where _ == _ = True
newtype FehPID3 = FehPID3 {fehPID :: First ProcessID} deriving (Show, Read, Typeable, Monoid) instance Eq FehPID3 where _ == _ = True
Then i define typeclass for start/stop interface (why there is Monoid constraint see runWith code below):
class (Eq a, Monoid a) => RestartClass3 a where getPidP3 :: a -> Maybe ProcessID setPidP3 :: Maybe ProcessID -> a -> a runP3 :: a -> X a -- restartP3' relies on PID 'Nothing' after killP3, because it then calls -- startP3' and it won't do anything, if PID will still exist. So, here i -- should either set it to Nothing, or wait until it really terminates. killP3 :: a -> X a killP3 x = io $ do whenJust (getPidP3 x) $ signalProcess sigTERM return (setPidP3 Nothing x)
defaultRunP3 :: RestartClass3 a => [String] -> a -> X a defaultRunP3 xs z = do p <- spawnPID' xs return (setPidP3 (Just p) z)
then i define instances for XmobarPID3 and FehPID3 with custom runP3 functions:
instance RestartClass3 XmobarPID3 where getPidP3 = getFirst . xmobarPID setPidP3 mp' x = x{xmobarPID = First mp'} runP3 x = do (h, p) <- spawnPipe' ["/usr/bin/xmobar", xmobarConf x] XS.put (XmobarHandle (Just h)) return (x{xmobarPID = First (Just p)})
instance RestartClass3 FehPID3 where getPidP3 = getFirst . fehPID setPidP3 mp' x = x{fehPID = First mp'} runP3 x = do h <- io $ getHomeDirectory let f = h > ".fehbg" b <- io $ doesFileExist f p <- if b then do cmd <- io $ readFile f -- ~/.fehbg content written assuming evaluation by shell, -- but i still need real process's PID, so add 'exec' . spawnPID ("exec " ++ cmd) else spawnPID' ["xsetroot", "-grey"] return (x{fehPID = First (Just p)})
trayer will use default run/kill implementation:
instance RestartClass3 TrayerPID3 where getPidP3 = getFirst . trayerPID setPidP3 mp' x = x{trayerPID = First mp'} runP3 = defaultRunP3 [ "trayer" , "--edge", "top", "--align", "right" , "--SetDockType", "true", "--SetPartialStrut", "true" , "--expand", "true", "--width", "10" , "--transparent", "true" , "--tint", "0x191970" , "--height", "12" ]
The other deficiency of my previous implementation was that i may store only one program's info for each newtype (e.g. i may run only one xmobar, because i've used (Maybe XmobarPID) to store its pid). Now i'll switch to list instead of Maybe in extensible state. Also, i want to make 'respawn' record of PidProg implicit: if i call 'restart' i ever want to kill program and run again; if i just want to be sure, that program is running, i should call the 'start' instead.
instance (Show a, Read a, Typeable a) => ExtensionClass [a] where initialValue = [] extensionType = PersistentExtension
-- Similar to insertWith from Data.Map, but for lists. insertWith :: Eq a => (a -> a -> a) -> a -> [a] -> [a] insertWith f y [] = [y] insertWith f y (x : xs) | y == x = f y x : xs | otherwise = x : insertWith f y xs
-- Run function on matched PIDs with specific type. -- Argument's Eq instance is used to find value in extensible state -- to act upon. Also, argument is `mappend`-ed to found value, -- so i should pass mempty, if i want to just "match", and -- something different, if i want to "match and replace". runWith :: (Eq a, Monoid a, ExtensionClass [a]) => (a -> X a) -> a -> X () runWith f y = do xs <- XS.gets (insertWith mappend y) xs'' <- mapM (\x -> if y == x then f x else return x) xs XS.put xs''
-- Based on doesPidProgRun . refreshPid :: (MonadIO m, RestartClass3 a) => a -> m a refreshPid x = case (getPidP3 x) of Nothing -> return x Just p -> liftIO $ do either (const (setPidP3 Nothing x)) (const x) `fmap` (try $ getProcessPriority p :: IO (Either IOException Int))
-- Run, if program is not running or already dead, otherwise do nothing. -- Note, that this function work on argument, not on extensible state. startP3' :: RestartClass3 a => a -> X a startP3' x = do x' <- refreshPid x case (getPidP3 x') of Nothing -> runP3 x' Just _ -> return x'
-- Kill program and run again. Note, that it will run again only, -- if killP3 kills it properly: either sets pid to Nothing -- or waits until it dies. -- Note, that this function work on argument, not on extensible state. restartP3' :: RestartClass3 a => a -> X a restartP3' = startP3' <=< killP3 <=< refreshPid
-- Here are versions of start/restart working on extensible state. -- Usually, these should be used. startP3 :: (ExtensionClass [a], RestartClass3 a) => a -> X () startP3 = runWith startP3'
restartP3 :: (ExtensionClass [a], RestartClass3 a) => a -> X () restartP3 = runWith restartP3'
Finally, i may define some concerete examples:
xmobarTop :: XmobarPID3 xmobarTop = XmobarPID3 { xmobarPID = First Nothing , xmobarConf = "/home/sgf" > ".xmobarrc" } xmobarBot :: XmobarPID3 xmobarBot = XmobarPID3 { xmobarPID = First Nothing , xmobarConf = "/home/sgf" > ".xmobarrc2" } trayer :: TrayerPID3 trayer = TrayerPID3 {trayerPID = First Nothing}
feh :: FehPID3 feh = FehPID3 {fehPID = First Nothing}
restartXmobarTop :: X () restartXmobarTop = restartP3 xmobarTop startXmobarTop :: X () startXmobarTop = startP3 xmobarTop
restartXmobarBoth :: X () restartXmobarBoth = mapM_ restartP3 [xmobarTop, xmobarBot] startXmobarBoth :: X () startXmobarBoth = mapM_ startP3 [xmobarTop, xmobarBot]
restartAll :: X () restartAll = do startP3 feh restartP3 trayer mapM_ restartP3 [xmobarTop, xmobarBot] startAll :: X () startAll = do startP3 feh startP3 trayer mapM_ startP3 [xmobarTop, xmobarBot]
Usually, i should just use `restartAll` in startupHook .

On 2015年01月25日 21:09, Dmitriy Matrosov wrote:
Hi.
Sorry for big delay, rewriting my previous solution takes a lot of time.
On 2015年01月20日 23:14, Brandon Allbery wrote:
then there is no (Show a, Read a) constraint. It will come up only, when i mention PersistentExtension in one of case branches, but, on the other hand, may be i can avoid
That would be expected, I believe; if you mentioned it, it must apply to the whole instance, not just one case branch. But I'm not quite clear on what you are saying here.
I mean, that i already have contraint (ExtensionClass a) in e.g.
instance (ExtensionClass a) => ExtensionClass (Maybe a) where initialValue = Nothing
then if type a had Show and Read instances, then (Maybe a) will had them too and i may define 'extensionType = PersistentExtension' in (Maybe a) instance. If type a had no Show and Read instances, then i may only define (Maybe a) to be a StateExtension . Thus, theoretically, (ExtensionClass a) contraint is enough, and i want to express above condition on (Maybe a) extensionType value with only that contraint. I can't express it by pattern-matching on type a's StateExtension data contructor, because that will bring up (Show a, Read a) constraint on (Maybe a) instance. I.e. i, probably, can't do it with condition at data level. Then, may be, i can make a condition at type level somehow?
Hm, i think, i miss something here. There should be: if type a had Show and Read instances * and have 'extensionType = PersistentExtension' * , then (Maybe a) * may * had it too. If type a had no Show and Read instances, then i may only define (Maybe a) to be a StateExtension .
participants (3)
-
Brandon Allbery
-
Dmitriy Matrosov
-
Thomas Bach