{-# LANGUAGE DeriveTraversable #-}
{-# LANGUAGE ExistentialQuantification #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE NamedFieldPuns #-}
{-# LANGUAGE ScopedTypeVariables #-}

-----------------------------------------------------------------------------
-- |
-- Module      :  XMonad.Core
-- Copyright   :  (c) Spencer Janssen 2007
-- License     :  BSD3-style (see LICENSE)
--
-- Maintainer  :  spencerjanssen@gmail.com
-- Stability   :  unstable
-- Portability :  not portable, uses cunning newtype deriving
--
-- The 'X' monad, a state monad transformer over 'IO', for the window
-- manager state, and support routines.
--
-----------------------------------------------------------------------------

module XMonad.Core (
    X, WindowSet, WindowSpace, WorkspaceId,
    ScreenId(..), ScreenDetail(..), XState(..),
    XConf(..), XConfig(..), LayoutClass(..),
    Layout(..), readsLayout, Typeable, Message,
    SomeMessage(..), fromMessage, LayoutMessages(..),
    StateExtension(..), ExtensionClass(..), ConfExtension(..),
    runX, catchX, userCode, userCodeDef, io, catchIO, installSignalHandlers, uninstallSignalHandlers,
    withDisplay, withWindowSet, isRoot, runOnWorkspaces,
    getAtom, spawn, spawnPID, xfork, xmessage, recompile, trace, whenJust, whenX,
    getXMonadDir, getXMonadCacheDir, getXMonadDataDir, stateFileName, binFileName,
    atom_WM_STATE, atom_WM_PROTOCOLS, atom_WM_DELETE_WINDOW, atom_WM_TAKE_FOCUS, withWindowAttributes,
    ManageHook, Query(..), runQuery, Directories'(..), Directories, getDirectories,
  ) where

import XMonad.StackSet hiding (modify)

import Prelude
import Control.Exception (fromException, try, bracket_, throw, finally, SomeException(..))
import qualified Control.Exception as E
import Control.Applicative ((<|>), empty)
import Control.Monad.Fail
import Control.Monad.State
import Control.Monad.Reader
import Control.Monad (void)
import Data.Semigroup
import Data.Traversable (for)
import Data.Time.Clock (UTCTime)
import Data.Default.Class
import System.Environment (lookupEnv)
import System.FilePath
import System.IO
import System.Info
import System.Posix.Env (getEnv)
import System.Posix.Process (executeFile, forkProcess, getAnyProcessStatus, createSession)
import System.Posix.Signals
import System.Posix.IO
import System.Posix.Types (ProcessID)
import System.Process
import System.Directory
import System.Exit
import Graphics.X11.Xlib
import Graphics.X11.Xlib.Extras (getWindowAttributes, WindowAttributes, Event)
import Data.Typeable
import Data.List (isInfixOf, (\\))
import Data.Maybe (isJust,fromMaybe)

import qualified Data.Map as M
import qualified Data.Set as S

-- | XState, the (mutable) window manager state.
data XState = XState
    { XState -> WindowSet
windowset        :: !WindowSet                     -- ^ workspace list
    , XState -> Set Window
mapped           :: !(S.Set Window)                -- ^ the Set of mapped windows
    , XState -> Map Window Int
waitingUnmap     :: !(M.Map Window Int)            -- ^ the number of expected UnmapEvents
    , XState -> Maybe (Position -> Position -> X (), X ())
dragging         :: !(Maybe (Position -> Position -> X (), X ()))
    , XState -> KeyMask
numberlockMask   :: !KeyMask                       -- ^ The numlock modifier
    , XState -> Map String (Either String StateExtension)
extensibleState  :: !(M.Map String (Either String StateExtension))
    -- ^ stores custom state information.
    --
    -- The module "XMonad.Util.ExtensibleState" in xmonad-contrib
    -- provides additional information and a simple interface for using this.
    }

-- | XConf, the (read-only) window manager configuration.
data XConf = XConf
    { XConf -> Display
display       :: Display        -- ^ the X11 display
    , XConf -> XConfig Layout
config        :: !(XConfig Layout)       -- ^ initial user configuration
    , XConf -> Window
theRoot       :: !Window        -- ^ the root window
    , XConf -> Window
normalBorder  :: !Pixel         -- ^ border color of unfocused windows
    , XConf -> Window
focusedBorder :: !Pixel         -- ^ border color of the focused window
    , XConf -> Map (KeyMask, Window) (X ())
keyActions    :: !(M.Map (KeyMask, KeySym) (X ()))
                                      -- ^ a mapping of key presses to actions
    , XConf -> Map (KeyMask, Button) (Window -> X ())
buttonActions :: !(M.Map (KeyMask, Button) (Window -> X ()))
                                      -- ^ a mapping of button presses to actions
    , XConf -> Bool
mouseFocused :: !Bool           -- ^ was refocus caused by mouse action?
    , XConf -> Maybe (Position, Position)
mousePosition :: !(Maybe (Position, Position))
                                      -- ^ position of the mouse according to
                                      -- the event currently being processed
    , XConf -> Maybe Event
currentEvent :: !(Maybe Event)  -- ^ event currently being processed
    , XConf -> Directories
directories  :: !Directories    -- ^ directories to use
    }

-- todo, better name
data XConfig l = XConfig
    { forall (l :: * -> *). XConfig l -> String
normalBorderColor  :: !String              -- ^ Non focused windows border color. Default: \"#dddddd\"
    , forall (l :: * -> *). XConfig l -> String
focusedBorderColor :: !String              -- ^ Focused windows border color. Default: \"#ff0000\"
    , forall (l :: * -> *). XConfig l -> String
terminal           :: !String              -- ^ The preferred terminal application. Default: \"xterm\"
    , forall (l :: * -> *). XConfig l -> l Window
layoutHook         :: !(l Window)          -- ^ The available layouts
    , forall (l :: * -> *). XConfig l -> ManageHook
manageHook         :: !ManageHook          -- ^ The action to run when a new window is opened
    , forall (l :: * -> *). XConfig l -> Event -> X All
handleEventHook    :: !(Event -> X All)    -- ^ Handle an X event, returns (All True) if the default handler
                                                 -- should also be run afterwards. mappend should be used for combining
                                                 -- event hooks in most cases.
    , forall (l :: * -> *). XConfig l -> [String]
workspaces         :: ![String]            -- ^ The list of workspaces' names
    , forall (l :: * -> *). XConfig l -> KeyMask
modMask            :: !KeyMask             -- ^ the mod modifier
    , forall (l :: * -> *).
XConfig l -> XConfig Layout -> Map (KeyMask, Window) (X ())
keys               :: !(XConfig Layout -> M.Map (ButtonMask,KeySym) (X ()))
                                                 -- ^ The key binding: a map from key presses and actions
    , forall (l :: * -> *).
XConfig l
-> XConfig Layout -> Map (KeyMask, Button) (Window -> X ())
mouseBindings      :: !(XConfig Layout -> M.Map (ButtonMask, Button) (Window -> X ()))
                                                 -- ^ The mouse bindings
    , forall (l :: * -> *). XConfig l -> Button
borderWidth        :: !Dimension           -- ^ The border width
    , forall (l :: * -> *). XConfig l -> X ()
logHook            :: !(X ())              -- ^ The action to perform when the windows set is changed
    , forall (l :: * -> *). XConfig l -> X ()
startupHook        :: !(X ())              -- ^ The action to perform on startup
    , forall (l :: * -> *). XConfig l -> Bool
focusFollowsMouse  :: !Bool                -- ^ Whether window entry events can change focus
    , forall (l :: * -> *). XConfig l -> Bool
clickJustFocuses   :: !Bool                -- ^ False to make a click which changes focus to be additionally passed to the window
    , forall (l :: * -> *). XConfig l -> Window
clientMask         :: !EventMask           -- ^ The client events that xmonad is interested in
    , forall (l :: * -> *). XConfig l -> Window
rootMask           :: !EventMask           -- ^ The root events that xmonad is interested in
    , forall (l :: * -> *).
XConfig l -> [String] -> XConfig Layout -> IO (XConfig Layout)
handleExtraArgs    :: !([String] -> XConfig Layout -> IO (XConfig Layout))
                                                 -- ^ Modify the configuration, complain about extra arguments etc. with arguments that are not handled by default
    , forall (l :: * -> *). XConfig l -> Map TypeRep ConfExtension
extensibleConf     :: !(M.Map TypeRep ConfExtension)
                                                 -- ^ Stores custom config information.
                                                 --
                                                 -- The module "XMonad.Util.ExtensibleConf" in xmonad-contrib
                                                 -- provides additional information and a simple interface for using this.
    }


type WindowSet   = StackSet  WorkspaceId (Layout Window) Window ScreenId ScreenDetail
type WindowSpace = Workspace WorkspaceId (Layout Window) Window

-- | Virtual workspace indices
type WorkspaceId = String

-- | Physical screen indices
newtype ScreenId    = S Int deriving (ScreenId -> ScreenId -> Bool
(ScreenId -> ScreenId -> Bool)
-> (ScreenId -> ScreenId -> Bool) -> Eq ScreenId
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ScreenId -> ScreenId -> Bool
$c/= :: ScreenId -> ScreenId -> Bool
== :: ScreenId -> ScreenId -> Bool
$c== :: ScreenId -> ScreenId -> Bool
Eq,Eq ScreenId
Eq ScreenId
-> (ScreenId -> ScreenId -> Ordering)
-> (ScreenId -> ScreenId -> Bool)
-> (ScreenId -> ScreenId -> Bool)
-> (ScreenId -> ScreenId -> Bool)
-> (ScreenId -> ScreenId -> Bool)
-> (ScreenId -> ScreenId -> ScreenId)
-> (ScreenId -> ScreenId -> ScreenId)
-> Ord ScreenId
ScreenId -> ScreenId -> Bool
ScreenId -> ScreenId -> Ordering
ScreenId -> ScreenId -> ScreenId
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: ScreenId -> ScreenId -> ScreenId
$cmin :: ScreenId -> ScreenId -> ScreenId
max :: ScreenId -> ScreenId -> ScreenId
$cmax :: ScreenId -> ScreenId -> ScreenId
>= :: ScreenId -> ScreenId -> Bool
$c>= :: ScreenId -> ScreenId -> Bool
> :: ScreenId -> ScreenId -> Bool
$c> :: ScreenId -> ScreenId -> Bool
<= :: ScreenId -> ScreenId -> Bool
$c<= :: ScreenId -> ScreenId -> Bool
< :: ScreenId -> ScreenId -> Bool
$c< :: ScreenId -> ScreenId -> Bool
compare :: ScreenId -> ScreenId -> Ordering
$ccompare :: ScreenId -> ScreenId -> Ordering
Ord,Int -> ScreenId -> ShowS
[ScreenId] -> ShowS
ScreenId -> String
(Int -> ScreenId -> ShowS)
-> (ScreenId -> String) -> ([ScreenId] -> ShowS) -> Show ScreenId
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ScreenId] -> ShowS
$cshowList :: [ScreenId] -> ShowS
show :: ScreenId -> String
$cshow :: ScreenId -> String
showsPrec :: Int -> ScreenId -> ShowS
$cshowsPrec :: Int -> ScreenId -> ShowS
Show,ReadPrec [ScreenId]
ReadPrec ScreenId
Int -> ReadS ScreenId
ReadS [ScreenId]
(Int -> ReadS ScreenId)
-> ReadS [ScreenId]
-> ReadPrec ScreenId
-> ReadPrec [ScreenId]
-> Read ScreenId
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ScreenId]
$creadListPrec :: ReadPrec [ScreenId]
readPrec :: ReadPrec ScreenId
$creadPrec :: ReadPrec ScreenId
readList :: ReadS [ScreenId]
$creadList :: ReadS [ScreenId]
readsPrec :: Int -> ReadS ScreenId
$creadsPrec :: Int -> ReadS ScreenId
Read,Int -> ScreenId
ScreenId -> Int
ScreenId -> [ScreenId]
ScreenId -> ScreenId
ScreenId -> ScreenId -> [ScreenId]
ScreenId -> ScreenId -> ScreenId -> [ScreenId]
(ScreenId -> ScreenId)
-> (ScreenId -> ScreenId)
-> (Int -> ScreenId)
-> (ScreenId -> Int)
-> (ScreenId -> [ScreenId])
-> (ScreenId -> ScreenId -> [ScreenId])
-> (ScreenId -> ScreenId -> [ScreenId])
-> (ScreenId -> ScreenId -> ScreenId -> [ScreenId])
-> Enum ScreenId
forall a.
(a -> a)
-> (a -> a)
-> (Int -> a)
-> (a -> Int)
-> (a -> [a])
-> (a -> a -> [a])
-> (a -> a -> [a])
-> (a -> a -> a -> [a])
-> Enum a
enumFromThenTo :: ScreenId -> ScreenId -> ScreenId -> [ScreenId]
$cenumFromThenTo :: ScreenId -> ScreenId -> ScreenId -> [ScreenId]
enumFromTo :: ScreenId -> ScreenId -> [ScreenId]
$cenumFromTo :: ScreenId -> ScreenId -> [ScreenId]
enumFromThen :: ScreenId -> ScreenId -> [ScreenId]
$cenumFromThen :: ScreenId -> ScreenId -> [ScreenId]
enumFrom :: ScreenId -> [ScreenId]
$cenumFrom :: ScreenId -> [ScreenId]
fromEnum :: ScreenId -> Int
$cfromEnum :: ScreenId -> Int
toEnum :: Int -> ScreenId
$ctoEnum :: Int -> ScreenId
pred :: ScreenId -> ScreenId
$cpred :: ScreenId -> ScreenId
succ :: ScreenId -> ScreenId
$csucc :: ScreenId -> ScreenId
Enum,Integer -> ScreenId
ScreenId -> ScreenId
ScreenId -> ScreenId -> ScreenId
(ScreenId -> ScreenId -> ScreenId)
-> (ScreenId -> ScreenId -> ScreenId)
-> (ScreenId -> ScreenId -> ScreenId)
-> (ScreenId -> ScreenId)
-> (ScreenId -> ScreenId)
-> (ScreenId -> ScreenId)
-> (Integer -> ScreenId)
-> Num ScreenId
forall a.
(a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a)
-> (a -> a)
-> (a -> a)
-> (Integer -> a)
-> Num a
fromInteger :: Integer -> ScreenId
$cfromInteger :: Integer -> ScreenId
signum :: ScreenId -> ScreenId
$csignum :: ScreenId -> ScreenId
abs :: ScreenId -> ScreenId
$cabs :: ScreenId -> ScreenId
negate :: ScreenId -> ScreenId
$cnegate :: ScreenId -> ScreenId
* :: ScreenId -> ScreenId -> ScreenId
$c* :: ScreenId -> ScreenId -> ScreenId
- :: ScreenId -> ScreenId -> ScreenId
$c- :: ScreenId -> ScreenId -> ScreenId
+ :: ScreenId -> ScreenId -> ScreenId
$c+ :: ScreenId -> ScreenId -> ScreenId
Num,Enum ScreenId
Real ScreenId
Real ScreenId
-> Enum ScreenId
-> (ScreenId -> ScreenId -> ScreenId)
-> (ScreenId -> ScreenId -> ScreenId)
-> (ScreenId -> ScreenId -> ScreenId)
-> (ScreenId -> ScreenId -> ScreenId)
-> (ScreenId -> ScreenId -> (ScreenId, ScreenId))
-> (ScreenId -> ScreenId -> (ScreenId, ScreenId))
-> (ScreenId -> Integer)
-> Integral ScreenId
ScreenId -> Integer
ScreenId -> ScreenId -> (ScreenId, ScreenId)
ScreenId -> ScreenId -> ScreenId
forall a.
Real a
-> Enum a
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> (a, a))
-> (a -> a -> (a, a))
-> (a -> Integer)
-> Integral a
toInteger :: ScreenId -> Integer
$ctoInteger :: ScreenId -> Integer
divMod :: ScreenId -> ScreenId -> (ScreenId, ScreenId)
$cdivMod :: ScreenId -> ScreenId -> (ScreenId, ScreenId)
quotRem :: ScreenId -> ScreenId -> (ScreenId, ScreenId)
$cquotRem :: ScreenId -> ScreenId -> (ScreenId, ScreenId)
mod :: ScreenId -> ScreenId -> ScreenId
$cmod :: ScreenId -> ScreenId -> ScreenId
div :: ScreenId -> ScreenId -> ScreenId
$cdiv :: ScreenId -> ScreenId -> ScreenId
rem :: ScreenId -> ScreenId -> ScreenId
$crem :: ScreenId -> ScreenId -> ScreenId
quot :: ScreenId -> ScreenId -> ScreenId
$cquot :: ScreenId -> ScreenId -> ScreenId
Integral,Num ScreenId
Ord ScreenId
Num ScreenId
-> Ord ScreenId -> (ScreenId -> Rational) -> Real ScreenId
ScreenId -> Rational
forall a. Num a -> Ord a -> (a -> Rational) -> Real a
toRational :: ScreenId -> Rational
$ctoRational :: ScreenId -> Rational
Real)

