module System.Taffybar.Information.X11DesktopInfo
  ( X11Context(..)
  , X11Property
  , X11Window
  , doLowerWindow
  , eventLoop
  , getAtom
  , getDefaultCtx
  , getDisplay
  , getPrimaryOutputNumber
  , getVisibleTags
  , getWindowState
  , getWindowStateProperty
  , isWindowUrgent
  , postX11RequestSyncProp
  , readAsInt
  , readAsListOfInt
  , readAsListOfString
  , readAsListOfWindow
  , readAsString
  , sendCommandEvent
  , sendWindowEvent
  , withDefaultCtx
  ) where
import Data.List
import Data.Maybe
import Codec.Binary.UTF8.String as UTF8
import qualified Control.Concurrent.MVar as MV
import Control.Monad
import Control.Monad.IO.Class
import Control.Monad.Trans.Class
import Control.Monad.Trans.Reader
import Data.Bits (testBit, (.|.))
import Data.List.Split (endBy)
import Graphics.X11.Xlib
import Graphics.X11.Xlib.Extras
  hiding (getWindowProperty8, getWindowProperty32, getWMHints)
import Graphics.X11.Xrandr
import Prelude
import System.Taffybar.Information.SafeX11
data X11Context = X11Context
  { contextDisplay :: Display
  , _contextRoot :: Window
  , atomCache :: MV.MVar [(String, Atom)]
  }
type X11Property a = ReaderT X11Context IO a
type X11Window = Window
type PropertyFetcher a = Display -> Atom -> Window -> IO (Maybe [a])
withDefaultCtx :: X11Property a -> IO a
withDefaultCtx fun = do
  ctx <- getDefaultCtx
  res <- runReaderT fun ctx
  closeDisplay (contextDisplay ctx)
  return res
getDisplay :: X11Property Display
getDisplay = contextDisplay <$> ask
readAsInt :: Maybe X11Window 
          -> String 
          -> X11Property Int
readAsInt window name = do
  prop <- fetch getWindowProperty32 window name
  case prop of
    Just (x:_) -> return (fromIntegral x)
    _          -> return (-1)
readAsListOfInt :: Maybe X11Window 
                -> String          
                -> X11Property [Int]
readAsListOfInt window name = do
  prop <- fetch getWindowProperty32 window name
  case prop of
    Just xs -> return (map fromIntegral xs)
    _       -> return []
readAsString :: Maybe X11Window 
             -> String          
             -> X11Property String
readAsString window name = do
  prop <- fetch getWindowProperty8 window name
  case prop of
    Just xs -> return . UTF8.decode . map fromIntegral $ xs
    _       -> return []
readAsListOfString :: Maybe X11Window 
                   -> String          
                   -> X11Property [String]
readAsListOfString window name = do
  prop <- fetch getWindowProperty8 window name
  case prop of
    Just xs -> return (parse xs)
    _       -> return []
  where
    parse = endBy "\0" . UTF8.decode . map fromIntegral
readAsListOfWindow :: Maybe X11Window 
                   -> String          
                   -> X11Property [X11Window]
readAsListOfWindow window name = do
  prop <- fetch getWindowProperty32 window name
  case prop of
    Just xs -> return $ map fromIntegral xs
    _       -> return []
isWindowUrgent :: X11Window -> X11Property Bool
isWindowUrgent window = do
  hints <- fetchWindowHints window
  return $ testBit (wmh_flags hints) urgencyHintBit
getVisibleTags :: X11Property [String]
getVisibleTags = readAsListOfString Nothing "_XMONAD_VISIBLE_WORKSPACES"
getAtom :: String -> X11Property Atom
getAtom s = do
  (X11Context d _ cacheVar) <- ask
  a <- lift $ lookup s <$> MV.readMVar cacheVar
  let updateCacheAction = lift $ MV.modifyMVar cacheVar updateCache
      updateCache currentCache =
        do
          atom <- internAtom d s False
          return ((s, atom):currentCache, atom)
  maybe updateCacheAction return a
