module System.Environment.XDG.DesktopEntry
( DesktopEntry(..)
, deCommand
, deComment
, deHasCategory
, deIcon
, deName
, deNoDisplay
, deNotShowIn
, deOnlyShowIn
, getClassNames
, getDirectoryEntriesDefault
, getDirectoryEntry
, getDirectoryEntryDefault
, getXDGDataDirs
, indexDesktopEntriesBy
, indexDesktopEntriesByClassName
, listDesktopEntries
, readDesktopEntry
) where
import Control.Monad
import Control.Monad.IO.Class
import Control.Monad.Trans.Except
import Data.Char
import qualified Data.ConfigFile as CF
import Data.Either
import Data.Either.Combinators
import qualified Data.MultiMap as MM
import Data.List
import Data.Maybe
import Safe
import System.Directory
import System.FilePath.Posix
import System.Posix.Files
import Text.Printf
import Text.Read (readMaybe)
data DesktopEntryType = Application | Link | Directory
deriving (Read, Show, Eq)
getXDGDataDirs :: IO [FilePath]
getXDGDataDirs =
liftM2 (:) (getXdgDirectory XdgData "") (getXdgDirectoryList XdgDataDirs)
data DesktopEntry = DesktopEntry
{ deType :: DesktopEntryType
, deFilename :: FilePath
, deAttributes :: [(String, String)]
} deriving (Read, Show, Eq)
deHasCategory
:: DesktopEntry
-> String
-> Bool
deHasCategory de cat =
maybe False ((cat `elem`) . splitAtSemicolon) $
lookup "Categories" (deAttributes de)
splitAtSemicolon :: String -> [String]
splitAtSemicolon = lines . map (\c -> if c == ';' then '\n' else c)
deName
:: [String]
-> DesktopEntry
-> String
deName langs de = fromMaybe (deFilename de) $ deLocalisedAtt langs de "Name"
deOnlyShowIn :: DesktopEntry -> [String]
deOnlyShowIn = maybe [] splitAtSemicolon . deAtt "OnlyShowIn"
deNotShowIn :: DesktopEntry -> [String]
deNotShowIn = maybe [] splitAtSemicolon . deAtt "NotShowIn"
deAtt :: String -> DesktopEntry -> Maybe String
deAtt att = lookup att . deAttributes
deIcon :: DesktopEntry -> Maybe String
deIcon = deAtt "Icon"
deNoDisplay :: DesktopEntry -> Bool
deNoDisplay de = maybe False (("true" ==) . map toLower) $ deAtt "NoDisplay" de
deLocalisedAtt
:: [String]
-> DesktopEntry
-> String
-> Maybe String
deLocalisedAtt langs de att =
let localeMatches =
mapMaybe (\l -> lookup (att ++ "[" ++ l ++ "]") (deAttributes de)) langs
in if null localeMatches
then lookup att $ deAttributes de
else Just $ head localeMatches
deComment :: [String]
-> DesktopEntry
-> Maybe String
deComment langs de = deLocalisedAtt langs de "Comment"
deCommand :: DesktopEntry -> Maybe String
deCommand de =
reverse . dropWhile (== ' ') . reverse . takeWhile (/= '%') <$>
lookup "Exec" (deAttributes de)
listDesktopEntries
:: String
-> FilePath
-> IO [DesktopEntry]
listDesktopEntries extension dir = do
let normalizedDir = normalise dir
ex <- doesDirectoryExist normalizedDir
if ex
then do
files <- map (normalizedDir </>) <$> listDirectory dir
entries <-
(nub . rights) <$>
mapM readDesktopEntry (filter (extension `isSuffixOf`) files)
subDirs <- filterM doesDirectoryExist files
subEntries <- concat <$> mapM (listDesktopEntries extension) subDirs
return $ entries ++ subEntries
else return []
getDirectoryEntry :: [FilePath] -> String -> IO (Maybe DesktopEntry)
getDirectoryEntry dirs name = do
exFiles <- filterM doesFileExist $ map ((</> name) . normalise) dirs
join . (fmap rightToMaybe) <$> traverse readDesktopEntry (headMay exFiles)
getDirectoryEntryDefault :: String -> IO (Maybe DesktopEntry)
getDirectoryEntryDefault entry =
fmap (</> "applications") <$> getXDGDataDirs >>=
flip getDirectoryEntry (printf "%s.desktop" entry)
getDirectoryEntriesDefault :: IO [DesktopEntry]
getDirectoryEntriesDefault =
fmap (</> "applications") <$> getXDGDataDirs >>= foldM addDesktopEntries []
where addDesktopEntries soFar directory =
(soFar ++) <$> listDesktopEntries "desktop" directory
readDesktopEntry :: FilePath -> IO (Either (CF.CPErrorData, String) DesktopEntry)
readDesktopEntry filePath = runExceptT $ do
result <- (join $ liftIO $ CF.readfile CF.emptyCP filePath) >>=
flip CF.items "Desktop Entry"
return DesktopEntry
{ deType = fromMaybe Application $ lookup "Type" result >>= readMaybe
, deFilename = filePath
, deAttributes = result
}
indexDesktopEntriesBy ::
Foldable t => (DesktopEntry -> [String]) ->
t DesktopEntry -> MM.MultiMap String DesktopEntry
indexDesktopEntriesBy getIndices = foldl insertByIndices MM.empty
where
insertByIndices entriesMap entry =
foldl insertForKey entriesMap $ getIndices entry
where insertForKey innerMap key = MM.insert key entry innerMap
getClassNames :: DesktopEntry -> [String]
getClassNames DesktopEntry { deAttributes = attributes, deFilename = filepath } =
(snd $ splitExtensions $ snd $ splitFileName filepath) :
catMaybes [lookup "StartupWMClass" attributes, lookup "Name" attributes]
indexDesktopEntriesByClassName
:: Foldable t => t DesktopEntry -> MM.MultiMap String DesktopEntry
indexDesktopEntriesByClassName = indexDesktopEntriesBy getClassNames