-- | The 'Rectangle' with screen dimensions
newtype ScreenDetail = SD { ScreenDetail -> Rectangle
screenRect :: Rectangle }
    deriving (ScreenDetail -> ScreenDetail -> Bool
(ScreenDetail -> ScreenDetail -> Bool)
-> (ScreenDetail -> ScreenDetail -> Bool) -> Eq ScreenDetail
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ScreenDetail -> ScreenDetail -> Bool
$c/= :: ScreenDetail -> ScreenDetail -> Bool
== :: ScreenDetail -> ScreenDetail -> Bool
$c== :: ScreenDetail -> ScreenDetail -> Bool
Eq,Int -> ScreenDetail -> ShowS
[ScreenDetail] -> ShowS
ScreenDetail -> String
(Int -> ScreenDetail -> ShowS)
-> (ScreenDetail -> String)
-> ([ScreenDetail] -> ShowS)
-> Show ScreenDetail
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ScreenDetail] -> ShowS
$cshowList :: [ScreenDetail] -> ShowS
show :: ScreenDetail -> String
$cshow :: ScreenDetail -> String
showsPrec :: Int -> ScreenDetail -> ShowS
$cshowsPrec :: Int -> ScreenDetail -> ShowS
Show, ReadPrec [ScreenDetail]
ReadPrec ScreenDetail
Int -> ReadS ScreenDetail
ReadS [ScreenDetail]
(Int -> ReadS ScreenDetail)
-> ReadS [ScreenDetail]
-> ReadPrec ScreenDetail
-> ReadPrec [ScreenDetail]
-> Read ScreenDetail
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ScreenDetail]
$creadListPrec :: ReadPrec [ScreenDetail]
readPrec :: ReadPrec ScreenDetail
$creadPrec :: ReadPrec ScreenDetail
readList :: ReadS [ScreenDetail]
$creadList :: ReadS [ScreenDetail]
readsPrec :: Int -> ReadS ScreenDetail
$creadsPrec :: Int -> ReadS ScreenDetail
Read)

------------------------------------------------------------------------

-- | The X monad, 'ReaderT' and 'StateT' transformers over 'IO'
-- encapsulating the window manager configuration and state,
-- respectively.
--
-- Dynamic components may be retrieved with 'get', static components
-- with 'ask'. With newtype deriving we get readers and state monads
-- instantiated on 'XConf' and 'XState' automatically.
--
newtype X a = X (ReaderT XConf (StateT XState IO) a)
    deriving ((forall a b. (a -> b) -> X a -> X b)
-> (forall a b. a -> X b -> X a) -> Functor X
forall a b. a -> X b -> X a
forall a b. (a -> b) -> X a -> X b
forall (f :: * -> *).
(forall a b. (a -> b) -> f a -> f b)
-> (forall a b. a -> f b -> f a) -> Functor f
<$ :: forall a b. a -> X b -> X a
$c<$ :: forall a b. a -> X b -> X a
fmap :: forall a b. (a -> b) -> X a -> X b
$cfmap :: forall a b. (a -> b) -> X a -> X b
Functor, Functor X
Functor X
-> (forall a. a -> X a)
-> (forall a b. X (a -> b) -> X a -> X b)
-> (forall a b c. (a -> b -> c) -> X a -> X b -> X c)
-> (forall a b. X a -> X b -> X b)
-> (forall a b. X a -> X b -> X a)
-> Applicative X
forall a. a -> X a
forall a b. X a -> X b -> X a
forall a b. X a -> X b -> X b
forall a b. X (a -> b) -> X a -> X b
forall a b c. (a -> b -> c) -> X a -> X b -> X c
forall (f :: * -> *).
Functor f
-> (forall a. a -> f a)
-> (forall a b. f (a -> b) -> f a -> f b)
-> (forall a b c. (a -> b -> c) -> f a -> f b -> f c)
-> (forall a b. f a -> f b -> f b)
-> (forall a b. f a -> f b -> f a)
-> Applicative f
<* :: forall a b. X a -> X b -> X a
$c<* :: forall a b. X a -> X b -> X a
*> :: forall a b. X a -> X b -> X b
$c*> :: forall a b. X a -> X b -> X b
liftA2 :: forall a b c. (a -> b -> c) -> X a -> X b -> X c
$cliftA2 :: forall a b c. (a -> b -> c) -> X a -> X b -> X c
<*> :: forall a b. X (a -> b) -> X a -> X b
$c<*> :: forall a b. X (a -> b) -> X a -> X b
pure :: forall a. a -> X a
$cpure :: forall a. a -> X a
Applicative, Applicative X
Applicative X
-> (forall a b. X a -> (a -> X b) -> X b)
-> (forall a b. X a -> X b -> X b)
-> (forall a. a -> X a)
-> Monad X
forall a. a -> X a
forall a b. X a -> X b -> X b
forall a b. X a -> (a -> X b) -> X b
forall (m :: * -> *).
Applicative m
-> (forall a b. m a -> (a -> m b) -> m b)
-> (forall a b. m a -> m b -> m b)
-> (forall a. a -> m a)
-> Monad m
return :: forall a. a -> X a
$creturn :: forall a. a -> X a
>> :: forall a b. X a -> X b -> X b
$c>> :: forall a b. X a -> X b -> X b
>>= :: forall a b. X a -> (a -> X b) -> X b
$c>>= :: forall a b. X a -> (a -> X b) -> X b
Monad, Monad X
Monad X -> (forall a. String -> X a) -> MonadFail X
forall a. String -> X a
forall (m :: * -> *).
Monad m -> (forall a. String -> m a) -> MonadFail m
fail :: forall a. String -> X a
$cfail :: forall a. String -> X a
MonadFail, Monad X
Monad X -> (forall a. IO a -> X a) -> MonadIO X
forall a. IO a -> X a
forall (m :: * -> *).
Monad m -> (forall a. IO a -> m a) -> MonadIO m
liftIO :: forall a. IO a -> X a
$cliftIO :: forall a. IO a -> X a
MonadIO, MonadState XState, MonadReader XConf)

instance Semigroup a => Semigroup (X a) where
    <> :: X a -> X a -> X a
(<>) = (a -> a -> a) -> X a -> X a -> X a
forall (m :: * -> *) a1 a2 r.
Monad m =>
(a1 -> a2 -> r) -> m a1 -> m a2 -> m r
liftM2 a -> a -> a
forall a. Semigroup a => a -> a -> a
(<>)

instance (Monoid a) => Monoid (X a) where
    mempty :: X a
mempty = a -> X a
forall (f :: * -> *) a. Applicative f => a -> f a
pure a
forall a. Monoid a => a
mempty

instance Default a => Default (X a) where
    def :: X a
def = a -> X a
forall (m :: * -> *) a. Monad m => a -> m a
return a
forall a. Default a => a
def

type ManageHook = Query (Endo WindowSet)
newtype Query a = Query (ReaderT Window X a)
    deriving ((forall a b. (a -> b) -> Query a -> Query b)
-> (forall a b. a -> Query b -> Query a) -> Functor Query
forall a b. a -> Query b -> Query a
forall a b. (a -> b) -> Query a -> Query b
forall (f :: * -> *).
(forall a b. (a -> b) -> f a -> f b)
-> (forall a b. a -> f b -> f a) -> Functor f
<$ :: forall a b. a -> Query b -> Query a
$c<$ :: forall a b. a -> Query b -> Query a
fmap :: forall a b. (a -> b) -> Query a -> Query b
$cfmap :: forall a b. (a -> b) -> Query a -> Query b
Functor, Functor Query
Functor Query
-> (forall a. a -> Query a)
-> (forall a b. Query (a -> b) -> Query a -> Query b)
-> (forall a b c. (a -> b -> c) -> Query a -> Query b -> Query c)
-> (forall a b. Query a -> Query b -> Query b)
-> (forall a b. Query a -> Query b -> Query a)
-> Applicative Query
forall a. a -> Query a
forall a b. Query a -> Query b -> Query a
forall a b. Query a -> Query b -> Query b
forall a b. Query (a -> b) -> Query a -> Query b
forall a b c. (a -> b -> c) -> Query a -> Query b -> Query c
forall (f :: * -> *).
Functor f
-> (forall a. a -> f a)
-> (forall a b. f (a -> b) -> f a -> f b)
-> (forall a b c. (a -> b -> c) -> f a -> f b -> f c)
-> (forall a b. f a -> f b -> f b)
-> (forall a b. f a -> f b -> f a)
-> Applicative f
<* :: forall a b. Query a -> Query b -> Query a
$c<* :: forall a b. Query a -> Query b -> Query a
*> :: forall a b. Query a -> Query b -> Query b
$c*> :: forall a b. Query a -> Query b -> Query b
liftA2 :: forall a b c. (a -> b -> c) -> Query a -> Query b -> Query c
$cliftA2 :: forall a b c. (a -> b -> c) -> Query a -> Query b -> Query c
<*> :: forall a b. Query (a -> b) -> Query a -> Query b
$c<*> :: forall a b. Query (a -> b) -> Query a -> Query b
pure :: forall a. a -> Query a
$cpure :: forall a. a -> Query a
Applicative, Applicative Query
Applicative Query
-> (forall a b. Query a -> (a -> Query b) -> Query b)
-> (forall a b. Query a -> Query b -> Query b)
-> (forall a. a -> Query a)
-> Monad Query
forall a. a -> Query a
forall a b. Query a -> Query b -> Query b
forall a b. Query a -> (a -> Query b) -> Query b
forall (m :: * -> *).
Applicative m
-> (forall a b. m a -> (a -> m b) -> m b)
-> (forall a b. m a -> m b -> m b)
-> (forall a. a -> m a)
-> Monad m
return :: forall a. a -> Query a
$creturn :: forall a. a -> Query a
>> :: forall a b. Query a -> Query b -> Query b
$c>> :: forall a b. Query a -> Query b -> Query b
>>= :: forall a b. Query a -> (a -> Query b) -> Query b
$c>>= :: forall a b. Query a -> (a -> Query b) -> Query b
Monad, MonadReader Window, Monad Query
Monad Query -> (forall a. IO a -> Query a) -> MonadIO Query
forall a. IO a -> Query a
forall (m :: * -> *).
Monad m -> (forall a. IO a -> m a) -> MonadIO m
liftIO :: forall a. IO a -> Query a
$cliftIO :: forall a. IO a -> Query a
MonadIO)

