Add new exported function defaultUserDataDirs
This commit is contained in:
parent
068fff2023
commit
a99423b59c
1 changed files with 17 additions and 1 deletions
|
@ -3,7 +3,6 @@
|
||||||
{-# LANGUAGE DeriveDataTypeable #-}
|
{-# LANGUAGE DeriveDataTypeable #-}
|
||||||
{-# LANGUAGE FlexibleContexts #-}
|
{-# LANGUAGE FlexibleContexts #-}
|
||||||
{-# LANGUAGE MultiParamTypeClasses #-}
|
{-# LANGUAGE MultiParamTypeClasses #-}
|
||||||
|
|
||||||
{-# LANGUAGE ScopedTypeVariables #-}
|
{-# LANGUAGE ScopedTypeVariables #-}
|
||||||
{-# LANGUAGE ViewPatterns #-}
|
{-# LANGUAGE ViewPatterns #-}
|
||||||
{-# LANGUAGE FlexibleInstances #-}
|
{-# LANGUAGE FlexibleInstances #-}
|
||||||
|
@ -90,6 +89,8 @@ module Text.Pandoc.Shared (
|
||||||
safeRead,
|
safeRead,
|
||||||
-- * Temp directory
|
-- * Temp directory
|
||||||
withTempDir,
|
withTempDir,
|
||||||
|
-- * User data directory
|
||||||
|
defaultUserDataDirs,
|
||||||
-- * Version
|
-- * Version
|
||||||
pandocVersion
|
pandocVersion
|
||||||
) where
|
) where
|
||||||
|
@ -910,3 +911,18 @@ withTempDir =
|
||||||
#else
|
#else
|
||||||
withSystemTempDirectory
|
withSystemTempDirectory
|
||||||
#endif
|
#endif
|
||||||
|
|
||||||
|
--
|
||||||
|
-- User data directory
|
||||||
|
--
|
||||||
|
|
||||||
|
-- | Return appropriate user data directory for platform. We use
|
||||||
|
-- XDG_DATA_HOME (or its default value), but fall back to the
|
||||||
|
-- legacy user data directory ($HOME/.pandoc on *nix) if this is
|
||||||
|
-- missing.
|
||||||
|
defaultUserDataDirs :: IO [FilePath]
|
||||||
|
defaultUserDataDirs = E.catch (do
|
||||||
|
xdgDir <- getXdgDirectory XdgData "pandoc"
|
||||||
|
legacyDir <- getAppUserDataDirectory "pandoc"
|
||||||
|
return $ ordNub [xdgDir, legacyDir])
|
||||||
|
(\(_ :: E.SomeException) -> return [])
|
||||||
|
|
Loading…
Reference in a new issue