{-# LANGUAGE CPP #-}

------------------------------------------------------------------------------
-- |
-- Module: Utils
-- Copyright: (c) 2010, 2018, 2020, 2022 Jose Antonio Ortega Ruiz
-- License: BSD3-style (see LICENSE)
--
-- Maintainer: Jose A Ortega Ruiz <jao@gnu.org>
-- Stability: unstable
-- Portability: unportable
-- Created: Sat Dec 11, 2010 20:55
--
--
-- Miscellaneous utility functions
--
------------------------------------------------------------------------------


module Xmobar.System.Utils
  ( expandHome
  , changeLoop
  , safeIndex
  , forkThread
  ) where

import Control.Monad
import Control.Concurrent.STM
import Control.Exception (handle, SomeException(..))

#ifdef THREADED_RUNTIME
import Control.Concurrent (forkOS)
#else
import Control.Concurrent (forkIO)
#endif

import qualified Data.List.NonEmpty as NE
import Data.Maybe (fromMaybe)

import System.Environment
import System.FilePath

expandHome :: FilePath -> IO FilePath
expandHome :: FilePath -> IO FilePath
expandHome (Char
'~':Char
'/':FilePath
path) = (FilePath -> FilePath) -> IO FilePath -> IO FilePath
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (FilePath -> FilePath -> FilePath
</> FilePath
path) (FilePath -> IO FilePath
getEnv FilePath
"HOME")
expandHome FilePath
p = FilePath -> IO FilePath
forall (m :: * -> *) a. Monad m => a -> m a
return FilePath
p

forkThread :: String -> IO () -> IO ()
forkThread :: FilePath -> IO () -> IO ()
forkThread FilePath
name IO ()
action = do
#ifdef THREADED_RUNTIME
    _ <- forkOS (handle (onError name) action)
#else
    ThreadId
_ <- IO () -> IO ThreadId
forkIO ((SomeException -> IO ()) -> IO () -> IO ()
forall e a. Exception e => (e -> IO a) -> IO a -> IO a
handle (FilePath -> SomeException -> IO ()
onError FilePath
name) IO ()
action)
#endif
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
  where
    onError :: FilePath -> SomeException -> IO ()
onError FilePath
thing (SomeException e
e) =
      IO () -> IO ()
forall (f :: * -> *) a. Functor f => f a -> f ()
void (IO () -> IO ()) -> IO () -> IO ()
forall a b. (a -> b) -> a -> b
$ FilePath -> IO ()
putStrLn (FilePath
"Thread " FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
thing FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
" failed: " FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ e -> FilePath
forall a. Show a => a -> FilePath
show e
e)

changeLoop :: Eq a => STM a -> (a -> IO ()) -> IO ()
changeLoop :: STM a -> (a -> IO ()) -> IO ()
changeLoop STM a
s a -> IO ()
f = STM a -> IO a
forall a. STM a -> IO a
atomically STM a
s IO a -> (a -> IO ()) -> IO ()
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= a -> IO ()
forall b. a -> IO b
go
 where
    go :: a -> IO b
go a
old = do
        a -> IO ()
f a
old
        a -> IO b
go (a -> IO b) -> IO a -> IO b
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< STM a -> IO a
forall a. STM a -> IO a
atomically (do
            a
new <- STM a
s
            Bool -> STM ()
forall (f :: * -> *). Alternative f => Bool -> f ()
guard (a
new a -> a -> Bool
forall a. Eq a => a -> a -> Bool
/= a
old)
            a -> STM a
forall (m :: * -> *) a. Monad m => a -> m a
return a
new)

(!!?) :: [a] -> Int -> Maybe a
!!? :: [a] -> Int -> Maybe a
(!!?) [a]
xs Int
i
    | Int
i Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
< Int
0     = Maybe a
forall a. Maybe a
Nothing
    | Bool
otherwise = Int -> [a] -> Maybe a
forall a. Int -> [a] -> Maybe a
go Int
i [a]
xs
  where
    go :: Int -> [a] -> Maybe a
    go :: Int -> [a] -> Maybe a
go Int
0 (a
x:[a]
_)  = a -> Maybe a
forall a. a -> Maybe a
Just a
x
    go Int
j (a
_:[a]
ys) = Int -> [a] -> Maybe a
forall a. Int -> [a] -> Maybe a
go (Int
j Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
1) [a]
ys
    go Int
_ []     = Maybe a
forall a. Maybe a
Nothing
{-# INLINE (!!?) #-}

safeIndex :: NE.NonEmpty a -> Int -> a
safeIndex :: NonEmpty a -> Int -> a
safeIndex NonEmpty a
xs Int
index = a -> Maybe a -> a
forall a. a -> Maybe a -> a
fromMaybe (NonEmpty a -> a
forall a. NonEmpty a -> a
NE.head NonEmpty a
xs) (NonEmpty a -> [a]
forall a. NonEmpty a -> [a]
NE.toList NonEmpty a
xs [a] -> Int -> Maybe a
forall a. [a] -> Int -> Maybe a
!!? Int
index)