{-# LANGUAGE CPP #-}
{-# LANGUAGE DeriveTraversable #-}
{-# LANGUAGE ExistentialQuantification #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE NamedFieldPuns #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE DerivingVia #-}
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, ifM,
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.Fix (fix)
import Control.Monad.State
import Control.Monad.Reader
import Control.Monad (filterM, guard, void, when)
import Data.Semigroup
import Data.Traversable (for)
import Data.Time.Clock (UTCTime)
import Data.Default.Class
import System.Environment (lookupEnv)
import Data.List (isInfixOf, intercalate, (\\))
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.Maybe (isJust,fromMaybe)
import Data.Monoid (Ap(..))
import qualified Data.Map as M
import qualified Data.Set as S
data XState = XState
{ XState -> WindowSet
windowset :: !WindowSet
, XState -> Set Window
mapped :: !(S.Set Window)
, XState -> Map Window Int
waitingUnmap :: !(M.Map Window Int)
, XState -> Maybe (Position -> Position -> X (), X ())
dragging :: !(Maybe (Position -> Position -> X (), X ()))
, XState -> KeyMask
numberlockMask :: !KeyMask
, XState -> Map FilePath (Either FilePath StateExtension)
extensibleState :: !(M.Map String (Either String StateExtension))
}
data XConf = XConf
{ XConf -> Display
display :: Display
, XConf -> XConfig Layout
config :: !(XConfig Layout)
, XConf -> Window
theRoot :: !Window
, XConf -> Window
normalBorder :: !Pixel
, XConf -> Window
focusedBorder :: !Pixel
, XConf -> Map (KeyMask, Window) (X ())
keyActions :: !(M.Map (KeyMask, KeySym) (X ()))
, XConf -> Map (KeyMask, Button) (Window -> X ())
buttonActions :: !(M.Map (KeyMask, Button) (Window -> X ()))
, XConf -> Bool
mouseFocused :: !Bool
, XConf -> Maybe (Position, Position)
mousePosition :: !(Maybe (Position, Position))
, XConf -> Maybe Event
currentEvent :: !(Maybe Event)
, XConf -> Directories
directories :: !Directories
}
data XConfig l = XConfig
{ forall (l :: * -> *). XConfig l -> FilePath
normalBorderColor :: !String
, forall (l :: * -> *). XConfig l -> FilePath
focusedBorderColor :: !String
, forall (l :: * -> *). XConfig l -> FilePath
terminal :: !String
, forall (l :: * -> *). XConfig l -> l Window
layoutHook :: !(l Window)
, forall (l :: * -> *). XConfig l -> ManageHook
manageHook :: !ManageHook
, forall (l :: * -> *). XConfig l -> Event -> X All
handleEventHook :: !(Event -> X All)
, forall (l :: * -> *). XConfig l -> [FilePath]
workspaces :: ![String]
, forall (l :: * -> *). XConfig l -> KeyMask
modMask :: !KeyMask
, forall (l :: * -> *).
XConfig l -> XConfig Layout -> Map (KeyMask, Window) (X ())
keys :: !(XConfig Layout -> M.Map (ButtonMask,KeySym) (X ()))
, forall (l :: * -> *).
XConfig l
-> XConfig Layout -> Map (KeyMask, Button) (Window -> X ())
mouseBindings :: !(XConfig Layout -> M.Map (ButtonMask, Button) (Window -> X ()))
, forall (l :: * -> *). XConfig l -> Button
borderWidth :: !Dimension
, forall (l :: * -> *). XConfig l -> X ()
logHook :: !(X ())
, forall (l :: * -> *). XConfig l -> X ()
startupHook :: !(X ())
, forall (l :: * -> *). XConfig l -> Bool
focusFollowsMouse :: !Bool
, forall (l :: * -> *). XConfig l -> Bool
clickJustFocuses :: !Bool
, forall (l :: * -> *). XConfig l -> Window
clientMask :: !EventMask
, forall (l :: * -> *). XConfig l -> Window
rootMask :: !EventMask
, forall (l :: * -> *).
XConfig l -> [FilePath] -> XConfig Layout -> IO (XConfig Layout)
handleExtraArgs :: !([String] -> XConfig Layout -> IO (XConfig Layout))
, forall (l :: * -> *). XConfig l -> Map TypeRep ConfExtension
extensibleConf :: !(M.Map TypeRep ConfExtension)
}
type WindowSet = StackSet WorkspaceId (Layout Window) Window ScreenId ScreenDetail
type WindowSpace = Workspace WorkspaceId (Layout Window) Window
type WorkspaceId = String
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
$c== :: ScreenId -> ScreenId -> Bool
== :: ScreenId -> ScreenId -> Bool
$c/= :: ScreenId -> ScreenId -> Bool
/= :: 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
$ccompare :: ScreenId -> ScreenId -> Ordering
compare :: ScreenId -> ScreenId -> Ordering
$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
>= :: ScreenId -> ScreenId -> Bool
$cmax :: ScreenId -> ScreenId -> ScreenId
max :: ScreenId -> ScreenId -> ScreenId
$cmin :: ScreenId -> ScreenId -> ScreenId
min :: ScreenId -> ScreenId -> ScreenId
Ord,Int -> ScreenId -> ShowS
[ScreenId] -> ShowS
ScreenId -> FilePath
(Int -> ScreenId -> ShowS)
-> (ScreenId -> FilePath) -> ([ScreenId] -> ShowS) -> Show ScreenId
forall a.
(Int -> a -> ShowS) -> (a -> FilePath) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> ScreenId -> ShowS
showsPrec :: Int -> ScreenId -> ShowS
$cshow :: ScreenId -> FilePath
show :: ScreenId -> FilePath
$cshowList :: [ScreenId] -> ShowS
showList :: [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
$creadsPrec :: Int -> ReadS ScreenId
readsPrec :: Int -> ReadS ScreenId
$creadList :: ReadS [ScreenId]
readList :: ReadS [ScreenId]
$creadPrec :: ReadPrec ScreenId
readPrec :: ReadPrec ScreenId
$creadListPrec :: ReadPrec [ScreenId]
readListPrec :: ReadPrec [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
$csucc :: ScreenId -> ScreenId
succ :: ScreenId -> ScreenId
$cpred :: ScreenId -> ScreenId
pred :: ScreenId -> ScreenId
$ctoEnum :: Int -> ScreenId
toEnum :: Int -> ScreenId
$cfromEnum :: ScreenId -> Int
fromEnum :: ScreenId -> Int
$cenumFrom :: ScreenId -> [ScreenId]
enumFrom :: ScreenId -> [ScreenId]
$cenumFromThen :: ScreenId -> ScreenId -> [ScreenId]
enumFromThen :: ScreenId -> ScreenId -> [ScreenId]
$cenumFromTo :: ScreenId -> ScreenId -> [ScreenId]
enumFromTo :: ScreenId -> ScreenId -> [ScreenId]
$cenumFromThenTo :: ScreenId -> ScreenId -> ScreenId -> [ScreenId]
enumFromThenTo :: ScreenId -> ScreenId -> 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
$c+ :: ScreenId -> ScreenId -> ScreenId
+ :: ScreenId -> ScreenId -> ScreenId
$c- :: ScreenId -> ScreenId -> ScreenId
- :: ScreenId -> ScreenId -> ScreenId
$c* :: ScreenId -> ScreenId -> ScreenId
* :: ScreenId -> ScreenId -> ScreenId
$cnegate :: ScreenId -> ScreenId
negate :: ScreenId -> ScreenId
$cabs :: ScreenId -> ScreenId
abs :: ScreenId -> ScreenId
$csignum :: ScreenId -> ScreenId
signum :: ScreenId -> ScreenId
$cfromInteger :: Integer -> ScreenId
fromInteger :: Integer -> 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
$cquot :: ScreenId -> ScreenId -> ScreenId
quot :: ScreenId -> ScreenId -> ScreenId
$crem :: ScreenId -> ScreenId -> ScreenId
rem :: ScreenId -> ScreenId -> ScreenId
$cdiv :: ScreenId -> ScreenId -> ScreenId
div :: ScreenId -> ScreenId -> ScreenId
$cmod :: ScreenId -> ScreenId -> ScreenId
mod :: ScreenId -> ScreenId -> ScreenId
$cquotRem :: ScreenId -> ScreenId -> (ScreenId, ScreenId)
quotRem :: ScreenId -> ScreenId -> (ScreenId, ScreenId)
$cdivMod :: ScreenId -> ScreenId -> (ScreenId, ScreenId)
divMod :: ScreenId -> ScreenId -> (ScreenId, ScreenId)
$ctoInteger :: ScreenId -> Integer
toInteger :: ScreenId -> Integer
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
$ctoRational :: ScreenId -> Rational
toRational :: ScreenId -> Rational
Real)
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
$c== :: ScreenDetail -> ScreenDetail -> Bool
== :: ScreenDetail -> ScreenDetail -> Bool
$c/= :: ScreenDetail -> ScreenDetail -> Bool
/= :: ScreenDetail -> ScreenDetail -> Bool
Eq,Int -> ScreenDetail -> ShowS
[ScreenDetail] -> ShowS
ScreenDetail -> FilePath
(Int -> ScreenDetail -> ShowS)
-> (ScreenDetail -> FilePath)
-> ([ScreenDetail] -> ShowS)
-> Show ScreenDetail
forall a.
(Int -> a -> ShowS) -> (a -> FilePath) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> ScreenDetail -> ShowS
showsPrec :: Int -> ScreenDetail -> ShowS
$cshow :: ScreenDetail -> FilePath
show :: ScreenDetail -> FilePath
$cshowList :: [ScreenDetail] -> ShowS
showList :: [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
$creadsPrec :: Int -> ReadS ScreenDetail
readsPrec :: Int -> ReadS ScreenDetail
$creadList :: ReadS [ScreenDetail]
readList :: ReadS [ScreenDetail]
$creadPrec :: ReadPrec ScreenDetail
readPrec :: ReadPrec ScreenDetail
$creadListPrec :: ReadPrec [ScreenDetail]
readListPrec :: ReadPrec [ScreenDetail]
Read)
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
$cfmap :: forall a b. (a -> b) -> X a -> X b
fmap :: forall a b. (a -> b) -> X a -> X b
$c<$ :: forall a b. a -> X b -> X a
<$ :: forall a b. a -> X b -> X a
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
$cpure :: forall a. a -> X a
pure :: forall a. a -> X a
$c<*> :: forall a b. X (a -> b) -> X a -> X b
<*> :: forall a b. X (a -> b) -> X a -> X b
$cliftA2 :: forall a b c. (a -> b -> c) -> X a -> X b -> X c
liftA2 :: forall a b c. (a -> b -> c) -> X a -> X b -> X c
$c*> :: forall a b. X a -> X b -> X b
*> :: forall a b. X a -> X b -> X b
$c<* :: forall a b. X a -> X b -> X a
<* :: forall a b. X a -> X b -> 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
$c>>= :: forall a b. X a -> (a -> X b) -> X b
>>= :: forall a b. X a -> (a -> X b) -> X b
$c>> :: forall a b. X a -> X b -> X b
>> :: forall a b. X a -> X b -> X b
$creturn :: forall a. a -> X a
return :: forall a. a -> X a
Monad, Monad X
Monad X => (forall a. FilePath -> X a) -> MonadFail X
forall a. FilePath -> X a
forall (m :: * -> *).
Monad m =>
(forall a. FilePath -> m a) -> MonadFail m
$cfail :: forall a. FilePath -> X a
fail :: forall a. FilePath -> 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
$cliftIO :: forall a. IO a -> X a
liftIO :: forall a. IO a -> X a
MonadIO, MonadState XState, MonadReader XConf)
deriving (NonEmpty (X a) -> X a
X a -> X a -> X a
(X a -> X a -> X a)
-> (NonEmpty (X a) -> X a)
-> (forall b. Integral b => b -> X a -> X a)
-> Semigroup (X a)
forall b. Integral b => b -> X a -> X a
forall a. Semigroup a => NonEmpty (X a) -> X a
forall a. Semigroup a => X a -> X a -> X a
forall a b. (Semigroup a, Integral b) => b -> X a -> X a
forall a.
(a -> a -> a)
-> (NonEmpty a -> a)
-> (forall b. Integral b => b -> a -> a)
-> Semigroup a
$c<> :: forall a. Semigroup a => X a -> X a -> X a
<> :: X a -> X a -> X a
$csconcat :: forall a. Semigroup a => NonEmpty (X a) -> X a
sconcat :: NonEmpty (X a) -> X a
$cstimes :: forall a b. (Semigroup a, Integral b) => b -> X a -> X a
stimes :: forall b. Integral b => b -> X a -> X a
Semigroup, Semigroup (X a)
X a
Semigroup (X a) =>
X a -> (X a -> X a -> X a) -> ([X a] -> X a) -> Monoid (X a)
[X a] -> X a
X a -> X a -> X a
forall a.
Semigroup a =>
a -> (a -> a -> a) -> ([a] -> a) -> Monoid a
forall a. Monoid a => Semigroup (X a)
forall a. Monoid a => X a
forall a. Monoid a => [X a] -> X a
forall a. Monoid a => X a -> X a -> X a
$cmempty :: forall a. Monoid a => X a
mempty :: X a
$cmappend :: forall a. Monoid a => X a -> X a -> X a
mappend :: X a -> X a -> X a
$cmconcat :: forall a. Monoid a => [X a] -> X a
mconcat :: [X a] -> X a
Monoid) via Ap X a
instance Default a => Default (X a) where
def :: X a
def = a -> X a
forall a. 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
$cfmap :: forall a b. (a -> b) -> Query a -> Query b
fmap :: forall a b. (a -> b) -> Query a -> Query b
$c<$ :: forall a b. a -> Query b -> Query a
<$ :: forall a b. a -> Query b -> Query a
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
$cpure :: forall a. a -> Query a
pure :: forall a. a -> Query a
$c<*> :: forall a b. Query (a -> b) -> Query a -> Query b
<*> :: forall a b. Query (a -> b) -> Query a -> Query b
$cliftA2 :: forall a b c. (a -> b -> c) -> Query a -> Query b -> Query c
liftA2 :: forall a b c. (a -> b -> c) -> Query a -> Query b -> Query c
$c*> :: forall a b. Query a -> Query b -> Query b
*> :: forall a b. Query a -> Query b -> Query b
$c<* :: forall a b. Query a -> Query b -> Query a
<* :: forall a b. Query a -> Query b -> 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
$c>>= :: forall a b. Query a -> (a -> Query b) -> Query b
>>= :: forall a b. Query a -> (a -> Query b) -> Query b
$c>> :: forall a b. Query a -> Query b -> Query b
>> :: forall a b. Query a -> Query b -> Query b
$creturn :: forall a. a -> Query a
return :: forall a. a -> Query a
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
$cliftIO :: forall a. IO a -> Query a
liftIO :: forall a. IO a -> Query a
MonadIO)
deriving (NonEmpty (Query a) -> Query a
Query a -> Query a -> Query a
(Query a -> Query a -> Query a)
-> (NonEmpty (Query a) -> Query a)
-> (forall b. Integral b => b -> Query a -> Query a)
-> Semigroup (Query a)
forall b. Integral b => b -> Query a -> Query a
forall a. Semigroup a => NonEmpty (Query a) -> Query a
forall a. Semigroup a => Query a -> Query a -> Query a
forall a b. (Semigroup a, Integral b) => b -> Query a -> Query a
forall a.
(a -> a -> a)
-> (NonEmpty a -> a)
-> (forall b. Integral b => b -> a -> a)
-> Semigroup a
$c<> :: forall a. Semigroup a => Query a -> Query a -> Query a
<> :: Query a -> Query a -> Query a
$csconcat :: forall a. Semigroup a => NonEmpty (Query a) -> Query a
sconcat :: NonEmpty (Query a) -> Query a
$cstimes :: forall a b. (Semigroup a, Integral b) => b -> Query a -> Query a
stimes :: forall b. Integral b => b -> Query a -> Query a
Semigroup, Semigroup (Query a)
Query a
Semigroup (Query a) =>
Query a
-> (Query a -> Query a -> Query a)
-> ([Query a] -> Query a)
-> Monoid (Query a)
[Query a] -> Query a
Query a -> Query a -> Query a
forall a.
Semigroup a =>
a -> (a -> a -> a) -> ([a] -> a) -> Monoid a
forall a. Monoid a => Semigroup (Query a)
forall a. Monoid a => Query a
forall a. Monoid a => [Query a] -> Query a
forall a. Monoid a => Query a -> Query a -> Query a
$cmempty :: forall a. Monoid a => Query a
mempty :: Query a
$cmappend :: forall a. Monoid a => Query a -> Query a -> Query a
mappend :: Query a -> Query a -> Query a
$cmconcat :: forall a. Monoid a => [Query a] -> Query a
mconcat :: [Query a] -> Query a
Monoid) via Ap Query a
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 Default a => Default (Query a) where
def :: Query a
def = a -> Query a
forall a. a -> Query a
forall (m :: * -> *) a. Monad m => a -> m a
return a
forall a. Default a => a
def
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
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 a. a -> X a
forall (m :: * -> *) a. Monad m => a -> m a
return a
a
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 a. a -> X a
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe a
forall a. Maybe a
Nothing)
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
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 a b. X a -> (a -> X b) -> X b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= Display -> X a
f
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 a b. X a -> (a -> X b) -> X b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= WindowSet -> X a
f
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 a. a -> X a
forall (m :: * -> *) a. Monad m => a -> m a
return ())
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
getAtom :: String -> X Atom
getAtom :: FilePath -> X Window
getAtom FilePath
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 -> FilePath -> Bool -> IO Window
internAtom Display
dpy FilePath
str Bool
False
atom_WM_PROTOCOLS, atom_WM_DELETE_WINDOW, atom_WM_STATE, atom_WM_TAKE_FOCUS :: X Atom
atom_WM_PROTOCOLS :: X Window
atom_WM_PROTOCOLS = FilePath -> X Window
getAtom FilePath
"WM_PROTOCOLS"
atom_WM_DELETE_WINDOW :: X Window
atom_WM_DELETE_WINDOW = FilePath -> X Window
getAtom FilePath
"WM_DELETE_WINDOW"
atom_WM_STATE :: X Window
atom_WM_STATE = FilePath -> X Window
getAtom FilePath
"WM_STATE"
atom_WM_TAKE_FOCUS :: X Window
atom_WM_TAKE_FOCUS = FilePath -> X Window
getAtom FilePath
"WM_TAKE_FOCUS"
data Layout a = forall l. (LayoutClass l a, Read (l a)) => Layout (l a)
readsLayout :: Layout a -> String -> [(Layout a, String)]
readsLayout :: forall a. Layout a -> FilePath -> [(Layout a, FilePath)]
readsLayout (Layout l a
l) FilePath
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), FilePath
rs) | (l a
x, FilePath
rs) <- ReadS (l a)
forall a. Read a => ReadS a
reads FilePath
s]
class (Show (layout a), Typeable layout) => LayoutClass layout a where
runLayout :: Workspace WorkspaceId (layout a) a
-> Rectangle
-> X ([(a, Rectangle)], Maybe (layout a))
runLayout (Workspace FilePath
_ 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
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 a. a -> X 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)
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 :: 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 a. a -> X a
forall (m :: * -> *) a. Monad m => a -> m a
return ([], Maybe (layout a)
forall a. Maybe a
Nothing)
handleMessage :: layout a -> SomeMessage -> X (Maybe (layout a))
handleMessage layout a
l = Maybe (layout a) -> X (Maybe (layout a))
forall a. a -> X 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
pureMessage :: layout a -> SomeMessage -> Maybe (layout a)
pureMessage layout a
_ SomeMessage
_ = Maybe (layout a)
forall a. Maybe a
Nothing
description :: layout a -> String
description = layout a -> FilePath
forall a. Show a => a -> FilePath
show
instance LayoutClass Layout Window where
runLayout :: Workspace FilePath (Layout Window) Window
-> Rectangle -> X ([(Window, Rectangle)], Maybe (Layout Window))
runLayout (Workspace FilePath
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 a b.
(a -> b)
-> ([(Window, Rectangle)], a) -> ([(Window, Rectangle)], b)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ((l Window -> Layout Window)
-> Maybe (l Window) -> Maybe (Layout Window)
forall a b. (a -> b) -> Maybe a -> Maybe b
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 a b. (a -> b) -> X a -> X b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
`fmap` Workspace FilePath (l Window) Window
-> Rectangle -> X ([(Window, Rectangle)], Maybe (l Window))
forall (layout :: * -> *) a.
LayoutClass layout a =>
Workspace FilePath (layout a) a
-> Rectangle -> X ([(a, Rectangle)], Maybe (layout a))
runLayout (FilePath
-> l Window
-> Maybe (Stack Window)
-> Workspace FilePath (l Window) Window
forall i l a. i -> l -> Maybe (Stack a) -> Workspace i l a
Workspace FilePath
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 a b.
(a -> b)
-> ([(Window, Rectangle)], a) -> ([(Window, Rectangle)], b)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ((l Window -> Layout Window)
-> Maybe (l Window) -> Maybe (Layout Window)
forall a b. (a -> b) -> Maybe a -> Maybe b
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 a b. (a -> b) -> X a -> X b
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 a b.
(a -> b)
-> ([(Window, Rectangle)], a) -> ([(Window, Rectangle)], b)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ((l Window -> Layout Window)
-> Maybe (l Window) -> Maybe (Layout Window)
forall a b. (a -> b) -> Maybe a -> Maybe b
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 a b. (a -> b) -> X a -> X b
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 a b. (a -> b) -> X a -> X b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ((l Window -> Layout Window)
-> Maybe (l Window) -> Maybe (Layout Window)
forall a b. (a -> b) -> Maybe a -> Maybe b
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 -> FilePath
description (Layout l Window
l) = l Window -> FilePath
forall (layout :: * -> *) a.
LayoutClass layout a =>
layout a -> FilePath
description l Window
l
instance Show (Layout a) where show :: Layout a -> FilePath
show (Layout l a
l) = l a -> FilePath
forall a. Show a => a -> FilePath
show l a
l
class Typeable a => Message a
data SomeMessage = forall a. Message a => SomeMessage a
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
instance Message Event
data LayoutMessages = Hide
| ReleaseResources
deriving LayoutMessages -> LayoutMessages -> Bool
(LayoutMessages -> LayoutMessages -> Bool)
-> (LayoutMessages -> LayoutMessages -> Bool) -> Eq LayoutMessages
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: LayoutMessages -> LayoutMessages -> Bool
== :: LayoutMessages -> LayoutMessages -> Bool
$c/= :: LayoutMessages -> LayoutMessages -> Bool
/= :: LayoutMessages -> LayoutMessages -> Bool
Eq
instance Message LayoutMessages
class Typeable a => ExtensionClass a where
{-# MINIMAL initialValue #-}
initialValue :: a
extensionType :: a -> StateExtension
extensionType = a -> StateExtension
forall a. ExtensionClass a => a -> StateExtension
StateExtension
data StateExtension =
forall a. ExtensionClass a => StateExtension a
| forall a. (Read a, Show a, ExtensionClass a) => PersistentExtension a
data ConfExtension = forall a. Typeable a => ConfExtension a
ifM :: Monad m => m Bool -> m a -> m a -> m a
ifM :: forall (m :: * -> *) a. Monad m => m Bool -> m a -> m a -> m a
ifM m Bool
mb m a
t m a
f = m Bool
mb m Bool -> (Bool -> m a) -> m a
forall a b. m a -> (a -> m b) -> m b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \Bool
b -> if Bool
b then m a
t else m a
f
io :: MonadIO m => IO a -> m a
io :: forall (m :: * -> *) a. MonadIO m => IO a -> m a
io = IO a -> m a
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO
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 a b. IO a -> IO b -> IO b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Handle -> IO ()
hFlush Handle
stderr)
spawn :: MonadIO m => String -> m ()
spawn :: forall (m :: * -> *). MonadIO m => FilePath -> m ()
spawn FilePath
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
$ FilePath -> m ProcessID
forall (m :: * -> *). MonadIO m => FilePath -> m ProcessID
spawnPID FilePath
x
spawnPID :: MonadIO m => String -> m ProcessID
spawnPID :: forall (m :: * -> *). MonadIO m => FilePath -> m ProcessID
spawnPID FilePath
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
$ FilePath
-> Bool -> [FilePath] -> Maybe [(FilePath, FilePath)] -> IO ()
forall a.
FilePath
-> Bool -> [FilePath] -> Maybe [(FilePath, FilePath)] -> IO a
executeFile FilePath
"/bin/sh" Bool
False [FilePath
"-c", FilePath
x] Maybe [(FilePath, FilePath)]
forall a. Maybe a
Nothing
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
#if MIN_VERSION_unix(2,8,0)
Fd
fd <- FilePath -> OpenMode -> OpenFileFlags -> IO Fd
openFd FilePath
"/dev/null" OpenMode
ReadOnly OpenFileFlags
defaultFileFlags
#else
fd <- openFd "/dev/null" ReadOnly Nothing defaultFileFlags
#endif
Fd -> Fd -> IO Fd
dupTo Fd
fd Fd
stdInput
Fd -> IO ()
closeFd Fd
fd
xmessage :: MonadIO m => String -> m ()
xmessage :: forall (m :: * -> *). MonadIO m => FilePath -> m ()
xmessage FilePath
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
FilePath
xmessageBin <- FilePath -> Maybe FilePath -> FilePath
forall a. a -> Maybe a -> a
fromMaybe FilePath
"xmessage" (Maybe FilePath -> FilePath) -> IO (Maybe FilePath) -> IO FilePath
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> IO (Maybe FilePath) -> IO (Maybe FilePath)
forall a. IO a -> IO a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (FilePath -> IO (Maybe FilePath)
lookupEnv FilePath
"XMONAD_XMESSAGE")
FilePath
-> Bool -> [FilePath] -> Maybe [(FilePath, FilePath)] -> IO ()
forall a.
FilePath
-> Bool -> [FilePath] -> Maybe [(FilePath, FilePath)] -> IO a
executeFile FilePath
xmessageBin Bool
True
[ FilePath
"-default", FilePath
"okay"
, FilePath
"-xrm", FilePath
"*international:true"
, FilePath
"-xrm", FilePath
"*fontSet:-*-fixed-medium-r-normal-*-18-*-*-*-*-*-*-*,-*-fixed-*-*-*-*-18-*-*-*-*-*-*-*,-*-*-*-*-*-*-18-*-*-*-*-*-*-*"
, FilePath
msg
] Maybe [(FilePath, FilePath)]
forall a. Maybe a
Nothing
runOnWorkspaces :: (WindowSpace -> X WindowSpace) -> X ()
runOnWorkspaces :: (Workspace FilePath (Layout Window) Window
-> X (Workspace FilePath (Layout Window) Window))
-> X ()
runOnWorkspaces Workspace FilePath (Layout Window) Window
-> X (Workspace FilePath (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 FilePath (Layout Window) Window]
h <- (Workspace FilePath (Layout Window) Window
-> X (Workspace FilePath (Layout Window) Window))
-> [Workspace FilePath (Layout Window) Window]
-> X [Workspace FilePath (Layout Window) Window]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> [a] -> m [b]
mapM Workspace FilePath (Layout Window) Window
-> X (Workspace FilePath (Layout Window) Window)
job ([Workspace FilePath (Layout Window) Window]
-> X [Workspace FilePath (Layout Window) Window])
-> [Workspace FilePath (Layout Window) Window]
-> X [Workspace FilePath (Layout Window) Window]
forall a b. (a -> b) -> a -> b
$ WindowSet -> [Workspace FilePath (Layout Window) Window]
forall i l a sid sd. StackSet i l a sid sd -> [Workspace i l a]
hidden WindowSet
ws
Screen FilePath (Layout Window) Window ScreenId ScreenDetail
c:[Screen FilePath (Layout Window) Window ScreenId ScreenDetail]
v <- (Screen FilePath (Layout Window) Window ScreenId ScreenDetail
-> X (Screen
FilePath (Layout Window) Window ScreenId ScreenDetail))
-> [Screen FilePath (Layout Window) Window ScreenId ScreenDetail]
-> X [Screen FilePath (Layout Window) Window ScreenId ScreenDetail]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> [a] -> m [b]
mapM (\Screen FilePath (Layout Window) Window ScreenId ScreenDetail
s -> (\Workspace FilePath (Layout Window) Window
w -> Screen FilePath (Layout Window) Window ScreenId ScreenDetail
s { workspace = w}) (Workspace FilePath (Layout Window) Window
-> Screen FilePath (Layout Window) Window ScreenId ScreenDetail)
-> X (Workspace FilePath (Layout Window) Window)
-> X (Screen FilePath (Layout Window) Window ScreenId ScreenDetail)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Workspace FilePath (Layout Window) Window
-> X (Workspace FilePath (Layout Window) Window)
job (Screen FilePath (Layout Window) Window ScreenId ScreenDetail
-> Workspace FilePath (Layout Window) Window
forall i l a sid sd. Screen i l a sid sd -> Workspace i l a
workspace Screen FilePath (Layout Window) Window ScreenId ScreenDetail
s))
([Screen FilePath (Layout Window) Window ScreenId ScreenDetail]
-> X [Screen
FilePath (Layout Window) Window ScreenId ScreenDetail])
-> [Screen FilePath (Layout Window) Window ScreenId ScreenDetail]
-> X [Screen FilePath (Layout Window) Window ScreenId ScreenDetail]
forall a b. (a -> b) -> a -> b
$ WindowSet
-> Screen FilePath (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 FilePath (Layout Window) Window ScreenId ScreenDetail
-> [Screen FilePath (Layout Window) Window ScreenId ScreenDetail]
-> [Screen FilePath (Layout Window) Window ScreenId ScreenDetail]
forall a. a -> [a] -> [a]
: WindowSet
-> [Screen FilePath (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 = ws { current = c, visible = v, hidden = h } }
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 -> FilePath
(Int -> Directories' a -> ShowS)
-> (Directories' a -> FilePath)
-> ([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 -> FilePath
forall a.
(Int -> a -> ShowS) -> (a -> FilePath) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: forall a. Show a => Int -> Directories' a -> ShowS
showsPrec :: Int -> Directories' a -> ShowS
$cshow :: forall a. Show a => Directories' a -> FilePath
show :: Directories' a -> FilePath
$cshowList :: forall a. Show a => [Directories' a] -> ShowS
showList :: [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
$cfmap :: forall a b. (a -> b) -> Directories' a -> Directories' b
fmap :: forall a b. (a -> b) -> Directories' a -> Directories' b
$c<$ :: forall a b. a -> Directories' b -> Directories' a
<$ :: forall a b. a -> Directories' b -> Directories' a
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
$cfold :: forall m. Monoid m => Directories' m -> m
fold :: forall m. Monoid m => Directories' m -> 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
foldMap' :: forall m a. Monoid m => (a -> m) -> Directories' a -> m
$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
foldr' :: forall a b. (a -> b -> 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
foldl' :: forall b a. (b -> a -> b) -> b -> Directories' a -> b
$cfoldr1 :: forall a. (a -> a -> a) -> Directories' a -> a
foldr1 :: forall a. (a -> a -> a) -> Directories' a -> a
$cfoldl1 :: forall a. (a -> a -> a) -> Directories' a -> a
foldl1 :: forall a. (a -> a -> a) -> Directories' a -> a
$ctoList :: forall a. Directories' a -> [a]
toList :: forall a. Directories' a -> [a]
$cnull :: forall a. Directories' a -> Bool
null :: forall a. Directories' a -> Bool
$clength :: forall a. Directories' a -> Int
length :: forall a. Directories' a -> Int
$celem :: forall a. Eq a => a -> Directories' a -> Bool
elem :: forall a. Eq a => a -> Directories' a -> Bool
$cmaximum :: forall a. Ord a => Directories' a -> a
maximum :: forall a. Ord a => Directories' a -> a
$cminimum :: forall a. Ord a => Directories' a -> a
minimum :: forall a. Ord a => Directories' a -> a
$csum :: forall a. Num a => Directories' a -> a
sum :: forall a. Num a => Directories' a -> a
$cproduct :: forall a. Num a => Directories' a -> a
product :: forall a. Num a => Directories' a -> a
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)
$ctraverse :: forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> Directories' a -> f (Directories' b)
traverse :: forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> Directories' a -> f (Directories' b)
$csequenceA :: forall (f :: * -> *) a.
Applicative f =>
Directories' (f a) -> f (Directories' a)
sequenceA :: forall (f :: * -> *) a.
Applicative f =>
Directories' (f a) -> f (Directories' a)
$cmapM :: forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> Directories' a -> m (Directories' b)
mapM :: forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> Directories' a -> m (Directories' b)
$csequence :: forall (m :: * -> *) a.
Monad m =>
Directories' (m a) -> m (Directories' a)
sequence :: forall (m :: * -> *) a.
Monad m =>
Directories' (m a) -> m (Directories' a)
Traversable)
type Directories = Directories' FilePath
getDirectories :: IO Directories
getDirectories :: IO Directories
getDirectories = IO Directories
xmEnvDirs IO Directories -> IO Directories -> IO Directories
forall a. IO a -> IO a -> IO a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> IO Directories
xmDirs IO Directories -> IO Directories -> IO Directories
forall a. IO a -> IO a -> IO a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> IO Directories
xdgDirs
where
xmEnvDirs :: IO Directories
xmEnvDirs :: IO Directories
xmEnvDirs = do
let xmEnvs :: Directories
xmEnvs = Directories{ dataDir :: FilePath
dataDir = FilePath
"XMONAD_DATA_DIR"
, cfgDir :: FilePath
cfgDir = FilePath
"XMONAD_CONFIG_DIR"
, cacheDir :: FilePath
cacheDir = FilePath
"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 a. IO a
forall (f :: * -> *) a. Alternative f => f a
empty Directories -> IO Directories
forall a. a -> IO a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Maybe Directories -> IO Directories)
-> (Directories' (Maybe FilePath) -> Maybe Directories)
-> Directories' (Maybe FilePath)
-> IO Directories
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Directories' (Maybe FilePath) -> Maybe Directories
forall (t :: * -> *) (f :: * -> *) a.
(Traversable t, Applicative f) =>
t (f a) -> f (t a)
forall (f :: * -> *) a.
Applicative f =>
Directories' (f a) -> f (Directories' a)
sequenceA (Directories' (Maybe FilePath) -> IO Directories)
-> IO (Directories' (Maybe FilePath)) -> IO Directories
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< (FilePath -> IO (Maybe FilePath))
-> Directories -> IO (Directories' (Maybe FilePath))
forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
(a -> f b) -> t a -> f (t b)
forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> Directories' a -> f (Directories' b)
traverse FilePath -> IO (Maybe FilePath)
getEnv Directories
xmEnvs
xmDirs :: IO Directories
xmDirs :: IO Directories
xmDirs = do
FilePath
xmDir <- FilePath -> IO FilePath
getAppUserDataDirectory FilePath
"xmonad"
Bool
conf <- FilePath -> IO Bool
doesFileExist (FilePath -> IO Bool) -> FilePath -> IO Bool
forall a b. (a -> b) -> a -> b
$ FilePath
xmDir FilePath -> ShowS
</> FilePath
"xmonad.hs"
Bool
build <- FilePath -> IO Bool
doesFileExist (FilePath -> IO Bool) -> FilePath -> IO Bool
forall a b. (a -> b) -> a -> b
$ FilePath
xmDir FilePath -> ShowS
</> FilePath
"build"
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 a. a -> IO a
forall (f :: * -> *) a. Applicative f => a -> f a
pure Directories{ dataDir :: FilePath
dataDir = FilePath
xmDir, cfgDir :: FilePath
cfgDir = FilePath
xmDir, cacheDir :: FilePath
cacheDir = FilePath
xmDir }
xdgDirs :: IO Directories
xdgDirs :: IO Directories
xdgDirs =
Directories' XdgDirectory
-> (XdgDirectory -> IO FilePath) -> IO Directories
forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
t a -> (a -> f b) -> f (t b)
for Directories{ dataDir :: XdgDirectory
dataDir = XdgDirectory
XdgData, cfgDir :: XdgDirectory
cfgDir = XdgDirectory
XdgConfig, cacheDir :: XdgDirectory
cacheDir = XdgDirectory
XdgCache }
((XdgDirectory -> IO FilePath) -> IO Directories)
-> (XdgDirectory -> IO FilePath) -> IO Directories
forall a b. (a -> b) -> a -> b
$ \XdgDirectory
dir -> do FilePath
d <- XdgDirectory -> FilePath -> IO FilePath
getXdgDirectory XdgDirectory
dir FilePath
"xmonad"
FilePath
d FilePath -> IO () -> IO FilePath
forall a b. a -> IO b -> IO a
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ Bool -> FilePath -> IO ()
createDirectoryIfMissing Bool
True FilePath
d
getXMonadDir :: X String
getXMonadDir :: X FilePath
getXMonadDir = (XConf -> FilePath) -> X FilePath
forall r (m :: * -> *) a. MonadReader r m => (r -> a) -> m a
asks (Directories -> FilePath
forall a. Directories' a -> a
cfgDir (Directories -> FilePath)
-> (XConf -> Directories) -> XConf -> FilePath
forall b c a. (b -> c) -> (a -> b) -> a -> c
. XConf -> Directories
directories)
{-# DEPRECATED getXMonadDir "Use `asks (cfgDir . directories)' instead." #-}
getXMonadCacheDir :: X String
getXMonadCacheDir :: X FilePath
getXMonadCacheDir = (XConf -> FilePath) -> X FilePath
forall r (m :: * -> *) a. MonadReader r m => (r -> a) -> m a
asks (Directories -> FilePath
forall a. Directories' a -> a
cacheDir (Directories -> FilePath)
-> (XConf -> Directories) -> XConf -> FilePath
forall b c a. (b -> c) -> (a -> b) -> a -> c
. XConf -> Directories
directories)
{-# DEPRECATED getXMonadCacheDir "Use `asks (cacheDir . directories)' instead." #-}
getXMonadDataDir :: X String
getXMonadDataDir :: X FilePath
getXMonadDataDir = (XConf -> FilePath) -> X FilePath
forall r (m :: * -> *) a. MonadReader r m => (r -> a) -> m a
asks (Directories -> FilePath
forall a. Directories' a -> a
dataDir (Directories -> FilePath)
-> (XConf -> Directories) -> XConf -> FilePath
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 -> FilePath
binFileName Directories{ FilePath
cacheDir :: forall a. Directories' a -> a
cacheDir :: FilePath
cacheDir } = FilePath
cacheDir FilePath -> ShowS
</> FilePath
"xmonad-" FilePath -> ShowS
forall a. Semigroup a => a -> a -> a
<> FilePath
arch FilePath -> ShowS
forall a. Semigroup a => a -> a -> a
<> FilePath
"-" FilePath -> ShowS
forall a. Semigroup a => a -> a -> a
<> FilePath
os
buildDirName :: Directories -> FilePath
buildDirName Directories{ FilePath
cacheDir :: forall a. Directories' a -> a
cacheDir :: FilePath
cacheDir } = FilePath
cacheDir FilePath -> ShowS
</> FilePath
"build-" FilePath -> ShowS
forall a. Semigroup a => a -> a -> a
<> FilePath
arch FilePath -> ShowS
forall a. Semigroup a => a -> a -> a
<> FilePath
"-" FilePath -> ShowS
forall a. Semigroup a => a -> a -> a
<> FilePath
os
errFileName, stateFileName :: Directories -> FilePath
errFileName :: Directories -> FilePath
errFileName Directories{ FilePath
dataDir :: forall a. Directories' a -> a
dataDir :: FilePath
dataDir } = FilePath
dataDir FilePath -> ShowS
</> FilePath
"xmonad.errors"
stateFileName :: Directories -> FilePath
stateFileName Directories{ FilePath
dataDir :: forall a. Directories' a -> a
dataDir :: FilePath
dataDir } = FilePath
dataDir FilePath -> ShowS
</> FilePath
"xmonad.state"
srcFileName, libFileName :: Directories -> FilePath
srcFileName :: Directories -> FilePath
srcFileName Directories{ FilePath
cfgDir :: forall a. Directories' a -> a
cfgDir :: FilePath
cfgDir } = FilePath
cfgDir FilePath -> ShowS
</> FilePath
"xmonad.hs"
libFileName :: Directories -> FilePath
libFileName Directories{ FilePath
cfgDir :: forall a. Directories' a -> a
cfgDir :: FilePath
cfgDir } = FilePath
cfgDir FilePath -> ShowS
</> FilePath
"lib"
buildScriptFileName, stackYamlFileName, nixFlakeFileName, nixDefaultFileName :: Directories -> FilePath
buildScriptFileName :: Directories -> FilePath
buildScriptFileName Directories{ FilePath
cfgDir :: forall a. Directories' a -> a
cfgDir :: FilePath
cfgDir } = FilePath
cfgDir FilePath -> ShowS
</> FilePath
"build"
stackYamlFileName :: Directories -> FilePath
stackYamlFileName Directories{ FilePath
cfgDir :: forall a. Directories' a -> a
cfgDir :: FilePath
cfgDir } = FilePath
cfgDir FilePath -> ShowS
</> FilePath
"stack.yaml"
nixFlakeFileName :: Directories -> FilePath
nixFlakeFileName Directories{ FilePath
cfgDir :: forall a. Directories' a -> a
cfgDir :: FilePath
cfgDir } = FilePath
cfgDir FilePath -> ShowS
</> FilePath
"flake.nix"
nixDefaultFileName :: Directories -> FilePath
nixDefaultFileName Directories{ FilePath
cfgDir :: forall a. Directories' a -> a
cfgDir :: FilePath
cfgDir } = FilePath
cfgDir FilePath -> ShowS
</> FilePath
"default.nix"
data Compile
= CompileGhc
| CompileStackGhc FilePath
| CompileNixFlake
| CompileNixDefault
| CompileScript FilePath
deriving (Int -> Compile -> ShowS
[Compile] -> ShowS
Compile -> FilePath
(Int -> Compile -> ShowS)
-> (Compile -> FilePath) -> ([Compile] -> ShowS) -> Show Compile
forall a.
(Int -> a -> ShowS) -> (a -> FilePath) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Compile -> ShowS
showsPrec :: Int -> Compile -> ShowS
$cshow :: Compile -> FilePath
show :: Compile -> FilePath
$cshowList :: [Compile] -> ShowS
showList :: [Compile] -> ShowS
Show)
detectCompile :: Directories -> IO Compile
detectCompile :: Directories -> IO Compile
detectCompile Directories
dirs =
IO Compile
tryScript IO Compile -> IO Compile -> IO Compile
forall a. IO a -> IO a -> IO a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> IO Compile
tryStack IO Compile -> IO Compile -> IO Compile
forall a. IO a -> IO a -> IO a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> IO Compile
tryNixFlake IO Compile -> IO Compile -> IO Compile
forall a. IO a -> IO a -> IO a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> IO Compile
tryNixDefault IO Compile -> IO Compile -> IO Compile
forall a. IO a -> IO a -> IO a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> IO Compile
useGhc
where
buildScript :: FilePath
buildScript = Directories -> FilePath
buildScriptFileName Directories
dirs
stackYaml :: FilePath
stackYaml = Directories -> FilePath
stackYamlFileName Directories
dirs
flakeNix :: FilePath
flakeNix = Directories -> FilePath
nixFlakeFileName Directories
dirs
defaultNix :: FilePath
defaultNix = Directories -> FilePath
nixDefaultFileName 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
=<< FilePath -> IO Bool
doesFileExist FilePath
buildScript
Bool
isExe <- FilePath -> IO Bool
isExecutable FilePath
buildScript
if Bool
isExe
then do
FilePath -> IO ()
forall (m :: * -> *). MonadIO m => FilePath -> m ()
trace (FilePath -> IO ()) -> FilePath -> IO ()
forall a b. (a -> b) -> a -> b
$ FilePath
"XMonad will use build script at " FilePath -> ShowS
forall a. Semigroup a => a -> a -> a
<> ShowS
forall a. Show a => a -> FilePath
show FilePath
buildScript FilePath -> ShowS
forall a. Semigroup a => a -> a -> a
<> FilePath
" to recompile."
Compile -> IO Compile
forall a. a -> IO a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Compile -> IO Compile) -> Compile -> IO Compile
forall a b. (a -> b) -> a -> b
$ FilePath -> Compile
CompileScript FilePath
buildScript
else do
FilePath -> IO ()
forall (m :: * -> *). MonadIO m => FilePath -> m ()
trace (FilePath -> IO ()) -> FilePath -> IO ()
forall a b. (a -> b) -> a -> b
$ FilePath
"XMonad will not use build script, because " FilePath -> ShowS
forall a. Semigroup a => a -> a -> a
<> ShowS
forall a. Show a => a -> FilePath
show FilePath
buildScript FilePath -> ShowS
forall a. Semigroup a => a -> a -> a
<> FilePath
" is not executable."
FilePath -> IO ()
forall (m :: * -> *). MonadIO m => FilePath -> m ()
trace (FilePath -> IO ()) -> FilePath -> IO ()
forall a b. (a -> b) -> a -> b
$ FilePath
"Suggested resolution to use it: chmod u+x " FilePath -> ShowS
forall a. Semigroup a => a -> a -> a
<> ShowS
forall a. Show a => a -> FilePath
show FilePath
buildScript
IO Compile
forall a. IO a
forall (f :: * -> *) a. Alternative f => f a
empty
tryNixFlake :: IO Compile
tryNixFlake = 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
=<< FilePath -> IO Bool
doesFileExist FilePath
flakeNix
FilePath
canonNixFlake <- FilePath -> IO FilePath
canonicalizePath FilePath
flakeNix
FilePath -> IO ()
forall (m :: * -> *). MonadIO m => FilePath -> m ()
trace (FilePath -> IO ()) -> FilePath -> IO ()
forall a b. (a -> b) -> a -> b
$ FilePath
"XMonad will use nix flake at " FilePath -> ShowS
forall a. Semigroup a => a -> a -> a
<> ShowS
forall a. Show a => a -> FilePath
show FilePath
canonNixFlake FilePath -> ShowS
forall a. Semigroup a => a -> a -> a
<> FilePath
" to recompile"
Compile -> IO Compile
forall a. a -> IO a
forall (f :: * -> *) a. Applicative f => a -> f a
pure Compile
CompileNixFlake
tryNixDefault :: IO Compile
tryNixDefault = 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
=<< FilePath -> IO Bool
doesFileExist FilePath
defaultNix
FilePath
canonNixDefault <- FilePath -> IO FilePath
canonicalizePath FilePath
defaultNix
FilePath -> IO ()
forall (m :: * -> *). MonadIO m => FilePath -> m ()
trace (FilePath -> IO ()) -> FilePath -> IO ()
forall a b. (a -> b) -> a -> b
$ FilePath
"XMonad will use nix file at " FilePath -> ShowS
forall a. Semigroup a => a -> a -> a
<> ShowS
forall a. Show a => a -> FilePath
show FilePath
canonNixDefault FilePath -> ShowS
forall a. Semigroup a => a -> a -> a
<> FilePath
" to recompile"
Compile -> IO Compile
forall a. a -> IO a
forall (f :: * -> *) a. Applicative f => a -> f a
pure Compile
CompileNixDefault
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
=<< FilePath -> IO Bool
doesFileExist FilePath
stackYaml
FilePath
canonStackYaml <- FilePath -> IO FilePath
canonicalizePath FilePath
stackYaml
FilePath -> IO ()
forall (m :: * -> *). MonadIO m => FilePath -> m ()
trace (FilePath -> IO ()) -> FilePath -> IO ()
forall a b. (a -> b) -> a -> b
$ FilePath
"XMonad will use stack ghc --stack-yaml " FilePath -> ShowS
forall a. Semigroup a => a -> a -> a
<> ShowS
forall a. Show a => a -> FilePath
show FilePath
canonStackYaml FilePath -> ShowS
forall a. Semigroup a => a -> a -> a
<> FilePath
" to recompile."
Compile -> IO Compile
forall a. a -> IO a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Compile -> IO Compile) -> Compile -> IO Compile
forall a b. (a -> b) -> a -> b
$ FilePath -> Compile
CompileStackGhc FilePath
canonStackYaml
useGhc :: IO Compile
useGhc = do
FilePath -> IO ()
forall (m :: * -> *). MonadIO m => FilePath -> m ()
trace (FilePath -> IO ()) -> FilePath -> IO ()
forall a b. (a -> b) -> a -> b
$ FilePath
"XMonad will use ghc to recompile, because none of "
FilePath -> ShowS
forall a. Semigroup a => a -> a -> a
<> FilePath -> [FilePath] -> FilePath
forall a. [a] -> [[a]] -> [a]
intercalate FilePath
", "
[ ShowS
forall a. Show a => a -> FilePath
show FilePath
buildScript
, ShowS
forall a. Show a => a -> FilePath
show FilePath
stackYaml
, ShowS
forall a. Show a => a -> FilePath
show FilePath
flakeNix
, ShowS
forall a. Show a => a -> FilePath
show FilePath
defaultNix
] FilePath -> ShowS
forall a. Semigroup a => a -> a -> a
<> FilePath
" exist."
Compile -> IO Compile
forall a. a -> IO a
forall (f :: * -> *) a. Applicative f => a -> f a
pure Compile
CompileGhc
isExecutable :: FilePath -> IO Bool
isExecutable :: FilePath -> IO Bool
isExecutable FilePath
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
<$> FilePath -> IO Permissions
getPermissions FilePath
f) (\(SomeException e
_) -> Bool -> IO Bool
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
False)
shouldCompile :: Directories -> Compile -> IO Bool
shouldCompile :: Directories -> Compile -> IO Bool
shouldCompile Directories
dirs Compile
CompileGhc = do
[Maybe UTCTime]
libTs <- (FilePath -> IO (Maybe UTCTime))
-> [FilePath] -> IO [Maybe UTCTime]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> [a] -> m [b]
mapM FilePath -> IO (Maybe UTCTime)
getModTime ([FilePath] -> IO [Maybe UTCTime])
-> ([FilePath] -> [FilePath]) -> [FilePath] -> IO [Maybe UTCTime]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (FilePath -> Bool) -> [FilePath] -> [FilePath]
forall a. (a -> Bool) -> [a] -> [a]
Prelude.filter FilePath -> Bool
isSource ([FilePath] -> IO [Maybe UTCTime])
-> IO [FilePath] -> IO [Maybe UTCTime]
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< FilePath -> IO [FilePath]
allFiles (Directories -> FilePath
libFileName Directories
dirs)
Maybe UTCTime
srcT <- FilePath -> IO (Maybe UTCTime)
getModTime (Directories -> FilePath
srcFileName Directories
dirs)
Maybe UTCTime
binT <- FilePath -> IO (Maybe UTCTime)
getModTime (Directories -> FilePath
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 a b. a -> IO b -> IO a
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ FilePath -> IO ()
forall (m :: * -> *). MonadIO m => FilePath -> m ()
trace FilePath
"XMonad recompiling because some files have changed."
else Bool
False Bool -> IO () -> IO Bool
forall a b. a -> IO b -> IO a
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ FilePath -> IO ()
forall (m :: * -> *). MonadIO m => FilePath -> m ()
trace FilePath
"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 :: FilePath -> Bool
isSource = (FilePath -> [FilePath] -> Bool) -> [FilePath] -> FilePath -> Bool
forall a b c. (a -> b -> c) -> b -> a -> c
flip FilePath -> [FilePath] -> Bool
forall a. Eq a => a -> [a] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
elem [FilePath
".hs",FilePath
".lhs",FilePath
".hsc"] (FilePath -> Bool) -> ShowS -> FilePath -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ShowS
takeExtension
allFiles :: FilePath -> IO [FilePath]
allFiles FilePath
t = do
let prep :: [FilePath] -> [FilePath]
prep = ShowS -> [FilePath] -> [FilePath]
forall a b. (a -> b) -> [a] -> [b]
map (FilePath
tFilePath -> ShowS
</>) ([FilePath] -> [FilePath])
-> ([FilePath] -> [FilePath]) -> [FilePath] -> [FilePath]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (FilePath -> Bool) -> [FilePath] -> [FilePath]
forall a. (a -> Bool) -> [a] -> [a]
Prelude.filter (FilePath -> [FilePath] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`notElem` [FilePath
".",FilePath
".."])
[FilePath]
cs <- [FilePath] -> [FilePath]
prep ([FilePath] -> [FilePath]) -> IO [FilePath] -> IO [FilePath]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> IO [FilePath] -> (SomeException -> IO [FilePath]) -> IO [FilePath]
forall e a. Exception e => IO a -> (e -> IO a) -> IO a
E.catch (FilePath -> IO [FilePath]
getDirectoryContents FilePath
t) (\(SomeException e
_) -> [FilePath] -> IO [FilePath]
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return [])
[FilePath]
ds <- (FilePath -> IO Bool) -> [FilePath] -> IO [FilePath]
forall (m :: * -> *) a.
Applicative m =>
(a -> m Bool) -> [a] -> m [a]
filterM FilePath -> IO Bool
doesDirectoryExist [FilePath]
cs
[[FilePath]] -> [FilePath]
forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat ([[FilePath]] -> [FilePath])
-> ([[FilePath]] -> [[FilePath]]) -> [[FilePath]] -> [FilePath]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (([FilePath]
cs [FilePath] -> [FilePath] -> [FilePath]
forall a. Eq a => [a] -> [a] -> [a]
\\ [FilePath]
ds)[FilePath] -> [[FilePath]] -> [[FilePath]]
forall a. a -> [a] -> [a]
:) ([[FilePath]] -> [FilePath]) -> IO [[FilePath]] -> IO [FilePath]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (FilePath -> IO [FilePath]) -> [FilePath] -> IO [[FilePath]]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> [a] -> m [b]
mapM FilePath -> IO [FilePath]
allFiles [FilePath]
ds
shouldCompile Directories
dirs CompileStackGhc{} = do
Maybe UTCTime
stackYamlT <- FilePath -> IO (Maybe UTCTime)
getModTime (Directories -> FilePath
stackYamlFileName Directories
dirs)
Maybe UTCTime
binT <- FilePath -> IO (Maybe UTCTime)
getModTime (Directories -> FilePath
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 a b. a -> IO b -> IO a
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ FilePath -> IO ()
forall (m :: * -> *). MonadIO m => FilePath -> m ()
trace FilePath
"XMonad recompiling because some files have changed."
else Directories -> Compile -> IO Bool
shouldCompile Directories
dirs Compile
CompileGhc
shouldCompile Directories
_dirs CompileNixFlake{} = Bool
True Bool -> IO () -> IO Bool
forall a b. a -> IO b -> IO a
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ FilePath -> IO ()
forall (m :: * -> *). MonadIO m => FilePath -> m ()
trace FilePath
"XMonad recompiling because flake recompilation is being used."
shouldCompile Directories
_dirs CompileNixDefault{} = Bool
True Bool -> IO () -> IO Bool
forall a b. a -> IO b -> IO a
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ FilePath -> IO ()
forall (m :: * -> *). MonadIO m => FilePath -> m ()
trace FilePath
"XMonad recompiling because nix recompilation is being used."
shouldCompile Directories
_dirs CompileScript{} =
Bool
True Bool -> IO () -> IO Bool
forall a b. a -> IO b -> IO a
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ FilePath -> IO ()
forall (m :: * -> *). MonadIO m => FilePath -> m ()
trace FilePath
"XMonad recompiling because a custom build script is being used."
getModTime :: FilePath -> IO (Maybe UTCTime)
getModTime :: FilePath -> IO (Maybe UTCTime)
getModTime FilePath
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
<$> FilePath -> IO UTCTime
getModificationTime FilePath
f) (\(SomeException e
_) -> Maybe UTCTime -> IO (Maybe UTCTime)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe UTCTime
forall a. Maybe a
Nothing)
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
$
FilePath -> IOMode -> (Handle -> IO ExitCode) -> IO ExitCode
forall r. FilePath -> IOMode -> (Handle -> IO r) -> IO r
withFile (Directories -> FilePath
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 :: FilePath -> [FilePath] -> IO ExitCode
run = FilePath -> Handle -> FilePath -> [FilePath] -> IO ExitCode
runProc (Directories -> FilePath
forall a. Directories' a -> a
cfgDir Directories
dirs) Handle
err
case Compile
method of
Compile
CompileGhc -> do
FilePath
ghc <- FilePath -> Maybe FilePath -> FilePath
forall a. a -> Maybe a -> a
fromMaybe FilePath
"ghc" (Maybe FilePath -> FilePath) -> IO (Maybe FilePath) -> IO FilePath
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> FilePath -> IO (Maybe FilePath)
lookupEnv FilePath
"XMONAD_GHC"
FilePath -> [FilePath] -> IO ExitCode
run FilePath
ghc [FilePath]
ghcArgs
CompileStackGhc FilePath
stackYaml ->
FilePath -> [FilePath] -> IO ExitCode
run FilePath
"stack" [FilePath
"build", FilePath
"--silent", FilePath
"--stack-yaml", FilePath
stackYaml] IO ExitCode -> IO ExitCode -> IO ExitCode
forall {m :: * -> *}.
Monad m =>
m ExitCode -> m ExitCode -> m ExitCode
.&&.
FilePath -> [FilePath] -> IO ExitCode
run FilePath
"stack" (FilePath
"ghc" FilePath -> [FilePath] -> [FilePath]
forall a. a -> [a] -> [a]
: FilePath
"--stack-yaml" FilePath -> [FilePath] -> [FilePath]
forall a. a -> [a] -> [a]
: FilePath
stackYaml FilePath -> [FilePath] -> [FilePath]
forall a. a -> [a] -> [a]
: FilePath
"--" FilePath -> [FilePath] -> [FilePath]
forall a. a -> [a] -> [a]
: [FilePath]
ghcArgs)
Compile
CompileNixFlake ->
FilePath -> [FilePath] -> IO ExitCode
run FilePath
"nix" [FilePath
"build"] IO ExitCode -> (ExitCode -> IO ExitCode) -> IO ExitCode
forall a b. IO a -> (a -> IO b) -> IO b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= ExitCode -> IO ExitCode
andCopyFromResultDir
Compile
CompileNixDefault ->
FilePath -> [FilePath] -> IO ExitCode
run FilePath
"nix-build" [] IO ExitCode -> (ExitCode -> IO ExitCode) -> IO ExitCode
forall a b. IO a -> (a -> IO b) -> IO b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= ExitCode -> IO ExitCode
andCopyFromResultDir
CompileScript FilePath
script ->
FilePath -> [FilePath] -> IO ExitCode
run FilePath
script [Directories -> FilePath
binFileName Directories
dirs]
where
ghcArgs :: [FilePath]
ghcArgs = [ FilePath
"--make"
, FilePath
"xmonad.hs"
, FilePath
"-i"
, FilePath
"-ilib"
, FilePath
"-fforce-recomp"
, FilePath
"-main-is", FilePath
"main"
, FilePath
"-v0"
, FilePath
"-outputdir", Directories -> FilePath
buildDirName Directories
dirs
, FilePath
"-o", Directories -> FilePath
binFileName Directories
dirs
]
andCopyFromResultDir :: ExitCode -> IO ExitCode
andCopyFromResultDir ExitCode
exitCode = do
if ExitCode
exitCode ExitCode -> ExitCode -> Bool
forall a. Eq a => a -> a -> Bool
== ExitCode
ExitSuccess then IO ExitCode
copyFromResultDir else ExitCode -> IO ExitCode
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ExitCode
exitCode
findM :: (a -> m Bool) -> t a -> m (Maybe a)
findM a -> m Bool
p = (a -> m (Maybe a) -> m (Maybe a))
-> m (Maybe a) -> t a -> m (Maybe a)
forall a b. (a -> b -> b) -> b -> t a -> b
forall (t :: * -> *) a b.
Foldable t =>
(a -> b -> b) -> b -> t a -> b
foldr (\a
x -> m Bool -> m (Maybe a) -> m (Maybe a) -> m (Maybe a)
forall (m :: * -> *) a. Monad m => m Bool -> m a -> m a -> m a
ifM (a -> m Bool
p a
x) (Maybe a -> m (Maybe a)
forall a. a -> m a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Maybe a -> m (Maybe a)) -> Maybe a -> m (Maybe a)
forall a b. (a -> b) -> a -> b
$ a -> Maybe a
forall a. a -> Maybe a
Just a
x)) (Maybe a -> m (Maybe a)
forall a. a -> m a
forall (f :: * -> *) a. Applicative f => a -> f a
pure Maybe a
forall a. Maybe a
Nothing)
catchAny :: IO a -> (SomeException -> IO a) -> IO a
catchAny :: forall a. IO a -> (SomeException -> IO a) -> IO a
catchAny = IO a -> (SomeException -> IO a) -> IO a
forall e a. Exception e => IO a -> (e -> IO a) -> IO a
E.catch
copyFromResultDir :: IO ExitCode
copyFromResultDir = do
let binaryDirectory :: FilePath
binaryDirectory = Directories -> FilePath
forall a. Directories' a -> a
cfgDir Directories
dirs FilePath -> ShowS
</> FilePath
"result" FilePath -> ShowS
</> FilePath
"bin"
[FilePath]
binFiles <- ShowS -> [FilePath] -> [FilePath]
forall a b. (a -> b) -> [a] -> [b]
map (FilePath
binaryDirectory FilePath -> ShowS
</>) ([FilePath] -> [FilePath]) -> IO [FilePath] -> IO [FilePath]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> IO [FilePath] -> (SomeException -> IO [FilePath]) -> IO [FilePath]
forall a. IO a -> (SomeException -> IO a) -> IO a
catchAny (FilePath -> IO [FilePath]
listDirectory FilePath
binaryDirectory) (\SomeException
_ -> [FilePath] -> IO [FilePath]
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return [])
Maybe FilePath
mfilepath <- (FilePath -> IO Bool) -> [FilePath] -> IO (Maybe FilePath)
forall {t :: * -> *} {m :: * -> *} {a}.
(Foldable t, Monad m) =>
(a -> m Bool) -> t a -> m (Maybe a)
findM FilePath -> IO Bool
isExecutable [FilePath]
binFiles
case Maybe FilePath
mfilepath of
Just FilePath
filepath -> FilePath -> FilePath -> IO ()
copyFile FilePath
filepath (Directories -> FilePath
binFileName Directories
dirs) IO () -> IO ExitCode -> IO ExitCode
forall a b. IO a -> IO b -> IO b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> ExitCode -> IO ExitCode
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ExitCode
ExitSuccess
Maybe FilePath
Nothing -> ExitCode -> IO ExitCode
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (ExitCode -> IO ExitCode) -> ExitCode -> IO ExitCode
forall a b. (a -> b) -> a -> b
$ Int -> ExitCode
ExitFailure Int
1
runProc :: FilePath -> Handle -> FilePath -> [FilePath] -> IO ExitCode
runProc FilePath
cwd Handle
err FilePath
exe [FilePath]
args = do
Handle -> FilePath -> IO ()
hPutStrLn Handle
err (FilePath -> IO ()) -> FilePath -> IO ()
forall a b. (a -> b) -> a -> b
$ [FilePath] -> FilePath
unwords ([FilePath] -> FilePath) -> [FilePath] -> FilePath
forall a b. (a -> b) -> a -> b
$ FilePath
"$" FilePath -> [FilePath] -> [FilePath]
forall a. a -> [a] -> [a]
: FilePath
exe FilePath -> [FilePath] -> [FilePath]
forall a. a -> [a] -> [a]
: [FilePath]
args
Handle -> IO ()
hFlush Handle
err
(Maybe Handle
_, Maybe Handle
_, Maybe Handle
_, ProcessHandle
h) <- FilePath
-> CreateProcess
-> IO (Maybe Handle, Maybe Handle, Maybe Handle, ProcessHandle)
createProcess_ FilePath
"runProc" (FilePath -> [FilePath] -> CreateProcess
proc FilePath
exe [FilePath]
args){ cwd = Just cwd, std_err = UseHandle 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 a b. m a -> (a -> m b) -> m b
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 a. a -> m a
forall (f :: * -> *) a. Applicative f => a -> f a
pure ExitCode
e
checkCompileWarnings :: Directories -> IO ()
checkCompileWarnings :: Directories -> IO ()
checkCompileWarnings Directories
dirs = do
FilePath
ghcErr <- FilePath -> IO FilePath
readFile (Directories -> FilePath
errFileName Directories
dirs)
if FilePath
"-Wdeprecations" FilePath -> FilePath -> Bool
forall a. Eq a => [a] -> [a] -> Bool
`isInfixOf` FilePath
ghcErr
then do
let msg :: FilePath
msg = [FilePath] -> FilePath
unlines ([FilePath] -> FilePath) -> [FilePath] -> FilePath
forall a b. (a -> b) -> a -> b
$
[FilePath
"Deprecations detected while compiling xmonad config: " FilePath -> ShowS
forall a. Semigroup a => a -> a -> a
<> Directories -> FilePath
srcFileName Directories
dirs]
[FilePath] -> [FilePath] -> [FilePath]
forall a. [a] -> [a] -> [a]
++ FilePath -> [FilePath]
lines FilePath
ghcErr
[FilePath] -> [FilePath] -> [FilePath]
forall a. [a] -> [a] -> [a]
++ [FilePath
"",FilePath
"Please correct them or silence using {-# OPTIONS_GHC -Wno-deprecations #-}."]
FilePath -> IO ()
forall (m :: * -> *). MonadIO m => FilePath -> m ()
trace FilePath
msg
FilePath -> IO ()
forall (m :: * -> *). MonadIO m => FilePath -> m ()
xmessage FilePath
msg
else
FilePath -> IO ()
forall (m :: * -> *). MonadIO m => FilePath -> m ()
trace FilePath
"XMonad recompilation process exited with success!"
compileFailed :: Directories -> ExitCode -> IO ()
compileFailed :: Directories -> ExitCode -> IO ()
compileFailed Directories
dirs ExitCode
status = do
FilePath
ghcErr <- FilePath -> IO FilePath
readFile (Directories -> FilePath
errFileName Directories
dirs)
let msg :: FilePath
msg = [FilePath] -> FilePath
unlines ([FilePath] -> FilePath) -> [FilePath] -> FilePath
forall a b. (a -> b) -> a -> b
$
[FilePath
"Errors detected while compiling xmonad config: " FilePath -> ShowS
forall a. Semigroup a => a -> a -> a
<> Directories -> FilePath
srcFileName Directories
dirs]
[FilePath] -> [FilePath] -> [FilePath]
forall a. [a] -> [a] -> [a]
++ FilePath -> [FilePath]
lines (if FilePath -> Bool
forall a. [a] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null FilePath
ghcErr then ExitCode -> FilePath
forall a. Show a => a -> FilePath
show ExitCode
status else FilePath
ghcErr)
[FilePath] -> [FilePath] -> [FilePath]
forall a. [a] -> [a] -> [a]
++ [FilePath
"",FilePath
"Please check the file for errors."]
FilePath -> IO ()
forall (m :: * -> *). MonadIO m => FilePath -> m ()
trace FilePath
msg
FilePath -> IO ()
forall (m :: * -> *). MonadIO m => FilePath -> m ()
xmessage FilePath
msg
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 a b. a -> IO b -> IO a
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ FilePath -> IO ()
forall (m :: * -> *). MonadIO m => FilePath -> m ()
trace FilePath
"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 a. a -> IO a
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 a. a -> IO a
forall (f :: * -> *) a. Applicative f => a -> f a
pure Bool
True
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 a. a -> m a
forall (m :: * -> *) a. Monad m => a -> m a
return ()) a -> m ()
f Maybe a
mg
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 a b. X a -> (a -> X b) -> X b
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
trace :: MonadIO m => String -> m ()
trace :: forall (m :: * -> *). MonadIO m => FilePath -> m ()
trace = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
io (IO () -> m ()) -> (FilePath -> IO ()) -> FilePath -> m ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Handle -> FilePath -> IO ()
hPutStrLn Handle
stderr
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
(IO a -> IO (Either SomeException a)
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 a. a -> IO a
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 a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()