Copyright | 2019 Ivan Malison |
---|---|
License | BSD3-style (see LICENSE) |
Maintainer | Ivan Malison |
Stability | unstable |
Portability | unportable |
Safe Haskell | Safe |
Language | Haskell2010 |
Implementation of version 1.2 of the freedesktop "Desktop Entry specification", see https://specifications.freedesktop.org/desktop-entry-spec/desktop-entry-spec-1.2.html.
Synopsis
- data DesktopEntry = DesktopEntry {
- deType :: DesktopEntryType
- deFilename :: FilePath
- deAttributes :: [(String, String)]
- deCommand :: DesktopEntry -> Maybe String
- deComment :: [String] -> DesktopEntry -> Maybe String
- deHasCategory :: DesktopEntry -> String -> Bool
- deIcon :: DesktopEntry -> Maybe String
- deName :: [String] -> DesktopEntry -> String
- deNoDisplay :: DesktopEntry -> Bool
- deNotShowIn :: DesktopEntry -> [String]
- deOnlyShowIn :: DesktopEntry -> [String]
- getClassNames :: DesktopEntry -> [String]
- getDirectoryEntriesDefault :: IO [DesktopEntry]
- getDirectoryEntry :: [FilePath] -> String -> IO (Maybe DesktopEntry)
- getDirectoryEntryDefault :: String -> IO (Maybe DesktopEntry)
- getXDGDataDirs :: IO [FilePath]
- indexDesktopEntriesBy :: Foldable t => (DesktopEntry -> [String]) -> t DesktopEntry -> MultiMap String DesktopEntry
- indexDesktopEntriesByClassName :: Foldable t => t DesktopEntry -> MultiMap String DesktopEntry
- listDesktopEntries :: String -> FilePath -> IO [DesktopEntry]
- readDesktopEntry :: FilePath -> IO (Either (CPErrorData, String) DesktopEntry)
Documentation
data DesktopEntry Source #
Desktop Entry. All attributes (key-value-pairs) are stored in an association list.
DesktopEntry | |
|
Instances
Eq DesktopEntry Source # | |
Defined in System.Environment.XDG.DesktopEntry (==) :: DesktopEntry -> DesktopEntry -> Bool # (/=) :: DesktopEntry -> DesktopEntry -> Bool # | |
Read DesktopEntry Source # | |
Defined in System.Environment.XDG.DesktopEntry readsPrec :: Int -> ReadS DesktopEntry # readList :: ReadS [DesktopEntry] # | |
Show DesktopEntry Source # | |
Defined in System.Environment.XDG.DesktopEntry showsPrec :: Int -> DesktopEntry -> ShowS # show :: DesktopEntry -> String # showList :: [DesktopEntry] -> ShowS # |
deCommand :: DesktopEntry -> Maybe String Source #
Return the command that should be executed when running this desktop entry.
:: [String] | Preferred languages |
-> DesktopEntry | |
-> Maybe String |
Return the proper comment of the desktop entry, depending on the list of preferred languages.
deHasCategory :: DesktopEntry -> String -> Bool Source #
Determine whether the Category attribute of a desktop entry contains a given value.
:: [String] | Preferred languages |
-> DesktopEntry | |
-> String |
Return the proper name of the desktop entry, depending on the list of preferred languages.
deNoDisplay :: DesktopEntry -> Bool Source #
Return True if the entry must not be displayed
deNotShowIn :: DesktopEntry -> [String] Source #
Return the categories in which the entry shall not be shown
deOnlyShowIn :: DesktopEntry -> [String] Source #
Return the categories in which the entry shall be shown
getClassNames :: DesktopEntry -> [String] Source #
Get all the text elements that could be interpreted as class names from a
DesktopEntry
.
getDirectoryEntriesDefault :: IO [DesktopEntry] Source #
Get all instances of DesktopEntry
for all desktop entry files that can be
found by looking in the directories specified by the XDG specification.
getDirectoryEntry :: [FilePath] -> String -> IO (Maybe DesktopEntry) Source #
Retrieve a desktop entry with a specific name.
getDirectoryEntryDefault :: String -> IO (Maybe DesktopEntry) Source #
Get a desktop entry with a specific name from the default directory entry locations.
getXDGDataDirs :: IO [FilePath] Source #
Get all of the XDG data directories (both global and user).
indexDesktopEntriesBy :: Foldable t => (DesktopEntry -> [String]) -> t DesktopEntry -> MultiMap String DesktopEntry Source #
Construct a Multimap
where each DesktopEntry
in the provided
foldable is indexed by the keys returned from the provided indexing function.
indexDesktopEntriesByClassName :: Foldable t => t DesktopEntry -> MultiMap String DesktopEntry Source #
Construct a multimap where desktop entries are indexed by their class names.
:: String | The extension to use in the search |
-> FilePath | The filepath at which to search |
-> IO [DesktopEntry] |
Return a list of all desktop entries in the given directory.
readDesktopEntry :: FilePath -> IO (Either (CPErrorData, String) DesktopEntry) Source #
Read a desktop entry from a file.