summaryrefslogtreecommitdiffhomepage
path: root/src
diff options
context:
space:
mode:
authorjao <jao@gnu.org>2020-10-09 17:51:07 +0100
committerjao <jao@gnu.org>2020-10-09 17:51:07 +0100
commit407866c433735e510b6bde2d06e2a18cff22c470 (patch)
treef7f73bc4f30f52844f5582c321e97d0375dce1b2 /src
parente71512b7c961ab379aee98c2f4d65ad4bdd3c5bf (diff)
downloadxmobar-407866c433735e510b6bde2d06e2a18cff22c470.tar.gz
xmobar-407866c433735e510b6bde2d06e2a18cff22c470.tar.bz2
hlinting
Diffstat (limited to 'src')
-rw-r--r--src/Xmobar/App/Config.hs3
-rw-r--r--src/Xmobar/App/EventLoop.hs8
-rw-r--r--src/Xmobar/App/Timer.hs6
-rw-r--r--src/Xmobar/Config/Parse.hs5
4 files changed, 12 insertions, 10 deletions
diff --git a/src/Xmobar/App/Config.hs b/src/Xmobar/App/Config.hs
index a183128..d17577e 100644
--- a/src/Xmobar/App/Config.hs
+++ b/src/Xmobar/App/Config.hs
@@ -21,6 +21,7 @@ module Xmobar.App.Config (defaultConfig,
xmobarConfigFile) where
import Control.Monad (when, filterM)
+import Data.Functor ((<&>))
import System.Environment
import System.Directory
@@ -105,7 +106,7 @@ findFirstDirOf create possibles = do
go [] = return Nothing
go (x:xs) = do
exists <- x >>= doesDirectoryExist
- if exists then x >>= return . Just else go xs
+ if exists then x <&> Just else go xs
-- | Simple wrapper around @findFirstDirOf@ that allows the primary
-- path to be specified by an environment variable.
diff --git a/src/Xmobar/App/EventLoop.hs b/src/Xmobar/App/EventLoop.hs
index 1c77ac1..4a0db46 100644
--- a/src/Xmobar/App/EventLoop.hs
+++ b/src/Xmobar/App/EventLoop.hs
@@ -70,7 +70,7 @@ runX :: XConf -> X () -> IO ()
runX xc f = runReaderT f xc
newRefreshLock :: IO (TMVar ())
-newRefreshLock = atomically $ newTMVar ()
+newRefreshLock = newTMVarIO ()
refreshLock :: TMVar () -> IO a -> IO a
refreshLock var = bracket_ lock unlock
@@ -95,7 +95,7 @@ startLoop xcfg@(XConf _ _ w _ _ _ _) sig pauser vs = do
#ifdef XFT
xftInitFtLibrary
#endif
- tv <- atomically $ newTVar []
+ tv <- newTVarIO []
_ <- forkIO (handle (handler "checker") (checker tv [] vs sig pauser))
#ifdef THREADED_RUNTIME
_ <- forkOS (handle (handler "eventer") (eventer sig))
@@ -238,10 +238,10 @@ startCommand :: TMVar SignalType
-> (Runnable,String,String)
-> IO ([Async ()], TVar String)
startCommand sig (com,s,ss)
- | alias com == "" = do var <- atomically $ newTVar is
+ | alias com == "" = do var <- newTVarIO is
atomically $ writeTVar var (s ++ ss)
return ([], var)
- | otherwise = do var <- atomically $ newTVar is
+ | otherwise = do var <- newTVarIO is
let cb str = atomically $ writeTVar var (s ++ str ++ ss)
a1 <- async $ start com cb
a2 <- async $ trigger com $ maybe (return ())
diff --git a/src/Xmobar/App/Timer.hs b/src/Xmobar/App/Timer.hs
index cf59630..23c48c0 100644
--- a/src/Xmobar/App/Timer.hs
+++ b/src/Xmobar/App/Timer.hs
@@ -2,7 +2,7 @@
------------------------------------------------------------------------------
-- |
-- Module: Xmobar.App.Timer
--- Copyright: (c) 2019 Tomáš Janoušek
+-- Copyright: (c) 2019, 2020 Tomáš Janoušek
-- License: BSD3-style (see LICENSE)
--
-- Maintainer: Tomáš Janoušek <tomi@nomi.cz>
@@ -54,7 +54,7 @@ newPeriod :: Int64 -> IO (Unique, Period)
newPeriod r = do
u <- newUnique
t <- now
- v <- atomically newEmptyTMVar
+ v <- newEmptyTMVarIO
let t' = t - t `mod` r
return (u, Period { rate = r, next = t', tick = v })
@@ -212,7 +212,7 @@ delayUntilNextFire = do
delay = (tNext - tNow) `min` fromIntegral maxDelay
delayUsec = fromIntegral delay * 100000
registerDelay delayUsec
- Nothing -> atomically $ newTVar False
+ Nothing -> newTVarIO False
atomically $ do
delayOver <- readTVar delayVar
periods' <- fromJust <$> readTVar periodsVar
diff --git a/src/Xmobar/Config/Parse.hs b/src/Xmobar/Config/Parse.hs
index 00ce99c..056f3fc 100644
--- a/src/Xmobar/Config/Parse.hs
+++ b/src/Xmobar/Config/Parse.hs
@@ -2,7 +2,7 @@
------------------------------------------------------------------------------
-- |
-- Module: Xmobar.Config.Parse
--- Copyright: (c) 2018 Jose Antonio Ortega Ruiz
+-- Copyright: (c) 2018, 2020 Jose Antonio Ortega Ruiz
-- License: BSD3-style (see LICENSE)
--
-- Maintainer: jao@gnu.org
@@ -22,6 +22,7 @@ import Text.ParserCombinators.Parsec
import Text.ParserCombinators.Parsec.Number (int)
import Text.ParserCombinators.Parsec.Perm ((<|?>), (<$?>), permute)
import Control.Monad.IO.Class (liftIO)
+import Data.Functor ((<&>))
import Xmobar.Config.Types
@@ -174,4 +175,4 @@ commandsErr = "commands: this usually means that a command could not" ++
-- parsed.
readConfig :: Config -> FilePath -> IO (Either ParseError (Config,[String]))
readConfig defaultConfig f =
- liftIO (readFileSafe f) >>= return . parseConfig defaultConfig
+ liftIO (readFileSafe f) <&> parseConfig defaultConfig