LoginSignup
1
1

More than 5 years have passed since last update.

XMonad の Resume (<M-q>) が失敗する問題に対処する

Last updated at Posted at 2012-04-28

xmonad: executeFile: resource exhausted (Argument list too long)
なやつ。
ながすぎる引数で状態を渡しているのが原因で失敗していたので、一時ファイルを使うように。

Resume.hs
{-# LANGUAGE ScopedTypeVariables #-}

module Anekos.Resume (withStrongResume, reload) where


import Control.Exception (catch, bracket)
import Control.Monad (void)
import Data.List (elemIndex)
import Data.Map (toList)
import Data.Maybe (mapMaybe)
import Prelude hiding (catch)
import System.Directory (removeFile)
import System.Environment (getArgs, withArgs)
import System.Exit (ExitCode(..))
import System.IO (FilePath)
import System.Posix.Files (fileExist)
import System.Posix.Process (executeFile)
import System.Process (runCommand, waitForProcess)
import XMonad
import qualified XMonad.StackSet as SS


stateFilepath :: FilePath
stateFilepath = "/tmp/xmonad-state"


withStrongResume :: IO () -> IO ()
withStrongResume act = do
    args <- newArgs
    withArgs args act

-- ref: restart@XMonad/Operations.hs

reload :: X ()
reload = do
    broadcastMessage ReleaseResources
    io . flush =<< asks display
    text <- gets $ show . (\s -> windowSetData s : extState s)
    io $ writeFile stateFilepath text
    whenX (recompile True) $ catchIO (executeFile "xmonad" True [] Nothing)
  where
    windowSetData   = show . SS.mapLayout show . windowset
    extState        = return . show . mapMaybe maybeShow . toList . extensibleState
    maybeShow (t, Right (PersistentExtension ext)) = Just (t, show ext)
    maybeShow (t, Left str)                        = Just (t, str)
    maybeShow _                                    = Nothing


newArgs :: IO [String]
newArgs = do cnt <- readFile stateFilepath
             let args = cnt `seq` read cnt
             removeFile stateFilepath
             return ("--resume" : args)
          `catch`
          \(e::IOError) -> return []

xmonad.hs

import Anekos.Resume (withStrongResume)

import XMonad


main = do
  withStrongResume $ xmonad $ defaultConfig
    { borderWidth        = 0
    , 
    -- ....
    } `additionalKeysP` myKeys

myKeys = [("M-q",       reload)]


1
1
0

Register as a new user and use Qiita more conveniently

  1. You get articles that match your needs
  2. You can efficiently read back useful information
  3. You can use dark theme
What you can do with signing up
1
1