{-# LANGUAGE DeriveDataTypeable #-}
module XMonad.Hooks.WallpaperSetter (
wallpaperSetter
, WallpaperConf(..)
, Wallpaper(..)
, WallpaperList(..)
, defWallpaperConf
, defWPNames
) where
import XMonad
import qualified XMonad.StackSet as S
import qualified XMonad.Util.ExtensibleState as XS
import System.IO
import System.Process
import System.Directory (getHomeDirectory, doesFileExist, doesDirectoryExist, getDirectoryContents)
import System.FilePath ((</>))
import System.Random (randomRIO)
import qualified Data.Map as M
import Data.List (intersperse, sortBy)
import Data.Char (isAlphaNum)
import Data.Ord (comparing)
import Control.Monad
import Control.Applicative
import Data.Maybe
import Data.Monoid hiding ((<>))
import Data.Semigroup
data WCState = WCState (Maybe [WorkspaceId]) (Maybe ProcessHandle) deriving Typeable
instance ExtensionClass WCState where
initialValue = WCState Nothing Nothing
data Wallpaper = WallpaperFix FilePath
| WallpaperDir FilePath
deriving (Eq, Show, Read)
newtype WallpaperList = WallpaperList [(WorkspaceId, Wallpaper)]
deriving (Show,Read)
instance Monoid WallpaperList where
mempty = WallpaperList []
mappend (WallpaperList w1) (WallpaperList w2) =
WallpaperList $ M.toList $ (M.fromList w2) `M.union` (M.fromList w1)
instance Semigroup WallpaperList where
(<>) = mappend
data WallpaperConf = WallpaperConf {
wallpaperBaseDir :: FilePath
, wallpapers :: WallpaperList
} deriving (Show, Read)
defWallpaperConf :: WallpaperConf
defWallpaperConf = WallpaperConf "" $ WallpaperList []
instance Default WallpaperConf where
def = defWallpaperConf
defWPNames :: [WorkspaceId] -> WallpaperList
defWPNames xs = WallpaperList $ map (\x -> (x,WallpaperFix (filter isAlphaNum x++".jpg"))) xs
wallpaperSetter :: WallpaperConf -> X ()
wallpaperSetter wpconf = do
WCState oldws h <- XS.get
visws <- getVisibleWorkspaces
when (Just visws /= oldws) $ do
wpconf' <- completeWPConf wpconf
wspicpaths <- getPicPathsAndWSRects wpconf'
case h of
Nothing -> return ()
Just pid -> liftIO $ terminateProcess pid
handle <- applyWallpaper wspicpaths
XS.put $ WCState (Just visws) $ Just handle
pickFrom :: [a] -> IO a
pickFrom list = do
i <- randomRIO (0,length list - 1)
return $ list !! i
getPicPath :: WallpaperConf -> Wallpaper -> IO (Maybe FilePath)
getPicPath conf (WallpaperDir dir) = do
direxists <- doesDirectoryExist $ wallpaperBaseDir conf </> dir
if direxists
then do files <- getDirectoryContents $ wallpaperBaseDir conf </> dir
let files' = filter ((/='.').head) files
file <- pickFrom files'
return $ Just $ wallpaperBaseDir conf </> dir </> file
else return Nothing
getPicPath conf (WallpaperFix file) = do
exist <- doesFileExist path
return $ if exist then Just path else Nothing
where path = wallpaperBaseDir conf </> file
getPicRes :: FilePath -> IO (Maybe (Int,Int))
getPicRes picpath = do
(_, Just outh,_,_pid) <- createProcess $ (proc "identify" ["-format", "%w %h", picpath]) { std_out = CreatePipe }
output <- hGetContents outh
return $ case map reads (words output) of
[[(w,"")],[(h,"")]] -> Just (w,h)
_ -> Nothing
completeWPConf :: WallpaperConf -> X WallpaperConf
completeWPConf (WallpaperConf dir (WallpaperList ws)) = do
home <- liftIO getHomeDirectory
winset <- gets windowset
let tags = map S.tag $ S.workspaces winset
dir' = if null dir then home </> ".wallpapers" else dir
ws' = if null ws then defWPNames tags else WallpaperList ws
return (WallpaperConf dir' ws')
getVisibleWorkspaces :: X [WorkspaceId]
getVisibleWorkspaces = do
winset <- gets windowset
return $ map (S.tag . S.workspace) . sortBy (comparing S.screen) $ S.current winset : S.visible winset
getPicPathsAndWSRects :: WallpaperConf -> X [(Rectangle, FilePath)]
getPicPathsAndWSRects wpconf = do
winset <- gets windowset
paths <- liftIO getPicPaths
visws <- getVisibleWorkspaces
let visscr = S.current winset : S.visible winset
visrects = M.fromList $ map (\x -> ((S.tag . S.workspace) x, S.screenDetail x)) visscr
hasPicAndIsVisible (n, mp) = n `elem` visws && (isJust mp)
getRect tag = screenRect $ fromJust $ M.lookup tag visrects
foundpaths = map (\(n,Just p)->(getRect n,p)) $ filter hasPicAndIsVisible paths
return foundpaths
where getPicPaths = mapM (\(x,y) -> getPicPath wpconf y
>>= \p -> return (x,p)) wl
WallpaperList wl = wallpapers wpconf
applyWallpaper :: [(Rectangle, FilePath)] -> X ProcessHandle
applyWallpaper parts = do
winset <- gets windowset
let (vx,vy) = getVScreenDim winset
layers <- liftIO $ mapM layerCommand parts
let basepart ="convert -size "++show vx++"x"++show vy++" xc:black "
endpart =" jpg:- | feh --no-xinerama --bg-tile --no-fehbg -"
cmd = basepart ++ (concat $ intersperse " " layers) ++ endpart
liftIO $ runCommand cmd
getVScreenDim :: S.StackSet i l a sid ScreenDetail -> (Integer, Integer)
getVScreenDim = foldr maxXY (0,0) . map (screenRect . S.screenDetail) . S.screens
where maxXY (Rectangle x y w h) (mx,my) = ( fromIntegral ((fromIntegral x)+w) `max` mx
, fromIntegral ((fromIntegral y)+h) `max` my )
needsRotation :: Rectangle -> (Int,Int) -> Bool
needsRotation rect (px,py) = let wratio, pratio :: Double
wratio = (fromIntegral $ rect_width rect) / (fromIntegral $ rect_height rect)
pratio = fromIntegral px / fromIntegral py
in wratio > 1 && pratio < 1 || wratio < 1 && pratio > 1
layerCommand :: (Rectangle, FilePath) -> IO String
layerCommand (rect, path) = do
res <- getPicRes path
return $ case needsRotation rect <$> res of
Nothing -> ""
Just rotate ->
" \\( '"++path++"' "++(if rotate then "-rotate 90 " else "")
++ " -scale "++(show$rect_width rect)++"x"++(show$rect_height rect)++"! \\)"
++ " -geometry +"++(show$rect_x rect)++"+"++(show$rect_y rect)++" -composite "