runQuery :: Query a -> Window -> X a
runQuery :: forall a. Query a -> Window -> X a
runQuery (Query ReaderT Window X a
m) = ReaderT Window X a -> Window -> X a
forall r (m :: * -> *) a. ReaderT r m a -> r -> m a
runReaderT ReaderT Window X a
m

instance Semigroup a => Semigroup (Query a) where
    <> :: Query a -> Query a -> Query a
(<>) = (a -> a -> a) -> Query a -> Query a -> Query a
forall (m :: * -> *) a1 a2 r.
Monad m =>
(a1 -> a2 -> r) -> m a1 -> m a2 -> m r
liftM2 a -> a -> a
forall a. Semigroup a => a -> a -> a
(<>)

instance Monoid a => Monoid (Query a) where
    mempty :: Query a
mempty = a -> Query a
forall (f :: * -> *) a. Applicative f => a -> f a
pure a
forall a. Monoid a => a
mempty

instance Default a => Default (Query a) where
    def :: Query a
def = a -> Query a
forall (m :: * -> *) a. Monad m => a -> m a
return a
forall a. Default a => a
def

-- | Run the 'X' monad, given a chunk of 'X' monad code, and an initial state
-- Return the result, and final state
runX :: XConf -> XState -> X a -> IO (a, XState)
runX :: forall a. XConf -> XState -> X a -> IO (a, XState)
runX XConf
c XState
st (X ReaderT XConf (StateT XState IO) a
a) = StateT XState IO a -> XState -> IO (a, XState)
forall s (m :: * -> *) a. StateT s m a -> s -> m (a, s)
runStateT (ReaderT XConf (StateT XState IO) a -> XConf -> StateT XState IO a
forall r (m :: * -> *) a. ReaderT r m a -> r -> m a
runReaderT ReaderT XConf (StateT XState IO) a
a XConf
c) XState
st

-- | Run in the 'X' monad, and in case of exception, and catch it and log it
-- to stderr, and run the error case.
catchX :: X a -> X a -> X a
catchX :: forall a. X a -> X a -> X a
catchX X a
job X a
errcase = do
    XState
st <- X XState
forall s (m :: * -> *). MonadState s m => m s
get
    XConf
