[xmonad] darcs patch: Separate source and build directories (and 1 more)

Carsten Mattner carstenmattner at googlemail.com
Tue Jun 26 22:04:25 CEST 2012


On Tue, Jun 26, 2012 at 9:16 PM,  <daniel.trstenjak at googlemail.com> wrote:
> 2 patches for repository http://code.haskell.org/xmonad:
>
> Thu Jun  7 15:16:32 CEST 2012  daniel.trstenjak at gmail.com
>  * Separate source and build directories
>  The source files are still located in '~/.xmonad'
>  and the build files and the xmonad binary are now put
>  into '~/.xmonad_build'.

An alternative location could be ~/.cache/xmonad.
yi - possibly via dyre - stores stuff in ~/.cache/yi.

>  By separating the source and build directories it's
>  easier and nicer to backup and synchronize the source files.
>
> Tue Jun 26 20:26:40 CEST 2012  daniel.trstenjak at gmail.com
>  * Add getXMonadDir for backward compatibility
>
>
>
> [Separate source and build directories
> daniel.trstenjak at gmail.com**20120607131632
>  Ignore-this: 28d77ca18bd2f05013759b3b50cc1476
>  The source files are still located in '~/.xmonad'
>  and the build files and the xmonad binary are now put
>  into '~/.xmonad_build'.
>
>  By separating the source and build directories it's
>  easier and nicer to backup and synchronize the source files.
> ] {
> hunk ./Main.hs 95
>  buildLaunch ::  IO ()
>  buildLaunch = do
>     recompile False
> -    dir  <- getXMonadDir
> -    args <- getArgs
> -    executeFile (dir ++ "/xmonad-"++arch++"-"++os) False args Nothing
> +    binPath <- getXMonadBinaryPath
> +    args    <- getArgs
> +    executeFile binPath False args Nothing
>     return ()
>
>  sendRestart :: IO ()
> hunk ./XMonad/Core.hs 28
>     StateExtension(..), ExtensionClass(..),
>     runX, catchX, userCode, userCodeDef, io, catchIO, installSignalHandlers, uninstallSignalHandlers,
>     withDisplay, withWindowSet, isRoot, runOnWorkspaces,
> -    getAtom, spawn, spawnPID, xfork, getXMonadDir, recompile, trace, whenJust, whenX,
> -    atom_WM_STATE, atom_WM_PROTOCOLS, atom_WM_DELETE_WINDOW, ManageHook, Query(..), runQuery
> +    getAtom, spawn, spawnPID, xfork, getXMonadBinaryPath, getXMonadSourceDir, getXMonadBuildDir,
> +    recompile, trace, whenJust, whenX, atom_WM_STATE, atom_WM_PROTOCOLS, atom_WM_DELETE_WINDOW, ManageHook, Query(..), runQuery
>   ) where
>
>  import XMonad.StackSet hiding (modify)
> hunk ./XMonad/Core.hs 420
>     modify $ \s -> s { windowset = ws { current = c, visible = v, hidden = h } }
>
>  -- | Return the path to @~\/.xmonad at .
> -getXMonadDir :: MonadIO m => m String
> -getXMonadDir = io $ getAppUserDataDirectory "xmonad"
> +getXMonadSourceDir :: MonadIO m => m String
> +getXMonadSourceDir = io $ getAppUserDataDirectory "xmonad"
> +
> +-- | Return the path to @~\/.xmonad_build at .
> +getXMonadBuildDir :: MonadIO m => m String
> +getXMonadBuildDir = do
> +   dir <- io $ (++ "_build") <$> getXMonadSourceDir
> +   io $ createDirectoryIfMissing False dir
> +   return dir
> +
> +getXMonadBinaryPath :: MonadIO m => m String
> +getXMonadBinaryPath = io $ (</> binName) <$> getXMonadBuildDir
> +   where
> +      binName = "xmonad-" ++ arch ++ "-" ++ os
>
>  -- | 'recompile force', recompile @~\/.xmonad\/xmonad.hs@ when any of the
>  -- following apply:
> hunk ./XMonad/Core.hs 456
>  --
>  recompile :: MonadIO m => Bool -> m Bool
>  recompile force = io $ do
> -    dir <- getXMonadDir
> -    let binn = "xmonad-"++arch++"-"++os
> -        bin  = dir </> binn
> -        base = dir </> "xmonad"
> -        err  = base ++ ".errors"
> -        src  = base ++ ".hs"
> -        lib  = dir </> "lib"
> +    srcDir   <- getXMonadSourceDir
> +    buildDir <- getXMonadBuildDir
> +    binPath  <- getXMonadBinaryPath
> +    let err  = buildDir </> "xmonad" <.> "errors"
> +        src  = srcDir </> "xmonad" <.> "hs"
> +        lib  = srcDir </> "lib"
>     libTs <- mapM getModTime . Prelude.filter isSource =<< allFiles lib
> hunk ./XMonad/Core.hs 463
> -    srcT <- getModTime src
> -    binT <- getModTime bin
> +    srcT  <- getModTime src
> +    binT  <- getModTime binPath
>     if force || any (binT <) (srcT : libTs)
>       then do
>         -- temporarily disable SIGCHLD ignoring:
> hunk ./XMonad/Core.hs 469
>         uninstallSignalHandlers
> +        let ghcOpts = ["--make", "xmonad.hs", "-i", "-ilib", "-fforce-recomp", "-v0", "-outputdir", buildDir, "-o", binPath]
>         status <- bracket (openFile err WriteMode) hClose $ \h ->
> hunk ./XMonad/Core.hs 471
> -            waitForProcess =<< runProcess "ghc" ["--make", "xmonad.hs", "-i", "-ilib", "-fforce-recomp", "-v0", "-o",binn] (Just dir)
> +            waitForProcess =<< runProcess "ghc" ghcOpts (Just srcDir)
>                                     Nothing Nothing Nothing (Just h)
>
>         -- re-enable SIGCHLD:
> }
> [Add getXMonadDir for backward compatibility
> daniel.trstenjak at gmail.com**20120626182640
>  Ignore-this: 9d83affafd1d8a19285292edca7ccbef
> ] {
> hunk ./XMonad/Core.hs 28
>     StateExtension(..), ExtensionClass(..),
>     runX, catchX, userCode, userCodeDef, io, catchIO, installSignalHandlers, uninstallSignalHandlers,
>     withDisplay, withWindowSet, isRoot, runOnWorkspaces,
> -    getAtom, spawn, spawnPID, xfork, getXMonadBinaryPath, getXMonadSourceDir, getXMonadBuildDir,
> +    getAtom, spawn, spawnPID, xfork, getXMonadBinaryPath, getXMonadSourceDir, getXMonadBuildDir, getXMonadDir,
>     recompile, trace, whenJust, whenX, atom_WM_STATE, atom_WM_PROTOCOLS, atom_WM_DELETE_WINDOW, ManageHook, Query(..), runQuery
>   ) where
>
> hunk ./XMonad/Core.hs 419
>              $ current ws : visible ws
>     modify $ \s -> s { windowset = ws { current = c, visible = v, hidden = h } }
>
> +getXMonadDir = getXMonadSourceDir
> +
>  -- | Return the path to @~\/.xmonad at .
>  getXMonadSourceDir :: MonadIO m => m String
>  getXMonadSourceDir = io $ getAppUserDataDirectory "xmonad"
> }
>
>
> _______________________________________________
> xmonad mailing list
> xmonad at haskell.org
> http://www.haskell.org/mailman/listinfo/xmonad
>



More information about the xmonad mailing list