eventLoop :: (Event -> IO ()) -> X11Property ()
eventLoop dispatch = do
  (X11Context d w _) <- ask
  liftIO $ do
    selectInput d w $ propertyChangeMask .|. substructureNotifyMask
    allocaXEvent $ \e -> forever $ do
      event <- nextEvent d e >> getEvent e
      case event of
        MapNotifyEvent { ev_window = window } ->
          selectInput d window propertyChangeMask
        _ -> return ()
      dispatch event
sendCommandEvent :: Atom -> Atom -> X11Property ()
sendCommandEvent cmd arg = do
  (X11Context dpy root _) <- ask
  sendCustomEvent dpy cmd arg root root
sendWindowEvent :: Atom -> X11Window -> X11Property ()
sendWindowEvent cmd win = do
  (X11Context dpy root _) <- ask
  sendCustomEvent dpy cmd cmd root win
getDefaultCtx :: IO X11Context
getDefaultCtx = do
  d <- openDisplay ""
  w <- rootWindow d $ defaultScreen d
  cache <- MV.newMVar []
  return $ X11Context d w cache
getWindowStateProperty :: X11Window -> String -> X11Property Bool
getWindowStateProperty window property = not . null <$> getWindowState window [property]
getWindowState :: X11Window -> [String] -> X11Property [String]
getWindowState window request = do
  let getAsLong s = fromIntegral <$> getAtom s
  integers <- mapM getAsLong request
  properties <- fetch getWindowProperty32 (Just window) "_NET_WM_STATE"
  let integerToString = zip integers request
      present = intersect integers $ fromMaybe [] properties
      presentStrings = map (`lookup` integerToString) present
  return $ catMaybes presentStrings
fetch :: (Integral a)
      => PropertyFetcher a 
      -> Maybe X11Window   
      -> String            
      -> X11Property (Maybe [a])
fetch fetcher window name = do
  (X11Context dpy root _) <- ask
  atom <- getAtom name
  liftIO $ fetcher dpy atom (fromMaybe root window)
fetchWindowHints :: X11Window -> X11Property WMHints
fetchWindowHints window = do
  (X11Context d _ _) <- ask
  liftIO $ getWMHints d window
sendCustomEvent :: Display
                -> Atom
                -> Atom
                -> X11Window
                -> X11Window
                -> X11Property ()
sendCustomEvent dpy cmd arg root win =
  liftIO $ allocaXEvent $ \e -> do
    setEventType e clientMessage
    setClientMessageEvent e win cmd 32 arg currentTime
    sendEvent dpy root False structureNotifyMask e
    sync dpy False
postX11RequestSyncProp :: X11Property a -> a -> X11Property a
postX11RequestSyncProp prop def = do
  c <- ask
  let action = runReaderT prop c
  lift $ postX11RequestSyncDef def action
isActiveOutput :: XRRScreenResources -> RROutput -> X11Property Bool
isActiveOutput sres output = do
  (X11Context display _ _) <- ask
  maybeOutputInfo <- liftIO $ xrrGetOutputInfo display sres output
  return $ maybe 0 xrr_oi_crtc maybeOutputInfo /= 0
getActiveOutputs :: X11Property [RROutput]
getActiveOutputs = do
  (X11Context display rootw _) <- ask
  maybeSres <- liftIO $ xrrGetScreenResources display rootw
  maybe (return []) (\sres -> filterM (isActiveOutput sres) $ xrr_sr_outputs sres)
        maybeSres
getPrimaryOutputNumber :: X11Property (Maybe Int)
getPrimaryOutputNumber = do
  (X11Context display rootw _) <- ask
  primary <- liftIO $ xrrGetOutputPrimary display rootw
  outputs <- getActiveOutputs
  return $ primary `elemIndex` outputs
doLowerWindow :: X11Window -> X11Property ()
doLowerWindow window =
  asks contextDisplay >>= lift . flip lowerWindow window