c <- X XConf
forall r (m :: * -> *). MonadReader r m => m r
ask
    (a
a, XState
s') <- IO (a, XState) -> X (a, XState)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
io (IO (a, XState) -> X (a, XState))
-> IO (a, XState) -> X (a, XState)
forall a b. (a -> b) -> a -> b
$ XConf -> XState -> X a -> IO (a, XState)
forall a. XConf -> XState -> X a -> IO (a, XState)
runX XConf
c XState
st X a
job IO (a, XState)
-> (SomeException -> IO (a, XState)) -> IO (a, XState)
forall e a. Exception e => IO a -> (e -> IO a) -> IO a
`E.catch` \SomeException
e -> case SomeException -> Maybe ExitCode
forall e. Exception e => SomeException -> Maybe e
fromException SomeException
e of
                        Just (ExitCode
_ :: ExitCode) -> SomeException -> IO (a, XState)
forall a e. Exception e => e -> a
throw SomeException
e
                        Maybe ExitCode
_ -> do Handle -> SomeException -> IO ()
forall a. Show a => Handle -> a -> IO ()
hPrint Handle
stderr SomeException
e; XConf -> XState -> X a -> IO (a, XState)
forall a. XConf -> XState -> X a -> IO (a, XState)
runX XConf
c XState
st X a
errcase
    XState -> X ()
forall s (m :: * -> *). MonadState s m => s -> m ()
put XState
s'
    a -> X a
forall (m :: * -> *) a. Monad m => a -> m a
return a
a

-- | Execute the argument, catching all exceptions.  Either this function or
-- 'catchX' should be used at all callsites of user customized code.
userCode :: X a -> X (Maybe a)
userCode :: forall a. X a -> X (Maybe a)
userCode X a
a = X (Maybe a) -> X (Maybe a) -> X (Maybe a)
forall a. X a -> X a -> X a
catchX (a -> Maybe a
forall a. a -> Maybe a
Just (a -> Maybe a) -> X a -> X (Maybe a)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> X a
a) (Maybe a -> X (Maybe a)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe a
forall a. Maybe a
Nothing)

-- | Same as userCode but with a default argument to return instead of using
-- Maybe, provided for convenience.
userCodeDef :: a -> X a -> X a
userCodeDef :: forall a. a -> X a -> X a
userCodeDef a
defValue X a
a = a -> Maybe a -> a
forall a. a -> Maybe a -> a
fromMaybe a
defValue (Maybe a -> a) -> X (Maybe a) -> X a
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> X a -> X (Maybe a)
forall a. X a -> X (Maybe a)
userCode X a
a

-- ---------------------------------------------------------------------
-- Convenient wrappers to state

-- | Run a monad action with the current display settings
withDisplay :: (Display -> X a) -> X a
withDisplay :: forall a. (Display -> X a) -> X a
withDisplay   Display -> X a
f = (XConf -> Display) -> X Display
forall r (m :: * -> *) a. MonadReader r m => (r -> a) -> m a
asks XConf -> Display
display X Display -> (Display -> X a) -> X a
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= Display -> X a
f

-- | Run a monadic action with the current stack set
withWindowSet :: (WindowSet -> X a) -> X a
withWindowSet :: forall a. (WindowSet -> X a) -> X a
withWindowSet WindowSet -> X a
f = (XState -> WindowSet) -> X WindowSet
forall s (m :: * -> *) a. MonadState s m => (s -> a) -> m a
gets XState -> WindowSet
windowset X WindowSet -> (WindowSet -> X a) -> X a
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= WindowSet -> X a
f

-- | Safely access window attributes.
withWindowAttributes :: Display -> Window -> (WindowAttributes -> X ()) -> X ()
withWindowAttributes :: Display -> Window -> (WindowAttributes -> X ()) -> X ()
withWindowAttributes Display
dpy Window
win WindowAttributes -> X ()
f = do
    Maybe WindowAttributes
wa <- X WindowAttributes -> X (Maybe WindowAttributes)
forall a. X a -> X (Maybe a)
userCode (IO WindowAttributes -> X WindowAttributes
forall (m :: * -> *) a. MonadIO m => IO a -> m a
io (IO WindowAttributes -> X WindowAttributes)
-> IO WindowAttributes -> X WindowAttributes
forall a b. (a -> b) -> a -> b
$ Display -> Window -> IO WindowAttributes
getWindowAttributes Display
dpy Window
win)
    X () -> X () -> X ()
forall a. X a -> X a -> X a
catchX (Maybe WindowAttributes -> (WindowAttributes -> X ()) -> X ()
forall (m :: * -> *) a. Monad m => Maybe a -> (a -> m ()) -> m ()
whenJust Maybe WindowAttributes
wa WindowAttributes -> X ()
f) (() -> X ()
forall (m :: * -> *) a. Monad m => a -> m a
return ())

-- | True if the given window is the root window
isRoot :: Window -> X Bool
isRoot :: Window -> X Bool
isRoot Window
w = (XConf -> Bool) -> X Bool
forall r (m :: * -> *) a. MonadReader r m => (r -> a) -> m a
asks ((XConf -> Bool) -> X Bool) -> (XConf -> Bool) -> X Bool
forall a b. (a -> b) -> a -> b
$ (Window
w Window -> Window -> Bool
forall a. Eq a => a -> a -> Bool
==) (Window -> Bool) -> (XConf -> Window) -> XConf -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. XConf -> Window
theRoot

-- | Wrapper for the common case of atom internment
getAtom :: String -> X Atom
getAtom :: String -> X Window
getAtom String
str = (Display -> X Window) -> X Window
forall a. (Display -> X a) -> X a
withDisplay ((Display -> X Window) -> X Window)
-> (Display -> X Window) -> X Window
forall a b. (a -> b) -> a -> b
$ \Display
dpy -> IO Window -> X Window
forall (m :: * -> *) a. MonadIO m => IO a -> m a
io (IO Window -> X Window) -> IO Window -> X Window
forall a b. (a -> b) -> a -> b
$ Display -> String -> Bool -> IO Window
internAtom Display
dpy String
str Bool
False

-- | Common non-predefined atoms
atom_WM_PROTOCOLS, atom_WM_DELETE_WINDOW, atom_WM_STATE, atom_WM_TAKE_FOCUS :: X Atom
atom_WM_PROTOCOLS :: X Window
atom_WM_PROTOCOLS       = String -> X Window
getAtom String
"WM_PROTOCOLS"
atom_WM_DELETE_WINDOW :: X Window
atom_WM_DELETE_WINDOW   = String -> X Window
getAtom String
"WM_DELETE_WINDOW"
atom_WM_STATE :: X Window
atom_WM_STATE           = String -> X Window
getAtom String
"WM_STATE"
atom_WM_TAKE_FOCUS :: X Window
atom_WM_TAKE_FOCUS      = String -> X Window
getAtom String
"WM_TAKE_FOCUS"

------------------------------------------------------------------------
-- LayoutClass handling. See particular instances in Operations.hs

-- | An existential type that can hold any object that is in 'Read'
--   and 'LayoutClass'.
data Layout a = forall l. (LayoutClass l a, Read (l a)) => Layout (l a)

-- | Using the 'Layout' as a witness, parse existentially wrapped windows
-- from a 'String'.
readsLayout :: Layout a -> String -> [(Layout a, String)]
readsLayout :: forall a. Layout a -> String -> [(Layout a, String)]
readsLayout (Layout l a
l) String
s = [(l a -> Layout a
forall a (l :: * -> *).
(LayoutClass l a, Read (l a)) =>
l a -> Layout a
Layout (l a -> l a -> l a
forall a. a -> a -> a
asTypeOf l a
x l a
l), String
rs) | (l a
x, String
rs) <- ReadS (l a)
forall a. Read a => ReadS a
reads String
s]

-- | Every layout must be an instance of 'LayoutClass', which defines
-- the basic layout operations along with a sensible default for each.
--
-- All of the methods have default implementations, so there is no
-- minimal complete definition.  They do, however, have a dependency
-- structure by default; this is something to be aware of should you
-- choose to implement one of these methods.  Here is how a minimal
-- complete definition would look like if we did not provide any default
-- implementations:
--
-- * 'runLayout' || (('doLayout' || 'pureLayout') && 'emptyLayout')
--
-- * 'handleMessage' || 'pureMessage'
--
-- * 'description'
--
-- Note that any code which /uses/ 'LayoutClass' methods should only
-- ever call 'runLayout', 'handleMessage', and 'description'!  In
-- other words, the only calls to 'doLayout', 'pureMessage', and other
-- such methods should be from the default implementations of
-- 'runLayout', 'handleMessage', and so on.  This ensures that the
-- proper methods will be used, regardless of the particular methods
-- that any 'LayoutClass' instance chooses to define.
class (Show (layout a), Typeable layout) => LayoutClass layout a where

    -- | By default, 'runLayout' calls 'doLayout' if there are any
    --   windows to be laid out, and 'emptyLayout' otherwise.  Most
    --   instances of 'LayoutClass' probably do not need to implement
    --   'runLayout'; it is only useful for layouts which wish to make
    --   use of more of the 'Workspace' information (for example,
    --   "XMonad.Layout.PerWorkspace").
    runLayout :: Workspace WorkspaceId (layout a) a
              -> Rectangle
              -> X ([(a, Rectangle)], Maybe (layout a))
    runLayout (Workspace String
_ layout a
l Maybe (Stack a)
ms) Rectangle
r = X ([(a, Rectangle)], Maybe (layout a))
-> (Stack a -> X ([(a, Rectangle)], Maybe (layout a)))
-> Maybe (Stack a)
-> X ([(a, Rectangle)], Maybe (layout a))
forall b a. b -> (a -> b) -> Maybe a -> b
maybe (layout a -> Rectangle -> X ([(a, Rectangle)], Maybe (layout a))
forall (layout :: * -> *) a.
LayoutClass layout a =>
layout a -> Rectangle -> X ([(a, Rectangle)], Maybe (layout a))
emptyLayout layout a
l Rectangle
r) (layout a
-> Rectangle -> Stack a -> X ([(a, Rectangle)], Maybe (layout a))
forall (layout :: * -> *) a.
LayoutClass layout a =>
layout a
-> Rectangle -> Stack a -> X ([(a, Rectangle)], Maybe (layout a))
doLayout layout a
l Rectangle
r) Maybe (Stack a)
ms

    -- | Given a 'Rectangle' in which to place the windows, and a 'Stack'
    -- of windows, return a list of windows and their corresponding
    -- Rectangles.  If an element is not given a Rectangle by
    -- 'doLayout', then it is not shown on screen.  The order of
    -- windows in this list should be the desired stacking order.
    --
    -- Also possibly return a modified layout (by returning @Just
    -- newLayout@), if this layout needs to be modified (e.g. if it
    -- keeps track of some sort of state).  Return @Nothing@ if the
    -- layout does not need to be modified.
    --
    -- Layouts which do not need access to the 'X' monad ('IO', window
    -- manager state, or configuration) and do not keep track of their
    -- own state should implement 'pureLayout' instead of 'doLayout'.
    doLayout    :: layout a -> Rectangle -> Stack a
                -> X ([(a, Rectangle)], Maybe (layout a))
    doLayout layout a
l Rectangle
r Stack a
s   = ([(a, Rectangle)], Maybe (layout a))
-> X ([(a, Rectangle)], Maybe (layout a))
forall (m :: * -> *) a. Monad m => a -> m a
return (layout a -> Rectangle -> Stack a -> [(a, Rectangle)]
forall (layout :: * -> *) a.
LayoutClass layout a =>
layout a -> Rectangle -> Stack a -> [(a, Rectangle)]
pureLayout layout a
l Rectangle
r Stack a
s, Maybe (layout a)
forall a. Maybe a
Nothing)

    -- | This is a pure version of 'doLayout', for cases where we
    -- don't need access to the 'X' monad to determine how to lay out
    -- the windows, and we don't need to modify the layout itself.
    pureLayout  :: layout a -> Rectangle -> Stack a -> [(a, Rectangle)]
    pureLayout layout a
_ Rectangle
r Stack a
s = [(Stack a -> a
forall a. Stack a -> a
focus Stack a
s, Rectangle
r)]

    -- | 'emptyLayout' is called when there are no windows.
    emptyLayout :: layout a -> Rectangle -> X ([(a, Rectangle)], Maybe (layout a))
    emptyLayout layout a
_ Rectangle
_ = ([(a, Rectangle)], Maybe (layout a))
-> X ([(a, Rectangle)], Maybe (layout a))
forall (m :: * -> *) a. Monad m => a -> m a
return ([], Maybe (layout a)
forall a. Maybe a
Nothing)

    -- | 'handleMessage' performs message handling.  If
    -- 'handleMessage' returns @Nothing@, then the layout did not
    -- respond to the message and the screen is not refreshed.
    -- Otherwise, 'handleMessage' returns an updated layout and the
    -- screen is refreshed.
    --
    -- Layouts which do not need access to the 'X' monad to decide how
    -- to handle messages should implement 'pureMessage' instead of
    -- 'handleMessage' (this restricts the risk of error, and makes
    -- testing much easier).
    handleMessage :: layout a -> SomeMessage -> X (Maybe (layout a))
    handleMessage layout a
l  = Maybe (layout a) -> X (Maybe (layout a))
forall (m :: * -> *) a. Monad m => a -> m a
return (Maybe (layout a) -> X (Maybe (layout a)))
-> (SomeMessage -> Maybe (layout a))
-> SomeMessage
-> X (Maybe (layout a))
forall b c a. (b -> c) -> (a -> b) -> a -> c
. layout a -> SomeMessage -> Maybe (layout a)
forall (layout :: * -> *) a.
LayoutClass layout a =>
layout a -> SomeMessage -> Maybe (layout a)
pureMessage layout a
l

    -- | Respond to a message by (possibly) changing our layout, but
    -- taking no other action.  If the layout changes, the screen will
    -- be refreshed.
    pureMessage :: layout a -> SomeMessage -> Maybe (layout a)
    pureMessage layout a
_ SomeMessage
_  = Maybe (layout a)
forall a. Maybe a
Nothing

    -- | This should be a human-readable string that is used when
    -- selecting layouts by name.  The default implementation is
    -- 'show', which is in some cases a poor default.
    description :: layout a -> String
    description      = layout a -> String
forall a. Show a => a -> String
show

instance LayoutClass Layout Window where
    runLayout :: Workspace String (Layout Window) Window
-> Rectangle -> X ([(Window, Rectangle)], Maybe (Layout Window))
runLayout (Workspace String
i (Layout l Window
l) Maybe (Stack Window)
ms) Rectangle
r = (Maybe (l Window) -> Maybe (Layout Window))
-> ([(Window, Rectangle)], Maybe (l Window))
-> ([(Window, Rectangle)], Maybe (Layout Window))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ((l Window -> Layout Window)
-> Maybe (l Window) -> Maybe (Layout Window)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap l Window -> Layout Window
forall a (l :: * -> *).
(LayoutClass l a, Read (l a)) =>
l a -> Layout a
Layout) (([(Window, Rectangle)], Maybe (l Window))
 -> ([(Window, Rectangle)], Maybe (Layout Window)))
-> X ([(Window, Rectangle)], Maybe (l Window))
-> X ([(Window, Rectangle)], Maybe (Layout Window))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
`fmap` Workspace String (l Window) Window
-> Rectangle -> X ([(Window, Rectangle)], Maybe (l Window))
forall (layout :: * -> *) a.
LayoutClass layout a =>
Workspace String (layout a) a
-> Rectangle -> X ([(a, Rectangle)], Maybe (layout a))
runLayout (String
-> l Window
-> Maybe (Stack Window)
-> Workspace String (l Window) Window
forall i l a. i -> l -> Maybe (Stack a) -> Workspace i l a
Workspace String
i l Window
l Maybe (Stack Window)
ms) Rectangle
r
    doLayout :: Layout Window
-> Rectangle
-> Stack Window
-> X ([(Window, Rectangle)], Maybe (Layout Window))
doLayout (Layout l Window
l) Rectangle
r Stack Window
s  = (Maybe (l Window) -> Maybe (Layout Window))
-> ([(Window, Rectangle)], Maybe (l Window))
-> ([(Window, Rectangle)], Maybe (Layout Window))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ((l Window -> Layout Window)
-> Maybe (l Window) -> Maybe (Layout Window)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap l Window -> Layout Window
forall a (l :: * -> *).
(LayoutClass l a, Read (l a)) =>
l a -> Layout a
Layout) (([(Window, Rectangle)], Maybe (l Window))
 -> ([(Window, Rectangle)], Maybe (Layout Window)))
-> X ([(Window, Rectangle)], Maybe (l Window))
-> X ([(Window, Rectangle)], Maybe (Layout Window))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
`fmap` l Window
-> Rectangle
-> Stack Window
-> X ([(Window, Rectangle)], Maybe (l Window))
forall (layout :: * -> *) a.
LayoutClass layout a =>
layout a
-> Rectangle -> Stack a -> X ([(a, Rectangle)], Maybe (layout a))
doLayout l Window
l Rectangle
r Stack Window
s
    emptyLayout :: Layout Window
-> Rectangle -> X ([(Window, Rectangle)], Maybe (Layout Window))
emptyLayout (Layout l Window
l) Rectangle
r = (Maybe (l Window) -> Maybe (Layout Window))
-> ([(Window, Rectangle)], Maybe (l Window))
-> ([(Window, Rectangle)], Maybe (Layout Window))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ((l Window -> Layout Window)
-> Maybe (l Window) -> Maybe (Layout Window)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap l Window -> Layout Window
forall a (l :: * -> *).
(LayoutClass l a, Read (l a)) =>
l a -> Layout a
Layout) (([(Window, Rectangle)], Maybe (l Window))
 -> ([(Window, Rectangle)], Maybe (Layout Window)))
-> X ([(Window, Rectangle)], Maybe (l Window))
-> X ([(Window, Rectangle)], Maybe (Layout Window))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
`fmap` l Window
-> Rectangle -> X ([(Window, Rectangle)], Maybe (l Window))
forall (layout :: * -> *) a.
LayoutClass layout a =>
layout a -> Rectangle -> X ([(a, Rectangle)], Maybe (layout a))
emptyLayout l Window
l Rectangle
r
    handleMessage :: Layout Window -> SomeMessage -> X (Maybe (Layout Window))
handleMessage (Layout l Window
l) = (Maybe (l Window) -> Maybe (Layout Window))
-> X (Maybe (l Window)) -> X (Maybe (Layout Window))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ((l Window -> Layout Window)
-> Maybe (l Window) -> Maybe (Layout Window)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap l Window -> Layout Window
forall a (l :: * -> *).
(LayoutClass l a, Read (l a)) =>
l a -> Layout a
Layout) (X (Maybe (l Window)) -> X (Maybe (Layout Window)))
-> (SomeMessage -> X (Maybe (l Window)))
-> SomeMessage
-> X (Maybe (Layout Window))
forall b c a. (b -> c) -> (a -> b) -> a -> c
. l Window -> SomeMessage -> X (Maybe (l Window))
forall (layout :: * -> *) a.
LayoutClass layout a =>
layout a -> SomeMessage -> X (Maybe (layout a))
handleMessage l Window
l
    description :: Layout Window -> String
description (Layout l Window
l)   = l Window -> String
forall (layout :: * -> *) a.
LayoutClass layout a =>
layout a -> String
description l Window
l

instance Show (Layout a) where show :: Layout a -> String
show (Layout l a
l) = l a -> String
forall a. Show a => a -> String
show l a
l

-- | Based on ideas in /An Extensible Dynamically-Typed Hierarchy of
-- Exceptions/, Simon Marlow, 2006. Use extensible messages to the
-- 'handleMessage' handler.
--
-- User-extensible messages must be a member of this class.
--
class Typeable a => Message a

-- |
-- A wrapped value of some type in the 'Message' class.
--
data SomeMessage = forall a. Message a => SomeMessage a

-- |
-- And now, unwrap a given, unknown 'Message' type, performing a (dynamic)
-- type check on the result.
--
fromMessage :: Message m => SomeMessage -> Maybe m
fromMessage :: forall m. Message m => SomeMessage -> Maybe m
fromMessage (SomeMessage a
m) = a -> Maybe m
forall a b. (Typeable a, Typeable b) => a -> Maybe b
cast a
m

-- X Events are valid Messages.
instance Message Event

-- | 'LayoutMessages' are core messages that all layouts (especially stateful
-- layouts) should consider handling.
data LayoutMessages = Hide              -- ^ sent when a layout becomes non-visible
                    | ReleaseResources  -- ^ sent when xmonad is exiting or restarting
    deriving LayoutMessages -> LayoutMessages -> Bool
(LayoutMessages -> LayoutMessages -> Bool)
-> (LayoutMessages -> LayoutMessages -> Bool) -> Eq LayoutMessages
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: LayoutMessages -> LayoutMessages -> Bool
$c/= :: LayoutMessages -> LayoutMessages -> Bool
== :: LayoutMessages -> LayoutMessages -> Bool
$c== :: LayoutMessages -> LayoutMessages -> Bool
Eq

instance Message LayoutMessages

-- ---------------------------------------------------------------------
-- Extensible state/config
--

-- | Every module must make the data it wants to store
-- an instance of this class.
--
-- Minimal complete definition: initialValue
class Typeable a => ExtensionClass a where
    {-# MINIMAL initialValue #-}
    -- | Defines an initial value for the state extension
    initialValue :: a
    -- | Specifies whether the state extension should be
    -- persistent. Setting this method to 'PersistentExtension'
    -- will make the stored data survive restarts, but
    -- requires a to be an instance of Read and Show.
    --
    -- It defaults to 'StateExtension', i.e. no persistence.
    extensionType :: a -> StateExtension
    extensionType = a -> StateExtension
forall a. ExtensionClass a => a -> StateExtension
StateExtension

-- | Existential type to store a state extension.
data StateExtension =
    forall a. ExtensionClass a => StateExtension a
    -- ^ Non-persistent state extension
  | forall a. (Read a, Show a, ExtensionClass a) => PersistentExtension a
    -- ^ Persistent extension

-- | Existential type to store a config extension.
data ConfExtension = forall a. Typeable a => ConfExtension a

-- ---------------------------------------------------------------------
-- | General utilities
--
-- Lift an 'IO' action into the 'X' monad
io :: MonadIO m => IO a -> m a
io :: forall (m :: * -> *) a. MonadIO m => IO a -> m a
io = IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO

-- | Lift an 'IO' action into the 'X' monad.  If the action results in an 'IO'
-- exception, log the exception to stderr and continue normal execution.
catchIO :: MonadIO m => IO () -> m ()
catchIO :: forall (m :: * -> *). MonadIO m => IO () -> m ()
catchIO IO ()
f = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
io (IO ()
f IO () -> (SomeException -> IO ()) -> IO ()
forall e a. Exception e => IO a -> (e -> IO a) -> IO a
`E.catch` \(SomeException e
e) -> Handle -> e -> IO ()
forall a. Show a => Handle -> a -> IO ()
hPrint Handle
stderr e
e IO () -> IO () -> IO ()
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Handle -> IO ()
hFlush Handle
stderr)

-- | spawn. Launch an external application. Specifically, it double-forks and
-- runs the 'String' you pass as a command to \/bin\/sh.
--
-- Note this function assumes your locale uses utf8.
spawn :: MonadIO m => String -> m ()
spawn :: forall (m :: * -> *). MonadIO m => String -> m ()
spawn String
x = m ProcessID -> m ()
forall (f :: * -> *) a. Functor f => f a -> f ()
void (m ProcessID -> m ()) -> m ProcessID -> m ()
forall a b. (a -> b) -> a -> b
$ String -> m ProcessID
forall (m :: * -> *). MonadIO m => String -> m ProcessID
spawnPID String
x

-- | Like 'spawn', but returns the 'ProcessID' of the launched application
spawnPID :: MonadIO m => String -> m ProcessID
spawnPID :: forall (m :: * -> *). MonadIO m => String -> m ProcessID
spawnPID String
x = IO () -> m ProcessID
forall (m :: * -> *). MonadIO m => IO () -> m ProcessID
xfork (IO () -> m ProcessID) -> IO () -> m ProcessID
forall a b. (a -> b) -> a -> b
$ String -> Bool -> [String] -> Maybe [(String, String)] -> IO ()
forall a.
String -> Bool -> [String] -> Maybe [(String, String)] -> IO a
executeFile String
"/bin/sh" Bool
False [String
"-c", String
x] Maybe [(String, String)]
forall a. Maybe a
Nothing

-- | A replacement for 'forkProcess' which resets default signal handlers.
xfork :: MonadIO m => IO () -> m ProcessID
xfork :: forall (m :: * -> *). MonadIO m => IO () -> m ProcessID
xfork IO ()
x = IO ProcessID -> m ProcessID
forall (m :: * -> *) a. MonadIO m => IO a -> m a
io (IO ProcessID -> m ProcessID)
-> (IO () -> IO ProcessID) -> IO () -> m ProcessID
forall b c a. (b -> c) -> (a -> b) -> a -> c
. IO () -> IO ProcessID
forkProcess (IO () -> IO ProcessID)
-> (IO () -> IO ()) -> IO () -> IO ProcessID
forall b c a. (b -> c) -> (a -> b) -> a -> c
. IO () -> IO () -> IO ()
forall a b. IO a -> IO b -> IO a
finally IO ()
nullStdin (IO () -> m ProcessID) -> IO () -> m ProcessID
forall a b. (a -> b) -> a -> b
$ do
                IO ()
forall (m :: * -> *). MonadIO m => m ()
uninstallSignalHandlers
                IO ProcessID
createSession
                IO ()
x
 where
    nullStdin :: IO ()
nullStdin = do
        Fd
fd <- String -> OpenMode -> Maybe FileMode -> OpenFileFlags -> IO Fd
openFd String
"/dev/null" OpenMode
ReadOnly Maybe FileMode
forall a. Maybe a
Nothing OpenFileFlags
defaultFileFlags
        Fd -> Fd -> IO Fd
dupTo Fd
fd Fd
stdInput
        Fd -> IO ()
closeFd Fd
fd

-- | Use @xmessage@ to show information to the user.
xmessage :: MonadIO m => String -> m ()
xmessage :: forall (m :: * -> *). MonadIO m => String -> m ()
xmessage String
msg = m ProcessID -> m ()
forall (f :: * -> *) a. Functor f => f a -> f ()
void (m ProcessID -> m ()) -> (IO () -> m ProcessID) -> IO () -> m ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. IO () -> m ProcessID
forall (m :: * -> *). MonadIO m => IO () -> m ProcessID
xfork (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    String
xmessageBin <- String -> Maybe String -> String
forall a. a -> Maybe a -> a
fromMaybe String
"xmessage" (Maybe String -> String) -> IO (Maybe String) -> IO String
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> IO (Maybe String) -> IO (Maybe String)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (String -> IO (Maybe String)
lookupEnv String
"XMONAD_XMESSAGE")
    String -> Bool -> [String] -> Maybe [(String, String)] -> IO ()
forall a.
String -> Bool -> [String] -> Maybe [(String, String)] -> IO a
executeFile String
xmessageBin Bool
True
        [ String
"-default", String
"okay"
        , String
"-xrm", String
"*international:true"
        , String
"-xrm", String
"*fontSet:-*-fixed-medium-r-normal-*-18-*-*-*-*-*-*-*,-*-fixed-*-*-*-*-18-*-*-*-*-*-*-*,-*-*-*-*-*-*-18-*-*-*-*-*-*-*"
        , String
msg
        ] Maybe [(String, String)]
forall a. Maybe a
Nothing

-- | This is basically a map function, running a function in the 'X' monad on
-- each workspace with the output of that function being the modified workspace.
runOnWorkspaces :: (WindowSpace -> X WindowSpace) -> X ()
runOnWorkspaces :: (Workspace String (Layout Window) Window
 -> X (Workspace String (Layout Window) Window))
-> X ()
runOnWorkspaces Workspace String (Layout Window) Window
-> X (Workspace String (Layout Window) Window)
job = do
    WindowSet
ws <- (XState -> WindowSet) -> X WindowSet
forall s (m :: * -> *) a. MonadState s m => (s -> a) -> m a
gets XState -> WindowSet
windowset
    [Workspace String (Layout Window) Window]
h <- (Workspace String (Layout Window) Window
 -> X (Workspace String (Layout Window) Window))
-> [Workspace String (Layout Window) Window]
-> X [Workspace String (Layout Window) Window]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM Workspace String (Layout Window) Window
-> X (Workspace String (Layout Window) Window)
job ([Workspace String (Layout Window) Window]
 -> X [Workspace String (Layout Window) Window])
-> [Workspace String (Layout Window) Window]
-> X [Workspace String (Layout Window) Window]
forall a b. (a -> b) -> a -> b
$ WindowSet -> [Workspace String (Layout Window) Window]
forall i l a sid sd. StackSet i l a sid sd -> [Workspace i l a]
hidden WindowSet
ws
    Screen String (Layout Window) Window ScreenId ScreenDetail
c:[Screen String (Layout Window) Window ScreenId ScreenDetail]
v <- (Screen String (Layout Window) Window ScreenId ScreenDetail
 -> X (Screen String (Layout Window) Window ScreenId ScreenDetail))
-> [Screen String (Layout Window) Window ScreenId ScreenDetail]
-> X [Screen String (Layout Window) Window ScreenId ScreenDetail]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM (\Screen String (Layout Window) Window ScreenId ScreenDetail
s -> (\Workspace String (Layout Window) Window
w -> Screen String (Layout Window) Window ScreenId ScreenDetail
s { workspace :: Workspace String (Layout Window) Window
workspace = Workspace String (Layout Window) Window
w}) (Workspace String (Layout Window) Window
 -> Screen String (Layout Window) Window ScreenId ScreenDetail)
-> X (Workspace String (Layout Window) Window)
-> X (Screen String (Layout Window) Window ScreenId ScreenDetail)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Workspace String (Layout Window) Window
-> X (Workspace String (Layout Window) Window)
job (Screen String (Layout Window) Window ScreenId ScreenDetail
-> Workspace String (Layout Window) Window
forall i l a sid sd. Screen i l a sid sd -> Workspace i l a
workspace Screen String (Layout Window) Window ScreenId ScreenDetail
s))
             ([Screen String (Layout Window) Window ScreenId ScreenDetail]
 -> X [Screen String (Layout Window) Window ScreenId ScreenDetail])
-> [Screen String (Layout Window) Window ScreenId ScreenDetail]
-> X [Screen String (Layout Window) Window ScreenId ScreenDetail]
forall a b. (a -> b) -> a -> b
$ WindowSet
-> Screen String (Layout Window) Window ScreenId ScreenDetail
forall i l a sid sd. StackSet i l a sid sd -> Screen i l a sid sd
current WindowSet
ws Screen String (Layout Window) Window ScreenId ScreenDetail
-> [Screen String (Layout Window) Window ScreenId ScreenDetail]
-> [Screen String (Layout Window) Window ScreenId ScreenDetail]
forall a. a -> [a] -> [a]
: WindowSet
-> [Screen String (Layout Window) Window ScreenId ScreenDetail]
forall i l a sid sd. StackSet i l a sid sd -> [Screen i l a sid sd]
visible WindowSet
ws
    (XState -> XState) -> X ()
forall s (m :: * -> *). MonadState s m => (s -> s) -> m ()
modify ((XState -> XState) -> X ()) -> (XState -> XState) -> X ()
forall a b. (a -> b) -> a -> b
$ \XState
s -> XState
s { windowset :: WindowSet
windowset = WindowSet
ws { current :: Screen String (Layout Window) Window ScreenId ScreenDetail
current = Screen String (Layout Window) Window ScreenId ScreenDetail
c, visible :: [Screen String (Layout Window) Window ScreenId ScreenDetail]
visible = [Screen String (Layout Window) Window ScreenId ScreenDetail]
v, hidden :: [Workspace String (Layout Window) Window]
hidden = [Workspace String (Layout Window) Window]
h } }

-- | All the directories that xmonad will use.  They will be used for
-- the following purposes:
--
-- * @dataDir@: This directory is used by XMonad to store data files
-- such as the run-time state file.
--
-- * @cfgDir@: This directory is where user configuration files are
-- stored (e.g, the xmonad.hs file).  You may also create a @lib@
-- subdirectory in the configuration directory and the default recompile
-- command will add it to the GHC include path.
--
-- * @cacheDir@: This directory is used to store temporary files that
-- can easily be recreated such as the configuration binary and any
-- intermediate object files generated by GHC.
-- Also, the XPrompt history file goes here.
--
-- For how these directories are chosen, see 'getDirectories'.
--
data Directories' a = Directories
    { forall a. Directories' a -> a
dataDir  :: !a
    , forall a. Directories' a -> a
cfgDir   :: !a
    , forall a. Directories' a -> a
cacheDir :: !a
    }
    deriving (Int -> Directories' a -> ShowS
[Directories' a] -> ShowS
Directories' a -> String
(Int -> Directories' a -> ShowS)
-> (Directories' a -> String)
-> ([Directories' a] -> ShowS)
-> Show (Directories' a)
forall a. Show a => Int -> Directories' a -> ShowS
forall a. Show a => [Directories' a] -> ShowS
forall a. Show a => Directories' a -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Directories' a] -> ShowS
$cshowList :: forall a. Show a => [Directories' a] -> ShowS
show :: Directories' a -> String
$cshow :: forall a. Show a => Directories' a -> String
showsPrec :: Int -> Directories' a -> ShowS
$cshowsPrec :: forall a. Show a => Int -> Directories' a -> ShowS
Show, (forall a b. (a -> b) -> Directories' a -> Directories' b)
-> (forall a b. a -> Directories' b -> Directories' a)
-> Functor Directories'
forall a b. a -> Directories' b -> Directories' a
forall a b. (a -> b) -> Directories' a -> Directories' b
forall (f :: * -> *).
(forall a b. (a -> b) -> f a -> f b)
-> (forall a b. a -> f b -> f a) -> Functor f
<$ :: forall a b. a -> Directories' b -> Directories' a
$c<$ :: forall a b. a -> Directories' b -> Directories' a
fmap :: forall a b. (a -> b) -> Directories' a -> Directories' b
$cfmap :: forall a b. (a -> b) -> Directories' a -> Directories' b
Functor, (forall m. Monoid m => Directories' m -> m)
-> (forall m a. Monoid m => (a -> m) -> Directories' a -> m)
-> (forall m a. Monoid m => (a -> m) -> Directories' a -> m)
-> (forall a b. (a -> b -> b) -> b -> Directories' a -> b)
-> (forall a b. (a -> b -> b) -> b -> Directories' a -> b)
-> (forall b a. (b -> a -> b) -> b -> Directories' a -> b)
-> (forall b a. (b -> a -> b) -> b -> Directories' a -> b)
-> (forall a. (a -> a -> a) -> Directories' a -> a)
-> (forall a. (a -> a -> a) -> Directories' a -> a)
-> (forall a. Directories' a -> [a])
-> (forall a. Directories' a -> Bool)
-> (forall a. Directories' a -> Int)
-> (forall a. Eq a => a -> Directories' a -> Bool)
-> (forall a. Ord a => Directories' a -> a)
-> (forall a. Ord a => Directories' a -> a)
-> (forall a. Num a => Directories' a -> a)
-> (forall a. Num a => Directories' a -> a)
-> Foldable Directories'
forall a. Eq a => a -> Directories' a -> Bool
forall a. Num a => Directories' a -> a
forall a. Ord a => Directories' a -> a
forall m. Monoid m => Directories' m -> m
forall a. Directories' a -> Bool
forall a. Directories' a -> Int
forall a. Directories' a -> [a]
forall a. (a -> a -> a) -> Directories' a -> a
forall m a. Monoid m => (a -> m) -> Directories' a -> m
forall b a. (b -> a -> b) -> b -> Directories' a -> b
forall a b. (a -> b -> b) -> b -> Directories' a -> b
forall (t :: * -> *).
(forall m. Monoid m => t m -> m)
-> (forall m a. Monoid m => (a -> m) -> t a -> m)
-> (forall m a. Monoid m => (a -> m) -> t a -> m)
-> (forall a b. (a -> b -> b) -> b -> t a -> b)
-> (forall a b. (a -> b -> b) -> b -> t a -> b)
-> (forall b a. (b -> a -> b) -> b -> t a -> b)
-> (forall b a. (b -> a -> b) -> b -> t a -> b)
-> (forall a. (a -> a -> a) -> t a -> a)
-> (forall a. (a -> a -> a) -> t a -> a)
-> (forall a. t a -> [a])
-> (forall a. t a -> Bool)
-> (forall a. t a -> Int)
-> (forall a. Eq a => a -> t a -> Bool)
-> (forall a. Ord a => t a -> a)
-> (forall a. Ord a => t a -> a)
-> (forall a. Num a => t a -> a)
-> (forall a. Num a => t a -> a)
-> Foldable t
product :: forall a. Num a => Directories' a -> a
$cproduct :: forall a. Num a => Directories' a -> a
sum :: forall a. Num a => Directories' a -> a
$csum :: forall a. Num a => Directories' a -> a
minimum :: forall a. Ord a => Directories' a -> a
$cminimum :: forall a. Ord a => Directories' a -> a
maximum :: forall a. Ord a => Directories' a -> a
$cmaximum :: forall a. Ord a => Directories' a -> a
elem :: forall a. Eq a => a -> Directories' a -> Bool
$celem :: forall a. Eq a => a -> Directories' a -> Bool
length :: forall a. Directories' a -> Int
$clength :: forall a. Directories' a -> Int
null :: forall a. Directories' a -> Bool
$cnull :: forall a. Directories' a -> Bool
toList :: forall a. Directories' a -> [a]
$ctoList :: forall a. Directories' a -> [a]
foldl1 :: forall a. (a -> a -> a) -> Directories' a -> a
$cfoldl1 :: forall a. (a -> a -> a) -> Directories' a -> a
foldr1 :: forall a. (a -> a -> a) -> Directories' a -> a
$cfoldr1 :: forall a. (a -> a -> a) -> Directories' a -> a
foldl' :: forall b a. (b -> a -> b) -> b -> Directories' a -> b
$cfoldl' :: forall b a. (b -> a -> b) -> b -> Directories' a -> b
foldl :: forall b a. (b -> a -> b) -> b -> Directories' a -> b
$cfoldl :: forall b a. (b -> a -> b) -> b -> Directories' a -> b
foldr' :: forall a b. (a -> b -> b) -> b -> Directories' a -> b
$cfoldr' :: forall a b. (a -> b -> b) -> b -> Directories' a -> b
foldr :: forall a b. (a -> b -> b) -> b -> Directories' a -> b
$cfoldr :: forall a b. (a -> b -> b) -> b -> Directories' a -> b
foldMap' :: forall m a. Monoid m => (a -> m) -> Directories' a -> m
$cfoldMap' :: forall m a. Monoid m => (a -> m) -> Directories' a -> m
foldMap :: forall m a. Monoid m => (a -> m) -> Directories' a -> m
$cfoldMap :: forall m a. Monoid m => (a -> m) -> Directories' a -> m
fold :: forall m. Monoid m => Directories' m -> m
$cfold :: forall m. Monoid m => Directories' m -> m
Foldable, Functor Directories'
Foldable Directories'
Functor Directories'
-> Foldable Directories'
-> (forall (f :: * -> *) a b.
    Applicative f =>
    (a -> f b) -> Directories' a -> f (Directories' b))
-> (forall (f :: * -> *) a.
    Applicative f =>
    Directories' (f a) -> f (Directories' a))
-> (forall (m :: * -> *) a b.
    Monad m =>
    (a -> m b) -> Directories' a -> m (Directories' b))
-> (forall (m :: * -> *) a.
    Monad m =>
    Directories' (m a) -> m (Directories' a))
-> Traversable Directories'
forall (t :: * -> *).
Functor t
-> Foldable t
-> (forall (f :: * -> *) a b.
    Applicative f =>
    (a -> f b) -> t a -> f (t b))
-> (forall (f :: * -> *) a. Applicative f => t (f a) -> f (t a))
-> (forall (m :: * -> *) a b.
    Monad m =>
    (a -> m b) -> t a -> m (t b))
-> (forall (m :: * -> *) a. Monad m => t (m a) -> m (t a))
-> Traversable t
forall (m :: * -> *) a.
Monad m =>
Directories' (m a) -> m (Directories' a)
forall (f :: * -> *) a.
Applicative f =>
Directories' (f a) -> f (Directories' a)
forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> Directories' a -> m (Directories' b)
forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> Directories' a -> f (Directories' b)
sequence :: forall (m :: * -> *) a.
Monad m =>
Directories' (m a) -> m (Directories' a)
$csequence :: forall (m :: * -> *) a.
Monad m =>
Directories' (m a) -> m (Directories' a)
mapM :: forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> Directories' a -> m (Directories' b)
$cmapM :: forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> Directories' a -> m (Directories' b)
sequenceA :: forall (f :: * -> *) a.
Applicative f =>
Directories' (f a) -> f (Directories' a)
$csequenceA :: forall (f :: * -> *) a.
Applicative f =>
Directories' (f a) -> f (Directories' a)
traverse :: forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> Directories' a -> f (Directories' b)
$ctraverse :: forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> Directories' a -> f (Directories' b)
Traversable)

-- | Convenient type alias for the most common case in which one might
-- want to use the 'Directories' type.
type Directories = Directories' FilePath

-- | Build up the 'Dirs' that xmonad will use.  They are chosen as
-- follows:
--
-- 1. If all three of xmonad's environment variables (@XMONAD_DATA_DIR@,
--    @XMONAD_CONFIG_DIR@, and @XMONAD_CACHE_DIR@) are set, use them.
-- 2. If there is a build script called @build@ or configuration
--    @xmonad.hs@ in @~\/.xmonad@, set all three directories to
--    @~\/.xmonad@.
-- 3. Otherwise, use the @xmonad@ directory in @XDG_DATA_HOME@,
--    @XDG_CONFIG_HOME@, and @XDG_CACHE_HOME@ (or their respective
--    fallbacks).  These directories are created if necessary.
--
-- The xmonad configuration file (or the build script, if present) is
-- always assumed to be in @cfgDir@.
--
getDirectories :: IO Directories
getDirectories :: IO Directories
getDirectories = IO Directories
xmEnvDirs IO Directories -> IO Directories -> IO Directories
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> IO Directories
xmDirs IO Directories -> IO Directories -> IO Directories
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> IO Directories
xdgDirs
  where
    -- | Check for xmonad's environment variables first
    xmEnvDirs :: IO Directories
    xmEnvDirs :: IO Directories
xmEnvDirs = do
        let xmEnvs :: Directories
xmEnvs = Directories :: forall a. a -> a -> a -> Directories' a
Directories{ dataDir :: String
dataDir  = String
"XMONAD_DATA_DIR"
                                , cfgDir :: String
cfgDir   = String
"XMONAD_CONFIG_DIR"
                                , cacheDir :: String
cacheDir = String
"XMONAD_CACHE_DIR"
                                }
        IO Directories
-> (Directories -> IO Directories)
-> Maybe Directories
-> IO Directories
forall b a. b -> (a -> b) -> Maybe a -> b
maybe IO Directories
forall (f :: * -> *) a. Alternative f => f a
empty Directories -> IO Directories
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Maybe Directories -> IO Directories)
-> (Directories' (Maybe String) -> Maybe Directories)
-> Directories' (Maybe String)
-> IO Directories
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Directories' (Maybe String) -> Maybe Directories
forall (t :: * -> *) (f :: * -> *) a.
(Traversable t, Applicative f) =>
t (f a) -> f (t a)
sequenceA (Directories' (Maybe String) -> IO Directories)
-> IO (Directories' (Maybe String)) -> IO Directories
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< (String -> IO (Maybe String))
-> Directories -> IO (Directories' (Maybe String))
forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
(a -> f b) -> t a -> f (t b)
traverse String -> IO (Maybe String)
getEnv Directories
xmEnvs

    -- | Check whether the config file or a build script is in the
    -- @~\/.xmonad@ directory
    xmDirs :: IO Directories
    xmDirs :: IO Directories
xmDirs = do
        String
xmDir <- String -> IO String
getAppUserDataDirectory String
"xmonad"
        Bool
conf  <- String -> IO Bool
doesFileExist (String -> IO Bool) -> String -> IO Bool
forall a b. (a -> b) -> a -> b
$ String
xmDir String -> ShowS
</> String
"xmonad.hs"
        Bool
build <- String -> IO Bool
doesFileExist (String -> IO Bool) -> String -> IO Bool
forall a b. (a -> b) -> a -> b
$ String
xmDir String -> ShowS
</> String
"build"

        -- Place *everything* in ~/.xmonad if yes
        Bool -> IO ()
forall (f :: * -> *). Alternative f => Bool -> f ()
guard (Bool -> IO ()) -> Bool -> IO ()
forall a b. (a -> b) -> a -> b
$ Bool
conf Bool -> Bool -> Bool
|| Bool
build
        Directories -> IO Directories
forall (f :: * -> *) a. Applicative f => a -> f a
pure Directories :: forall a. a -> a -> a -> Directories' a
Directories{ dataDir :: String
dataDir = String
xmDir, cfgDir :: String
cfgDir = String
xmDir, cacheDir :: String
cacheDir = String
xmDir }

    -- | Use XDG directories as a fallback
    xdgDirs :: IO Directories
    xdgDirs :: IO Directories
xdgDirs =
        Directories' XdgDirectory
-> (XdgDirectory -> IO String) -> IO Directories
forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
t a -> (a -> f b) -> f (t b)
for Directories :: forall a. a -> a -> a -> Directories' a
Directories{ dataDir :: XdgDirectory
dataDir = XdgDirectory
XdgData, cfgDir :: XdgDirectory
cfgDir = XdgDirectory
XdgConfig, cacheDir :: XdgDirectory
cacheDir = XdgDirectory
XdgCache }
            ((XdgDirectory -> IO String) -> IO Directories)
-> (XdgDirectory -> IO String) -> IO Directories
forall a b. (a -> b) -> a -> b
$ \XdgDirectory
dir -> do String
d <- XdgDirectory -> String -> IO String
getXdgDirectory XdgDirectory
dir String
"xmonad"
                         String
d String -> IO () -> IO String
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ Bool -> String -> IO ()
createDirectoryIfMissing Bool
True String
d

-- | Return the path to the xmonad configuration directory.
getXMonadDir :: X String
getXMonadDir :: X String
getXMonadDir = (XConf -> String) -> X String
forall r (m :: * -> *) a. MonadReader r m => (r -> a) -> m a
asks (Directories -> String
forall a. Directories' a -> a
cfgDir (Directories -> String)
-> (XConf -> Directories) -> XConf -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. XConf -> Directories
directories)
{-# DEPRECATED getXMonadDir "Use `asks (cfgDir . directories)' instead." #-}

-- | Return the path to the xmonad cache directory.
getXMonadCacheDir :: X String
getXMonadCacheDir :: X String
getXMonadCacheDir = (XConf -> String) -> X String
forall r (m :: * -> *) a. MonadReader r m => (r -> a) -> m a
asks (Directories -> String
forall a. Directories' a -> a
cacheDir (Directories -> String)
-> (XConf -> Directories) -> XConf -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. XConf -> Directories
directories)
{-# DEPRECATED getXMonadCacheDir "Use `asks (cacheDir . directories)' instead." #-}

-- | Return the path to the xmonad data directory.
getXMonadDataDir :: X String
getXMonadDataDir :: X String
getXMonadDataDir = (XConf -> String) -> X String
forall r (m :: * -> *) a. MonadReader r m => (r -> a) -> m a
asks (Directories -> String
forall a. Directories' a -> a
dataDir (Directories -> String)
-> (XConf -> Directories) -> XConf -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. XConf -> Directories
directories)
{-# DEPRECATED getXMonadDataDir "Use `asks (dataDir . directories)' instead." #-}

binFileName, buildDirName :: Directories -> FilePath
binFileName :: Directories -> String
binFileName  Directories{ String
cacheDir :: String
cacheDir :: forall a. Directories' a -> a
cacheDir } = String
cacheDir String -> ShowS
</> String
"xmonad-" String -> ShowS
forall a. Semigroup a => a -> a -> a
<> String
arch String -> ShowS
forall a. Semigroup a => a -> a -> a
<> String
"-" String -> ShowS
forall a. Semigroup a => a -> a -> a
<> String
os
buildDirName :: Directories -> String
buildDirName Directories{ String
cacheDir :: String
cacheDir :: forall a. Directories' a -> a
cacheDir } = String
cacheDir String -> ShowS
</> String
"build-" String -> ShowS
forall a. Semigroup a => a -> a -> a
<> String
arch String -> ShowS
forall a. Semigroup a => a -> a -> a
<> String
"-" String -> ShowS
forall a. Semigroup a => a -> a -> a
<> String
os

errFileName, stateFileName :: Directories -> FilePath
errFileName :: Directories -> String
errFileName   Directories{ String
dataDir :: String
dataDir :: forall a. Directories' a -> a
dataDir } = String
dataDir String -> ShowS
</> String
"xmonad.errors"
stateFileName :: Directories -> String
stateFileName Directories{ String
dataDir :: String
dataDir :: forall a. Directories' a -> a
dataDir } = String
dataDir String -> ShowS
</> String
"xmonad.state"

srcFileName, libFileName :: Directories -> FilePath
srcFileName :: Directories -> String
srcFileName Directories{ String
cfgDir :: String
cfgDir :: forall a. Directories' a -> a
cfgDir } = String
cfgDir String -> ShowS
</> String
"xmonad.hs"
libFileName :: Directories -> String
libFileName Directories{ String
cfgDir :: String
cfgDir :: forall a. Directories' a -> a
cfgDir } = String
cfgDir String -> ShowS
</> String
"lib"

buildScriptFileName, stackYamlFileName :: Directories -> FilePath
buildScriptFileName :: Directories -> String
buildScriptFileName Directories{ String
cfgDir :: String
cfgDir :: forall a. Directories' a -> a
cfgDir } = String
cfgDir String -> ShowS
</> String
"build"
stackYamlFileName :: Directories -> String
stackYamlFileName   Directories{ String
cfgDir :: String
cfgDir :: forall a. Directories' a -> a
cfgDir } = String
cfgDir String -> ShowS
</> String
"stack.yaml"

-- | Compilation method for xmonad configuration.
data Compile = CompileGhc | CompileStackGhc FilePath | CompileScript FilePath
    deriving (Int -> Compile -> ShowS
[Compile] -> ShowS
Compile -> String
(Int -> Compile -> ShowS)
-> (Compile -> String) -> ([Compile] -> ShowS) -> Show Compile
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Compile] -> ShowS
$cshowList :: [Compile] -> ShowS
show :: Compile -> String
$cshow :: Compile -> String
showsPrec :: Int -> Compile -> ShowS
$cshowsPrec :: Int -> Compile -> ShowS
Show)

-- | Detect compilation method by looking for known file names in xmonad
-- configuration directory.
detectCompile :: Directories -> IO Compile
detectCompile :: Directories -> IO Compile
detectCompile Directories
dirs = IO Compile
tryScript IO Compile -> IO Compile -> IO Compile
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> IO Compile
tryStack IO Compile -> IO Compile -> IO Compile
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> IO Compile
useGhc
  where
    buildScript :: String
buildScript = Directories -> String
buildScriptFileName Directories
dirs
    stackYaml :: String
stackYaml = Directories -> String
stackYamlFileName Directories
dirs

    tryScript :: IO Compile
tryScript = do
        Bool -> IO ()
forall (f :: * -> *). Alternative f => Bool -> f ()
guard (Bool -> IO ()) -> IO Bool -> IO ()
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< String -> IO Bool
doesFileExist String
buildScript
        Bool
isExe <- String -> IO Bool
isExecutable String
buildScript
        if Bool
isExe
          then do
            String -> IO ()
forall (m :: * -> *). MonadIO m => String -> m ()
trace (String -> IO ()) -> String -> IO ()
forall a b. (a -> b) -> a -> b
$ String
"XMonad will use build script at " String -> ShowS
forall a. Semigroup a => a -> a -> a
<> ShowS
forall a. Show a => a -> String
show String
buildScript String -> ShowS
forall a. Semigroup a => a -> a -> a
<> String
" to recompile."
            Compile -> IO Compile
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Compile -> IO Compile) -> Compile -> IO Compile
forall a b. (a -> b) -> a -> b
$ String -> Compile
CompileScript String
buildScript
          else do
            String -> IO ()
forall (m :: * -> *). MonadIO m => String -> m ()
trace (String -> IO ()) -> String -> IO ()
forall a b. (a -> b) -> a -> b
$ String
"XMonad will not use build script, because " String -> ShowS
forall a. Semigroup a => a -> a -> a
<> ShowS
forall a. Show a => a -> String
show String
buildScript String -> ShowS
forall a. Semigroup a => a -> a -> a
<> String
" is not executable."
            String -> IO ()
forall (m :: * -> *). MonadIO m => String -> m ()
trace (String -> IO ()) -> String -> IO ()
forall a b. (a -> b) -> a -> b
$ String
"Suggested resolution to use it: chmod u+x " String -> ShowS
forall a. Semigroup a => a -> a -> a
<> ShowS
forall a. Show a => a -> String
show String
buildScript
            IO Compile
forall (f :: * -> *) a. Alternative f => f a
empty

    tryStack :: IO Compile
tryStack = do
        Bool -> IO ()
forall (f :: * -> *). Alternative f => Bool -> f ()
guard (Bool -> IO ()) -> IO Bool -> IO ()
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< String -> IO Bool
doesFileExist String
stackYaml
        String
canonStackYaml <- String -> IO String
canonicalizePath String
stackYaml
        String -> IO ()
forall (m :: * -> *). MonadIO m => String -> m ()
trace (String -> IO ()) -> String -> IO ()
forall a b. (a -> b) -> a -> b
$ String
"XMonad will use stack ghc --stack-yaml " String -> ShowS
forall a. Semigroup a => a -> a -> a
<> ShowS
forall a. Show a => a -> String
show String
canonStackYaml String -> ShowS
forall a. Semigroup a => a -> a -> a
<> String
" to recompile."
        Compile -> IO Compile
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Compile -> IO Compile) -> Compile -> IO Compile
forall a b. (a -> b) -> a -> b
$ String -> Compile
CompileStackGhc String
canonStackYaml

    useGhc :: IO Compile
useGhc = do
        String -> IO ()
forall (m :: * -> *). MonadIO m => String -> m ()
trace (String -> IO ()) -> String -> IO ()
forall a b. (a -> b) -> a -> b
$ String
"XMonad will use ghc to recompile, because neither "
                String -> ShowS
forall a. Semigroup a => a -> a -> a
<> ShowS
forall a. Show a => a -> String
show String
buildScript String -> ShowS
forall a. Semigroup a => a -> a -> a
<> String
" nor " String -> ShowS
forall a. Semigroup a => a -> a -> a
<> ShowS
forall a. Show a => a -> String
show String
stackYaml String -> ShowS
forall a. Semigroup a => a -> a -> a
<> String
" exists."
        Compile -> IO Compile
forall (f :: * -> *) a. Applicative f => a -> f a
pure Compile
CompileGhc

    isExecutable :: String -> IO Bool
isExecutable String
f = IO Bool -> (SomeException -> IO Bool) -> IO Bool
forall e a. Exception e => IO a -> (e -> IO a) -> IO a
E.catch (Permissions -> Bool
executable (Permissions -> Bool) -> IO Permissions -> IO Bool
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> IO Permissions
getPermissions String
f) (\(SomeException e
_) -> Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
False)

-- | Should we recompile xmonad configuration? Is it newer than the compiled
-- binary?
shouldCompile :: Directories -> Compile -> IO Bool
shouldCompile :: Directories -> Compile -> IO Bool
shouldCompile Directories
dirs Compile
CompileGhc = do
    [Maybe UTCTime]
libTs <- (String -> IO (Maybe UTCTime)) -> [String] -> IO [Maybe UTCTime]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM String -> IO (Maybe UTCTime)
getModTime ([String] -> IO [Maybe UTCTime])
-> ([String] -> [String]) -> [String] -> IO [Maybe UTCTime]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (String -> Bool) -> [String] -> [String]
forall a. (a -> Bool) -> [a] -> [a]
Prelude.filter String -> Bool
isSource ([String] -> IO [Maybe UTCTime])
-> IO [String] -> IO [Maybe UTCTime]
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< String -> IO [String]
allFiles (Directories -> String
libFileName Directories
dirs)
    Maybe UTCTime
srcT <- String -> IO (Maybe UTCTime)
getModTime (Directories -> String
srcFileName Directories
dirs)
    Maybe UTCTime
binT <- String -> IO (Maybe UTCTime)
getModTime (Directories -> String
binFileName Directories
dirs)
    if (Maybe UTCTime -> Bool) -> [Maybe UTCTime] -> Bool
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
any (Maybe UTCTime
binT Maybe UTCTime -> Maybe UTCTime -> Bool
forall a. Ord a => a -> a -> Bool
<) (Maybe UTCTime
srcT Maybe UTCTime -> [Maybe UTCTime] -> [Maybe UTCTime]
forall a. a -> [a] -> [a]
: [Maybe UTCTime]
libTs)
        then Bool
True Bool -> IO () -> IO Bool
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ String -> IO ()
forall (m :: * -> *). MonadIO m => String -> m ()
trace String
"XMonad recompiling because some files have changed."
        else Bool
False Bool -> IO () -> IO Bool
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ String -> IO ()
forall (m :: * -> *). MonadIO m => String -> m ()
trace String
"XMonad skipping recompile because it is not forced (e.g. via --recompile), and neither xmonad.hs nor any *.hs / *.lhs / *.hsc files in lib/ have been changed."
  where
    isSource :: String -> Bool
isSource = (String -> [String] -> Bool) -> [String] -> String -> Bool
forall a b c. (a -> b -> c) -> b -> a -> c
flip String -> [String] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
elem [String
".hs",String
".lhs",String
".hsc"] (String -> Bool) -> ShowS -> String -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ShowS
takeExtension
    allFiles :: String -> IO [String]
allFiles String
t = do
        let prep :: [String] -> [String]
prep = ShowS -> [String] -> [String]
forall a b. (a -> b) -> [a] -> [b]
map (String
tString -> ShowS
</>) ([String] -> [String])
-> ([String] -> [String]) -> [String] -> [String]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (String -> Bool) -> [String] -> [String]
forall a. (a -> Bool) -> [a] -> [a]
Prelude.filter (String -> [String] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`notElem` [String
".",String
".."])
        [String]
cs <- [String] -> [String]
prep ([String] -> [String]) -> IO [String] -> IO [String]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> IO [String] -> (SomeException -> IO [String]) -> IO [String]
forall e a. Exception e => IO a -> (e -> IO a) -> IO a
E.catch (String -> IO [String]
getDirectoryContents String
t) (\(SomeException e
_) -> [String] -> IO [String]
forall (m :: * -> *) a. Monad m => a -> m a
return [])
        [String]
ds <- (String -> IO Bool) -> [String] -> IO [String]
forall (m :: * -> *) a.
Applicative m =>
(a -> m Bool) -> [a] -> m [a]
filterM String -> IO Bool
doesDirectoryExist [String]
cs
        [[String]] -> [String]
forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat ([[String]] -> [String])
-> ([[String]] -> [[String]]) -> [[String]] -> [String]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (([String]
cs [String] -> [String] -> [String]
forall a. Eq a => [a] -> [a] -> [a]
\\ [String]
ds)[String] -> [[String]] -> [[String]]
forall a. a -> [a] -> [a]
:) ([[String]] -> [String]) -> IO [[String]] -> IO [String]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (String -> IO [String]) -> [String] -> IO [[String]]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM String -> IO [String]
allFiles [String]
ds
shouldCompile Directories
dirs CompileStackGhc{} = do
    Maybe UTCTime
stackYamlT <- String -> IO (Maybe UTCTime)
getModTime (Directories -> String
stackYamlFileName Directories
dirs)
    Maybe UTCTime
binT <- String -> IO (Maybe UTCTime)
getModTime (Directories -> String
binFileName Directories
dirs)
    if Maybe UTCTime
binT Maybe UTCTime -> Maybe UTCTime -> Bool
forall a. Ord a => a -> a -> Bool
< Maybe UTCTime
stackYamlT
        then Bool
True Bool -> IO () -> IO Bool
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ String -> IO ()
forall (m :: * -> *). MonadIO m => String -> m ()
trace String
"XMonad recompiling because some files have changed."
        else Directories -> Compile -> IO Bool
shouldCompile Directories
dirs Compile
CompileGhc
shouldCompile Directories
_dirs CompileScript{} =
    Bool
True Bool -> IO () -> IO Bool
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ String -> IO ()
forall (m :: * -> *). MonadIO m => String -> m ()
trace String
"XMonad recompiling because a custom build script is being used."

getModTime :: FilePath -> IO (Maybe UTCTime)
getModTime :: String -> IO (Maybe UTCTime)
getModTime String
f = IO (Maybe UTCTime)
-> (SomeException -> IO (Maybe UTCTime)) -> IO (Maybe UTCTime)
forall e a. Exception e => IO a -> (e -> IO a) -> IO a
E.catch (UTCTime -> Maybe UTCTime
forall a. a -> Maybe a
Just (UTCTime -> Maybe UTCTime) -> IO UTCTime -> IO (Maybe UTCTime)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> IO UTCTime
getModificationTime String
f) (\(SomeException e
_) -> Maybe UTCTime -> IO (Maybe UTCTime)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe UTCTime
forall a. Maybe a
Nothing)

-- | Compile the configuration.
compile :: Directories -> Compile -> IO ExitCode
compile :: Directories -> Compile -> IO ExitCode
compile Directories
dirs Compile
method =
    IO () -> IO () -> IO ExitCode -> IO ExitCode
forall a b c. IO a -> IO b -> IO c -> IO c
bracket_ IO ()
forall (m :: * -> *). MonadIO m => m ()
uninstallSignalHandlers IO ()
forall (m :: * -> *). MonadIO m => m ()
installSignalHandlers (IO ExitCode -> IO ExitCode) -> IO ExitCode -> IO ExitCode
forall a b. (a -> b) -> a -> b
$
        String -> IOMode -> (Handle -> IO ExitCode) -> IO ExitCode
forall r. String -> IOMode -> (Handle -> IO r) -> IO r
withFile (Directories -> String
errFileName Directories
dirs) IOMode
WriteMode ((Handle -> IO ExitCode) -> IO ExitCode)
-> (Handle -> IO ExitCode) -> IO ExitCode
forall a b. (a -> b) -> a -> b
$ \Handle
err -> do
            let run :: String -> [String] -> IO ExitCode
run = String -> Handle -> String -> [String] -> IO ExitCode
runProc (Directories -> String
forall a. Directories' a -> a
cfgDir Directories
dirs) Handle
err
            case Compile
method of
                Compile
CompileGhc -> do
                    String
ghc <- String -> Maybe String -> String
forall a. a -> Maybe a -> a
fromMaybe String
"ghc" (Maybe String -> String) -> IO (Maybe String) -> IO String
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> IO (Maybe String)
lookupEnv String
"XMONAD_GHC"
                    String -> [String] -> IO ExitCode
run String
ghc [String]
ghcArgs
                CompileStackGhc String
stackYaml ->
                    String -> [String] -> IO ExitCode
run String
"stack" [String
"build", String
"--silent", String
"--stack-yaml", String
stackYaml] IO ExitCode -> IO ExitCode -> IO ExitCode
forall {m :: * -> *}.
Monad m =>
m ExitCode -> m ExitCode -> m ExitCode
.&&.
                    String -> [String] -> IO ExitCode
run String
"stack" (String
"ghc" String -> [String] -> [String]
forall a. a -> [a] -> [a]
: String
"--stack-yaml" String -> [String] -> [String]
forall a. a -> [a] -> [a]
: String
stackYaml String -> [String] -> [String]
forall a. a -> [a] -> [a]
: String
"--" String -> [String] -> [String]
forall a. a -> [a] -> [a]
: [String]
ghcArgs)
                CompileScript String
script ->
                    String -> [String] -> IO ExitCode
run String
script [Directories -> String
binFileName Directories
dirs]
  where
    ghcArgs :: [String]
ghcArgs = [ String
"--make"
              , String
"xmonad.hs"
              , String
"-i" -- only look in @lib@
              , String
"-ilib"
              , String
"-fforce-recomp"
              , String
"-main-is", String
"main"
              , String
"-v0"
              , String
"-outputdir", Directories -> String
buildDirName Directories
dirs
              , String
"-o", Directories -> String
binFileName Directories
dirs
              ]

    -- waitForProcess =<< System.Process.runProcess, but without closing the err handle
    runProc :: String -> Handle -> String -> [String] -> IO ExitCode
runProc String
cwd Handle
err String
exe [String]
args = do
        Handle -> String -> IO ()
hPutStrLn Handle
err (String -> IO ()) -> String -> IO ()
forall a b. (a -> b) -> a -> b
$ [String] -> String
unwords ([String] -> String) -> [String] -> String
forall a b. (a -> b) -> a -> b
$ String
"$" String -> [String] -> [String]
forall a. a -> [a] -> [a]
: String
exe String -> [String] -> [String]
forall a. a -> [a] -> [a]
: [String]
args
        Handle -> IO ()
hFlush Handle
err
        (Maybe Handle
_, Maybe Handle
_, Maybe Handle
_, ProcessHandle
h) <- String
-> CreateProcess
-> IO (Maybe Handle, Maybe Handle, Maybe Handle, ProcessHandle)
createProcess_ String
"runProc" (String -> [String] -> CreateProcess
proc String
exe [String]
args){ cwd :: Maybe String
cwd = String -> Maybe String
forall a. a -> Maybe a
Just String
cwd, std_err :: StdStream
std_err = Handle -> StdStream
UseHandle Handle
err }
        ProcessHandle -> IO ExitCode
waitForProcess ProcessHandle
h

    m ExitCode
cmd1 .&&. :: m ExitCode -> m ExitCode -> m ExitCode
.&&. m ExitCode
cmd2 = m ExitCode
cmd1 m ExitCode -> (ExitCode -> m ExitCode) -> m ExitCode
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \case
        ExitCode
ExitSuccess -> m ExitCode
cmd2
        ExitCode
e -> ExitCode -> m ExitCode
forall (f :: * -> *) a. Applicative f => a -> f a
pure ExitCode
e

-- | Check GHC output for deprecation warnings and notify the user if there
-- were any. Report success otherwise.
checkCompileWarnings :: Directories -> IO ()
checkCompileWarnings :: Directories -> IO ()
checkCompileWarnings Directories
dirs = do
    String
ghcErr <- String -> IO String
readFile (Directories -> String
errFileName Directories
dirs)
    if String
"-Wdeprecations" String -> String -> Bool
forall a. Eq a => [a] -> [a] -> Bool
`isInfixOf` String
ghcErr
      then do
        let msg :: String
msg = [String] -> String
unlines ([String] -> String) -> [String] -> String
forall a b. (a -> b) -> a -> b
$
                [String
"Deprecations detected while compiling xmonad config: " String -> ShowS
forall a. Semigroup a => a -> a -> a
<> Directories -> String
srcFileName Directories
dirs]
                [String] -> [String] -> [String]
forall a. [a] -> [a] -> [a]
++ String -> [String]
lines String
ghcErr
                [String] -> [String] -> [String]
forall a. [a] -> [a] -> [a]
++ [String
"",String
"Please correct them or silence using {-# OPTIONS_GHC -Wno-deprecations #-}."]
        String -> IO ()
forall (m :: * -> *). MonadIO m => String -> m ()
trace String
msg
        String -> IO ()
forall (m :: * -> *). MonadIO m => String -> m ()
xmessage String
msg
      else
        String -> IO ()
forall (m :: * -> *). MonadIO m => String -> m ()
trace String
"XMonad recompilation process exited with success!"

-- | Notify the user that compilation failed and what was wrong.
compileFailed :: Directories -> ExitCode -> IO ()
compileFailed :: Directories -> ExitCode -> IO ()
compileFailed Directories
dirs ExitCode
status = do
    String
ghcErr <- String -> IO String
readFile (Directories -> String
errFileName Directories
dirs)
    let msg :: String
msg = [String] -> String
unlines ([String] -> String) -> [String] -> String
forall a b. (a -> b) -> a -> b
$
            [String
"Errors detected while compiling xmonad config: " String -> ShowS
forall a. Semigroup a => a -> a -> a
<> Directories -> String
srcFileName Directories
dirs]
            [String] -> [String] -> [String]
forall a. [a] -> [a] -> [a]
++ String -> [String]
lines (if String -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null String
ghcErr then ExitCode -> String
forall a. Show a => a -> String
show ExitCode
status else String
ghcErr)
            [String] -> [String] -> [String]
forall a. [a] -> [a] -> [a]
++ [String
"",String
"Please check the file for errors."]
    -- nb, the ordering of printing, then forking, is crucial due to
    -- lazy evaluation
    String -> IO ()
forall (m :: * -> *). MonadIO m => String -> m ()
trace String
msg
    String -> IO ()
forall (m :: * -> *). MonadIO m => String -> m ()
xmessage String
msg

-- | Recompile the xmonad configuration file when any of the following apply:
--
--  * force is 'True'
--
--  * the xmonad executable does not exist
--
--  * the xmonad executable is older than @xmonad.hs@ or any file in
--    the @lib@ directory (under the configuration directory)
--
--  * custom @build@ script is being used
--
-- The -i flag is used to restrict recompilation to the xmonad.hs file only,
-- and any files in the aforementioned @lib@ directory.
--
-- Compilation errors (if any) are logged to the @xmonad.errors@ file
-- in the xmonad data directory.  If GHC indicates failure with a
-- non-zero exit code, an xmessage displaying that file is spawned.
--
-- 'False' is returned if there are compilation errors.
--
recompile :: MonadIO m => Directories -> Bool -> m Bool
recompile :: forall (m :: * -> *). MonadIO m => Directories -> Bool -> m Bool
recompile Directories
dirs Bool
force = IO Bool -> m Bool
forall (m :: * -> *) a. MonadIO m => IO a -> m a
io (IO Bool -> m Bool) -> IO Bool -> m Bool
forall a b. (a -> b) -> a -> b
$ do
    Compile
method <- Directories -> IO Compile
detectCompile Directories
dirs
    Bool
willCompile <- if Bool
force
        then Bool
True Bool -> IO () -> IO Bool
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ String -> IO ()
forall (m :: * -> *). MonadIO m => String -> m ()
trace String
"XMonad recompiling (forced)."
        else Directories -> Compile -> IO Bool
shouldCompile Directories
dirs Compile
method
    if Bool
willCompile
      then do
        ExitCode
status <- Directories -> Compile -> IO ExitCode
compile Directories
dirs Compile
method
        if ExitCode
status ExitCode -> ExitCode -> Bool
forall a. Eq a => a -> a -> Bool
== ExitCode
ExitSuccess
            then Directories -> IO ()
checkCompileWarnings Directories
dirs
            else Directories -> ExitCode -> IO ()
compileFailed Directories
dirs ExitCode
status
        Bool -> IO Bool
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Bool -> IO Bool) -> Bool -> IO Bool
forall a b. (a -> b) -> a -> b
$ ExitCode
status ExitCode -> ExitCode -> Bool
forall a. Eq a => a -> a -> Bool
== ExitCode
ExitSuccess
      else
        Bool -> IO Bool
forall (f :: * -> *) a. Applicative f => a -> f a
pure Bool
True

-- | Conditionally run an action, using a @Maybe a@ to decide.
whenJust :: Monad m => Maybe a -> (a -> m ()) -> m ()
whenJust :: forall (m :: * -> *) a. Monad m => Maybe a -> (a -> m ()) -> m ()
whenJust Maybe a
mg a -> m ()
f = m () -> (a -> m ()) -> Maybe a -> m ()
forall b a. b -> (a -> b) -> Maybe a -> b
maybe (() -> m ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()) a -> m ()
f Maybe a
mg

-- | Conditionally run an action, using a 'X' event to decide
whenX :: X Bool -> X () -> X ()
whenX :: X Bool -> X () -> X ()
whenX X Bool
a X ()
f = X Bool
a X Bool -> (Bool -> X ()) -> X ()
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \Bool
b -> Bool -> X () -> X ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when Bool
b X ()
f

-- | A 'trace' for the 'X' monad. Logs a string to stderr. The result may
-- be found in your .xsession-errors file
trace :: MonadIO m => String -> m ()
trace :: forall (m :: * -> *). MonadIO m => String -> m ()
trace = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
io (IO () -> m ()) -> (String -> IO ()) -> String -> m ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Handle -> String -> IO ()
hPutStrLn Handle
stderr

-- | Ignore SIGPIPE to avoid termination when a pipe is full, and SIGCHLD to
-- avoid zombie processes, and clean up any extant zombie processes.
installSignalHandlers :: MonadIO m => m ()
installSignalHandlers :: forall (m :: * -> *). MonadIO m => m ()
installSignalHandlers = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
io (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Signal -> Handler -> Maybe SignalSet -> IO Handler
installHandler Signal
openEndedPipe Handler
Ignore Maybe SignalSet
forall a. Maybe a
Nothing
    Signal -> Handler -> Maybe SignalSet -> IO Handler
installHandler Signal
sigCHLD Handler
Ignore Maybe SignalSet
forall a. Maybe a
Nothing
    (forall {a}. IO a -> IO (Either SomeException a)
forall e a. Exception e => IO a -> IO (Either e a)
try :: IO a -> IO (Either SomeException a))
      (IO () -> IO (Either SomeException ()))
-> IO () -> IO (Either SomeException ())
forall a b. (a -> b) -> a -> b
$ (IO () -> IO ()) -> IO ()
forall a. (a -> a) -> a
fix ((IO () -> IO ()) -> IO ()) -> (IO () -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \IO ()
more -> do
        Maybe (ProcessID, ProcessStatus)
x <- Bool -> Bool -> IO (Maybe (ProcessID, ProcessStatus))
getAnyProcessStatus Bool
False Bool
False
        Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (Maybe (ProcessID, ProcessStatus) -> Bool
forall a. Maybe a -> Bool
isJust Maybe (ProcessID, ProcessStatus)
x) IO ()
more
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

uninstallSignalHandlers :: MonadIO m => m ()
uninstallSignalHandlers :: forall (m :: * -> *). MonadIO m => m ()
uninstallSignalHandlers = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
io (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Signal -> Handler -> Maybe SignalSet -> IO Handler
installHandler Signal
openEndedPipe Handler
Default Maybe SignalSet
forall a. Maybe a
Nothing
    Signal -> Handler -> Maybe SignalSet -> IO Handler
installHandler Signal
sigCHLD Handler
Default Maybe SignalSet
forall a. Maybe a
Nothing
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()