-- Base
import XMonad
import System.Exit
import qualified XMonad.StackSet as W

-- Actions
import XMonad.Actions.CycleWS (toggleWS')
import XMonad.Actions.MouseResize

-- Data
import qualified Data.Map        as M
import Data.Maybe (isJust)

-- Hooks
import XMonad.Hooks.ManageHelpers
import XMonad.Hooks.StatusBar
import XMonad.Hooks.StatusBar.PP
import XMonad.Hooks.EwmhDesktops
import XMonad.Hooks.SetWMName
import XMonad.Hooks.InsertPosition

-- Layout modifiers
import XMonad.Layout.Renamed
import XMonad.Layout.Spacing
import XMonad.Layout.NoBorders
import XMonad.Layout.SimplestFloat
import XMonad.Layout.LayoutModifier
import XMonad.Layout.ResizableTile
import XMonad.Layout.WindowNavigation
import XMonad.Layout.PerWorkspace
import XMonad.Layout.WindowArranger (windowArrange, WindowArrangerMsg(..))

-- Utils
import XMonad.Util.Loggers
import XMonad.Util.NamedScratchpad
import XMonad.Util.SpawnOnce
import XMonad.Util.EZConfig
import XMonad.Util.Hacks

-- main loop
main :: IO ()
main = xmonad
    . ewmhFullscreen
    . ewmh
    . withEasySB (statusBarProp "xmobar ~/.config/xmobar/xmobarrc" (pure myXmobarPP)) toggleStrutsKey
    $ myConfig
  where
    toggleStrutsKey :: XConfig Layout -> (KeyMask, KeySym)
    toggleStrutsKey XConfig{ modMask = m } = (m, xK_F11)

-- My config
myConfig = def
  { modMask = myModMask
  , layoutHook = myLayoutHook
  , manageHook = insertPosition End Newer <+> myManageHook
  , handleEventHook = trayerAboveXmobarEventHook
  , focusFollowsMouse  = myFocusFollowsMouse
  , terminal = myTerminal
  , borderWidth = myBorderWidth
  , normalBorderColor = myNormalBorderColor
  , focusedBorderColor = myFocusedBorderColor
  , keys = myKeys
  , workspaces = myWorkspaces
  , startupHook = myStartupHook
  }

-- My variables
myModMask = mod4Mask
myTerminal = "alacritty"
myBorderWidth = 2

myFocusFollowsMouse :: Bool
myFocusFollowsMouse = False

myNormalBorderColor = "#737994"
myFocusedBorderColor = "#c6d0f5"

myWorkspaces    = ["一","二","三","四","五","六","七","八","九"]

-- My startup hook
myStartupHook :: X ()
myStartupHook = do
  spawn "killall trayer-srg"  -- kill current trayer on each restart
  spawnOnce "sxhkd -c $HOME/.config/sxhkd/general"
  spawnOnce "gentoo-pipewire-launcher"
  spawnOnce "transmission-daemon"
  spawnOnce "syncthing"
  spawnOnce "lxsession"
  spawnOnce "picom"
  spawnOnce "clipmenud"
  spawnOnce "dunst"
  -- spawnOnce "discord --start-minimized"
  spawnOnce "keepassxc"
  spawnOnce "/usr/libexec/polkit-gnome-authentication-agent-1"
  spawn ("sleep 2 && trayer-srg --edge top --align right --widthtype request --padding 6 --iconspacing 7 --SetDockType true --SetPartialStrut true --expand true --monitor 1 --transparent true --alpha 0 --tint 0x303446 --height 27 -l")
  setWMName "LG3D" -- Fix java programs

-- My scratchpads
myScratchPads :: [NamedScratchpad]
myScratchPads = [ NS "terminal" spawnTerm findTerm manageTerm
                , NS "wiki" spawnWiki findWiki manageWiki
                , NS "notes" spawnNotes findNotes manageNotes
                , NS "profanity" spawnProfanity findProfanity manageProfanity
                ]
  where
    spawnTerm  = myTerminal ++ " --class scratchpad,scratchpad"
    findTerm   = className =? "scratchpad"
    manageTerm = customFloating $ W.RationalRect l t w h
               where
                 h = 0.8
                 w = 0.8
                 t = 0.9 -h
                 l = 0.9 -w
    spawnWiki  = myTerminal ++ " --class wiki,wiki -e wiki"
    findWiki   = className =? "wiki"
    manageWiki = customFloating $ W.RationalRect l t w h
               where
                 h = 0.8
                 w = 0.8
                 t = 0.9 -h
                 l = 0.9 -w
    spawnNotes  = myTerminal ++ " --class wiki,wiki -e notes"
    findNotes   = className =? "notes"
    manageNotes = customFloating $ W.RationalRect l t w h
               where
                 h = 0.8
                 w = 0.8
                 t = 0.9 -h
                 l = 0.9 -w
    spawnProfanity  = myTerminal ++ " --class profanity,profanity -e profanity"
    findProfanity   = className =? "profanity"
    manageProfanity = customFloating $ W.RationalRect l t w h
               where
                 h = 0.8
                 w = 0.8
                 t = 0.9 -h
                 l = 0.9 -w


--Makes setting the spacingRaw simpler to write. The spacingRaw module adds a configurable amount of space around windows.
mySpacing :: Integer -> l a -> XMonad.Layout.LayoutModifier.ModifiedLayout Spacing l a
mySpacing i = spacingRaw False (Border i i i i) True (Border i i i i) True

-- Below is a variation of the above except no borders are applied
-- if fewer than two windows. So a single window has no gaps.
mySpacing' :: Integer -> l a -> XMonad.Layout.LayoutModifier.ModifiedLayout Spacing l a
mySpacing' i = spacingRaw True (Border i i i i) True (Border i i i i) True

-- My layouts
tall = renamed [Replace "tall"]
          $ withBorder myBorderWidth
          $ windowNavigation
          $ mySpacing 7
          $ ResizableTall 1 (3/100) (1/2) []
monocle  = renamed [Replace "monocle"]
          $ withBorder myBorderWidth
          $ mySpacing 7
          $ windowNavigation
          $ Full
floats   = renamed [Replace "floats"]
          $ withBorder myBorderWidth
          $ simplestFloat

myLayoutHook = lessBorders OnlyScreenFloat
          $ mouseResize
          $ windowArrange
          $ myDefaultLayout
  where
    myDefaultLayout = onWorkspaces [(myWorkspaces !! 0), (myWorkspaces !! 3), (myWorkspaces !! 4)] (monocle ||| floats ||| tall)
                    $ onWorkspace (myWorkspaces !! 5) (floats ||| tall ||| monocle)
                    $ tall
                    ||| monocle
                    ||| floats

-- My manage hook
myManageHook :: ManageHook
myManageHook = composeAll
    [ className =? "librewolf"          --> doShiftAndGo ( myWorkspaces !! 0)
    , className =? "newsboat"           --> doShiftAndGo ( myWorkspaces !! 3)
    , className =? "videos"             --> doShiftAndGo ( myWorkspaces !! 3)
    , className =? "ytfzf"              --> doShiftAndGo ( myWorkspaces !! 3)
    , className =? "lf"                 --> doShiftAndGo ( myWorkspaces !! 3)
    , className =? "thunderbird"        --> doShiftAndGo ( myWorkspaces !! 4)
    , className =? "Ferdium"            --> doShiftAndGo ( myWorkspaces !! 4)
    , className =? "discord"            --> doShiftAndGo ( myWorkspaces !! 4)
    , className =? "tutanota-desktop"   --> doShiftAndGo ( myWorkspaces !! 4)
    , className =? "Lutris"             --> doShiftAndGo ( myWorkspaces !! 5)
    , className =? "steam"              --> doShiftAndGo ( myWorkspaces !! 5)
    , className =? "heroic"             --> doShiftAndGo ( myWorkspaces !! 5)
    , className =? "cartridges"         --> doShiftAndGo ( myWorkspaces !! 5)
    , isDialog                          --> doCenterFloat <+> doF W.swapUp
    , className =? "Gimp"               --> doFloat <+> doF W.swapUp
    , className =? "confirm"            --> doFloat <+> doF W.swapUp
    , className =? "file_progress"      --> doFloat <+> doF W.swapUp
    , className =? "dialog"             --> doFloat <+> doF W.swapUp
    , className =? "download"           --> doFloat <+> doF W.swapUp
    , className =? "error"              --> doFloat <+> doF W.swapUp
    , className =? "notification"       --> doFloat <+> doF W.swapUp
    , className =? "splash"             --> doFloat <+> doF W.swapUp
    , className =? "toolbar"            --> doFloat <+> doF W.swapUp
    , className =? "pinentry-gtk-2"     --> doFloat <+> doF W.swapUp
    , className =? "Yad"                --> doCenterFloat <+> doF W.swapUp
    , className =? "badd"               --> doCenterFloat <+> doF W.swapUp
    , isFullscreen                      --> doFullFloat <+> doF W.swapUp
    , namedScratchpadManageHook myScratchPads
    ]
    where
      doShiftAndGo ws = doF (W.greedyView ws) <+> doShift ws

-- My keybindings in a nice readable format
myKeys = \c -> mkKeymap c $
  [ ("M-S-q", kill) -- kill active window
  , ("M-<Space>", sendMessage NextLayout) -- cycle layout
  , ("M-S-<Space>", withFocused toggleFloat) -- toggle floating state of a window
  , ("M-j", windows W.focusDown) -- Move focus down
  , ("M-k", windows W.focusUp) -- Move focus up
  , ("M-S-<Return>", windows W.swapMaster) -- Move Focused window to master
  , ("M-S-j", windows W.swapDown) --Move window down the stack
  , ("M-S-k", windows W.swapUp) -- Move window up the stack
  , ("M-h", sendMessage Shrink) -- Shrink master
  , ("M-l", sendMessage Expand) -- Expand master
  , ("M-,", sendMessage (IncMasterN 1)) -- Increase master count
  , ("M-.", sendMessage (IncMasterN (-1))) -- Decrease msaster count
  , ("M-C-e", io (exitWith ExitSuccess)) -- Quit xmonad
  , ("M-S-r", spawn "xmonad --recompile && xmonad --restart") -- Restart xmonad
  , ("M-<Tab>", toggleWS' ["NSP"]) -- Toogle last used workspace, ignoring named scratchpad
  , ("M-s t", namedScratchpadAction myScratchPads "terminal") -- Toggle scratchpad
  , ("M-s w", namedScratchpadAction myScratchPads "wiki") -- Toggle scratchpad
  , ("M-s n", namedScratchpadAction myScratchPads "notes") -- Toggle scratchpad
  , ("M-s p", namedScratchpadAction myScratchPads "profanity") -- Toggle scratchpad
  , ("M-1", viewDesktop 0) -- Check workspace 1
  , ("M-2", viewDesktop 1) -- Check workspace 2
  , ("M-3", viewDesktop 2) -- Check workspace 3
  , ("M-4", viewDesktop 3) -- Check workspace 4
  , ("M-5", viewDesktop 4) -- Check workspace 5
  , ("M-6", viewDesktop 5) -- Check workspace 6
  , ("M-7", viewDesktop 6) -- Check workspace 7
  , ("M-8", viewDesktop 7) -- Check workspace 8
  , ("M-9", viewDesktop 8) -- Check workspace 9
  , ("M-S-1", shiftWindow 0) -- Send window to workspace 1
  , ("M-S-2", shiftWindow 1) -- Send window to workspace 2
  , ("M-S-3", shiftWindow 2) -- Send window to workspace 3
  , ("M-S-4", shiftWindow 3) -- Send window to workspace 4
  , ("M-S-5", shiftWindow 4) -- Send window to workspace 5
  , ("M-S-6", shiftWindow 5) -- Send window to workspace 6
  , ("M-S-7", shiftWindow 6) -- Send window to workspace 7
  , ("M-S-8", shiftWindow 7) -- Send window to workspace 8
  , ("M-S-9", shiftWindow 8) -- Send window to workspace 9
  , ("M-C-1", shiftAndView 0) -- Send window and check workspace 1
  , ("M-C-2", shiftAndView 1) -- Send window and check workspace 2
  , ("M-C-3", shiftAndView 2) -- Send window and check workspace 3
  , ("M-C-4", shiftAndView 3) -- Send window and check workspace 4
  , ("M-C-5", shiftAndView 4) -- Send window and check workspace 5
  , ("M-C-6", shiftAndView 5) -- Send window and check workspace 6
  , ("M-C-7", shiftAndView 6) -- Send window and check workspace 7
  , ("M-C-8", shiftAndView 7) -- Send window and check workspace 8
  , ("M-C-9", shiftAndView 8) -- Send window and check workspace 9
  ]
  where
  toggleFloat w = windows (\s -> if M.member w (W.floating s)
                  then W.sink w s
                  else (W.float w (W.RationalRect (1/6) (1/6) (2/3) (2/3)) s))
  viewDesktop d = windows $ W.greedyView $ myWorkspaces !! d
  shiftWindow w = windows $ W.shift $ myWorkspaces !! w
  shiftAndView w = windows $ W.greedyView (myWorkspaces !! w) . W.shift (myWorkspaces !! w)

-- My xmobar workspace and other things config
myXmobarPP :: PP
myXmobarPP = filterOutWsPP ["NSP"]
      $ def
    { ppSep             = magenta " • "
    , ppWsSep           = " "
    , ppTitleSanitize   = xmobarStrip
    , ppCurrent         = xmobarBorder "Bottom" "#89b4fa" 2
    , ppHidden          = white
    , ppHiddenNoWindows = lowWhite
    , ppUrgent          = red . wrap (yellow "!") (yellow "!")
    , ppOrder           = \[ws, l, _, wins] -> [ws, l, wins]
    , ppExtras          = [logTitles formatFocused formatUnfocused]
    }
  where
    formatFocused   = wrap (white    "[") (white    "]") . magenta . ppWindow
    formatUnfocused = wrap (lowWhite "[") (lowWhite "]") . blue    . ppWindow

    ppWindow :: String -> String
    ppWindow = xmobarRaw . (\w -> if null w then "untitled" else w) . shorten 25

    blue, lowWhite, magenta, red, white, yellow :: String -> String
    magenta  = xmobarColor "#eba0ac" ""
    blue     = xmobarColor "#cba6f7" ""
    white    = xmobarColor "#cdd6f4" ""
    yellow   = xmobarColor "#f9e2af" ""
    red      = xmobarColor "#f38ba8" ""
    lowWhite = xmobarColor "#585b70" ""