Safe Haskell | Safe-Inferred |
---|---|
Language | GHC2021 |
Synopsis
- module BasePrelude
- data ByteString
- data Map k a
- data XdgDirectory = XdgConfig
- type Type = TYPE LiftedRep
- ifM :: Monad m => m Bool -> m a -> m a -> m a
- doesFileExist :: FilePath -> IO Bool
- proc :: FilePath -> [String] -> CreateProcess
- getXdgDirectory :: XdgDirectory -> FilePath -> IO FilePath
- spawnCommand :: String -> IO ProcessHandle
- createDirectoryIfMissing :: Bool -> FilePath -> IO ()
- type ShowBS = ByteString -> ByteString
- data OpenIn
- type Items = Map ByteString Double
- tryAddPrefix :: ByteString -> ByteString -> ByteString
- (<</>>) :: Functor f => f FilePath -> FilePath -> f FilePath
- (</>) :: FilePath -> FilePath -> FilePath
- hdmenuPath :: IO FilePath
- histFile :: IO FilePath
- spawn :: ByteString -> IO ()
- openWith :: OpenIn -> ByteString -> ByteString
Better prelude
module BasePrelude
data ByteString #
A space-efficient representation of a Word8
vector, supporting many
efficient operations.
A ByteString
contains 8-bit bytes, or by using the operations from
Data.ByteString.Char8 it can be interpreted as containing 8-bit
characters.
Instances
A Map from keys k
to values a
.
The Semigroup
operation for Map
is union
, which prefers
values from the left operand. If m1
maps a key k
to a value
a1
, and m2
maps the same key to a different value a2
, then
their union m1 <> m2
maps k
to a1
.
Instances
Bifoldable Map | Since: containers-0.6.3.1 |
Eq2 Map | Since: containers-0.5.9 |
Ord2 Map | Since: containers-0.5.9 |
Defined in Data.Map.Internal | |
Show2 Map | Since: containers-0.5.9 |
Hashable2 Map | Since: hashable-1.3.4.0 |
Defined in Data.Hashable.Class | |
(Lift k, Lift a) => Lift (Map k a :: Type) | Since: containers-0.6.6 |
Foldable (Map k) | Folds in order of increasing key. |
Defined in Data.Map.Internal fold :: Monoid m => Map k m -> m # foldMap :: Monoid m => (a -> m) -> Map k a -> m # foldMap' :: Monoid m => (a -> m) -> Map k a -> m # foldr :: (a -> b -> b) -> b -> Map k a -> b # foldr' :: (a -> b -> b) -> b -> Map k a -> b # foldl :: (b -> a -> b) -> b -> Map k a -> b # foldl' :: (b -> a -> b) -> b -> Map k a -> b # foldr1 :: (a -> a -> a) -> Map k a -> a # foldl1 :: (a -> a -> a) -> Map k a -> a # elem :: Eq a => a -> Map k a -> Bool # maximum :: Ord a => Map k a -> a # minimum :: Ord a => Map k a -> a # | |
Eq k => Eq1 (Map k) | Since: containers-0.5.9 |
Ord k => Ord1 (Map k) | Since: containers-0.5.9 |
Defined in Data.Map.Internal | |
(Ord k, Read k) => Read1 (Map k) | Since: containers-0.5.9 |
Defined in Data.Map.Internal | |
Show k => Show1 (Map k) | Since: containers-0.5.9 |
Traversable (Map k) | Traverses in order of increasing key. |
Functor (Map k) | |
Hashable k => Hashable1 (Map k) | Since: hashable-1.3.4.0 |
Defined in Data.Hashable.Class | |
(Data k, Data a, Ord k) => Data (Map k a) | |
Defined in Data.Map.Internal gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Map k a -> c (Map k a) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Map k a) # toConstr :: Map k a -> Constr # dataTypeOf :: Map k a -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Map k a)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Map k a)) # gmapT :: (forall b. Data b => b -> b) -> Map k a -> Map k a # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Map k a -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Map k a -> r # gmapQ :: (forall d. Data d => d -> u) -> Map k a -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Map k a -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Map k a -> m (Map k a) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Map k a -> m (Map k a) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Map k a -> m (Map k a) # | |
Ord k => Monoid (Map k v) | |
Ord k => Semigroup (Map k v) | |
Ord k => IsList (Map k v) | Since: containers-0.5.6.2 |
(Ord k, Read k, Read e) => Read (Map k e) | |
(Show k, Show a) => Show (Map k a) | |
(NFData k, NFData a) => NFData (Map k a) | |
Defined in Data.Map.Internal | |
(Eq k, Eq a) => Eq (Map k a) | |
(Ord k, Ord v) => Ord (Map k v) | |
(Hashable k, Hashable v) => Hashable (Map k v) | Since: hashable-1.3.4.0 |
Defined in Data.Hashable.Class | |
type Item (Map k v) | |
Defined in Data.Map.Internal |
data XdgDirectory #
Special directories for storing user-specific application data, configuration, and cache files, as specified by the XDG Base Directory Specification.
Note: On Windows, XdgData
and XdgConfig
usually map to the same
directory.
Since: directory-1.2.3.0
XdgConfig | For configuration files.
It uses the |
Instances
doesFileExist :: FilePath -> IO Bool #
The operation doesFileExist
returns True
if the argument file exists and is not a directory, and False
otherwise.
proc :: FilePath -> [String] -> CreateProcess #
Construct a CreateProcess
record for passing to createProcess
,
representing a raw command with arguments.
See RawCommand
for precise semantics of the specified FilePath
.
:: XdgDirectory | which special directory |
-> FilePath | a relative path that is appended to the path; if empty, the base path is returned |
-> IO FilePath |
Obtain the paths to special directories for storing user-specific
application data, configuration, and cache files, conforming to the
XDG Base Directory Specification.
Compared with getAppUserDataDirectory
, this function provides a more
fine-grained hierarchy as well as greater flexibility for the user.
On Windows, XdgData
and XdgConfig
usually map to the same directory
unless overridden.
Refer to the docs of XdgDirectory
for more details.
The second argument is usually the name of the application. Since it will be integrated into the path, it must consist of valid path characters. Note: if the second argument is an absolute path, it will just return the second argument.
Note: The directory may not actually exist, in which case you would need
to create it with file mode 700
(i.e. only accessible by the owner).
As of 1.3.5.0, the environment variable is ignored if set to a relative path, per revised XDG Base Directory Specification. See #100.
Since: directory-1.2.3.0
spawnCommand :: String -> IO ProcessHandle #
Creates a new process to run the specified shell command.
It does not wait for the program to finish, but returns the ProcessHandle
.
Since: process-1.2.0.0
creates a new directory
createDirectoryIfMissing
parents dirdir
if it doesn't exist. If the first argument is True
the function will also create all parent directories if they are missing.
Types
type ShowBS = ByteString -> ByteString Source #
ShowS
for ByteString
because it is shorter :>.
type Items = Map ByteString Double Source #
Type for an Map that describes all of the executables with their ratings.
Combining file paths
tryAddPrefix :: ByteString -> ByteString -> ByteString Source #
Add a prefix to a string if it does not start with "/".
This will ensure the user can specify absolute paths to files, but also
conveniently use relative paths (starting from $HOME
) if that is
desired.
(<</>>) :: Functor f => f FilePath -> FilePath -> f FilePath infixr 5 Source #
Functorial path-append operation.
(</>) :: FilePath -> FilePath -> FilePath infixr 5 Source #
Combine two paths into a new path. Adapted from: https://hackage.haskell.org/package/filepath
System file paths
hdmenuPath :: IO FilePath Source #
Path to the hdmenu directory.
XDG_CONFIG_HOME/hdmenu
, so probably ~/.config/hdmenu
.
Running commands
spawn :: ByteString -> IO () Source #
Spawn a command and forget about it.
:: OpenIn | How (and with what) to open something. |
-> ByteString | The thing to open. |
-> ByteString |
Open something.