
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?