Factor out a findM function (#6125)
This adds a new function to the API: Text.Pandoc.Shared.findM.
This commit is contained in:
parent
12c75701be
commit
f2f559003e
3 changed files with 13 additions and 18 deletions
|
@ -58,7 +58,7 @@ import Text.Pandoc.PDF (makePDF)
|
|||
import Text.Pandoc.SelfContained (makeDataURI, makeSelfContained)
|
||||
import Text.Pandoc.Shared (eastAsianLineBreakFilter, stripEmptyParagraphs,
|
||||
headerShift, isURI, tabFilter, uriPathToPath, filterIpynbOutput,
|
||||
defaultUserDataDirs, tshow)
|
||||
defaultUserDataDirs, tshow, findM)
|
||||
import Text.Pandoc.Writers.Shared (lookupMetaString)
|
||||
import Text.Pandoc.Readers.Markdown (yamlToMeta)
|
||||
import qualified Text.Pandoc.UTF8 as UTF8
|
||||
|
@ -94,13 +94,7 @@ convertWithOpts opts = do
|
|||
datadir <- case optDataDir opts of
|
||||
Nothing -> do
|
||||
ds <- defaultUserDataDirs
|
||||
let selectUserDataDir [] = return Nothing
|
||||
selectUserDataDir (dir:dirs) = do
|
||||
exists <- doesDirectoryExist dir
|
||||
if exists
|
||||
then return (Just dir)
|
||||
else selectUserDataDir dirs
|
||||
selectUserDataDir ds
|
||||
findM doesDirectoryExist ds
|
||||
Just _ -> return $ optDataDir opts
|
||||
|
||||
let runIO' :: PandocIO a -> IO a
|
||||
|
|
|
@ -50,7 +50,7 @@ import Text.Pandoc
|
|||
import Text.Pandoc.App.Opt (Opt (..), LineEnding (..), IpynbOutput (..), addMeta)
|
||||
import Text.Pandoc.Filter (Filter (..))
|
||||
import Text.Pandoc.Highlighting (highlightingStyles)
|
||||
import Text.Pandoc.Shared (ordNub, elemText, safeStrRead, defaultUserDataDirs)
|
||||
import Text.Pandoc.Shared (ordNub, elemText, safeStrRead, defaultUserDataDirs, findM)
|
||||
import Text.Printf
|
||||
|
||||
#ifdef EMBED_DATA_FILES
|
||||
|
@ -118,14 +118,6 @@ engines = map ("html",) htmlEngines ++
|
|||
pdfEngines :: [String]
|
||||
pdfEngines = ordNub $ map snd engines
|
||||
|
||||
findFile :: PandocMonad m => [FilePath] -> m (Maybe FilePath)
|
||||
findFile [] = return Nothing
|
||||
findFile (f:fs) = do
|
||||
exists <- fileExists f
|
||||
if exists
|
||||
then return $ Just f
|
||||
else findFile fs
|
||||
|
||||
-- | A list of functions, each transforming the options data structure
|
||||
-- in response to a command-line option.
|
||||
options :: [OptDescr (Opt -> IO Opt)]
|
||||
|
@ -996,7 +988,7 @@ applyDefaults opt file = runIOorExplode $ do
|
|||
Nothing -> map (</> ("defaults" </> fp))
|
||||
dataDirs
|
||||
Just dd -> [dd </> "defaults" </> fp]
|
||||
fp' <- fromMaybe fp <$> findFile fps
|
||||
fp' <- fromMaybe fp <$> findM fileExists fps
|
||||
inp <- readFileLazy fp'
|
||||
case Y.decode1 inp of
|
||||
Right (f :: Opt -> Opt) -> return $ f opt
|
||||
|
|
|
@ -27,6 +27,7 @@ module Text.Pandoc.Shared (
|
|||
splitTextByIndices,
|
||||
substitute,
|
||||
ordNub,
|
||||
findM,
|
||||
-- * Text processing
|
||||
ToString (..),
|
||||
ToText (..),
|
||||
|
@ -198,6 +199,14 @@ ordNub l = go Set.empty l
|
|||
go s (x:xs) = if x `Set.member` s then go s xs
|
||||
else x : go (Set.insert x s) xs
|
||||
|
||||
findM :: forall m t a. (Monad m, Foldable t) => (a -> m Bool) -> t a -> m (Maybe a)
|
||||
findM p = foldr go (pure Nothing)
|
||||
where
|
||||
go :: a -> m (Maybe a) -> m (Maybe a)
|
||||
go x acc = do
|
||||
b <- p x
|
||||
if b then pure (Just x) else acc
|
||||
|
||||
--
|
||||
-- Text processing
|
||||
--
|
||||
|
|
Loading…
Add table
Reference in a new issue