summaryrefslogtreecommitdiffstats
path: root/src/Main.hs
diff options
context:
space:
mode:
Diffstat (limited to 'src/Main.hs')
-rw-r--r--src/Main.hs35
1 files changed, 29 insertions, 6 deletions
diff --git a/src/Main.hs b/src/Main.hs
index 3a87cff..ea3cc64 100644
--- a/src/Main.hs
+++ b/src/Main.hs
@@ -1,3 +1,5 @@
+{-# LANGUAGE OverloadedRecordDot #-}
+
-- |
-- Module : Main
-- Description : Command-line interface for org-zk
@@ -29,6 +31,7 @@ module Main where
import Control.Exception (ioError)
import Control.Logging
+import Data.Map.Strict (intersection)
import qualified Data.Text as T
import Data.Version (showVersion)
import Paths_org_zk (version)
@@ -223,7 +226,9 @@ data Options = Options
-- | Csl FILE
optCsl :: Maybe FilePath,
-- | Index FILE (default: org-zettelkasten-index)
- optIndex :: Maybe FilePath,
+ optIndexFile :: Maybe FilePath,
+ -- | Only process these indices
+ optIndex :: [ZettelId],
-- | output DIR
optOutput :: Maybe FilePath,
-- | Verbose output while processing files
@@ -243,7 +248,8 @@ defaultOptions =
{ optBibliography = Nothing,
optOrgBibliography = Nothing,
optCsl = Nothing,
- optIndex = Nothing,
+ optIndexFile = Nothing,
+ optIndex = [],
optOutput = Nothing,
optVerbose = 0,
optQuiet = False,
@@ -251,6 +257,9 @@ defaultOptions =
optShowHelp = False
}
+parseIdList :: Text -> [ZettelId]
+parseIdList = fmap ZettelId . T.splitOn ","
+
options :: [OptDescr (Options -> Options)]
options =
[ Option
@@ -264,15 +273,21 @@ options =
(ReqArg (\f opts -> opts {optCsl = Just f}) "FILE")
"Csl FILE",
Option
+ ['f']
+ ["index-file"]
+ (ReqArg (\f opts -> opts {optIndexFile = Just f}) "FILE")
+ "Index FILE (default: org-zettelkasten-index)",
+ Option
['h']
["help"]
(NoArg (\opts -> opts {optShowHelp = True}))
"Show this help menu",
Option
['i']
- ["index"]
- (ReqArg (\f opts -> opts {optIndex = Just f}) "FILE")
- "Index FILE (default: org-zettelkasten-index)",
+ ["id"]
+ (ReqArg (\f opts -> opts {optIndex = opts.optIndex
+ ++ parseIdList (T.pack f)}) "ID")
+ "Only process these IDs",
Option
['o']
["output"]
@@ -312,6 +327,14 @@ compilerOpts argv =
(o, n, []) -> return (foldl' (flip id) defaultOptions o, n)
(_, _, errs) -> ioError (userError (concat errs ++ usageInfo headerOpts options))
+filterWithIds :: [ZettelId] -> ZettelGraph -> ZettelGraph
+filterWithIds [] zg = zg
+filterWithIds ids (ZettelGraph zidMap bibMap) =
+ ZettelGraph (intersection zidMap zidMapFilter) (intersection bibMap bibMapFilter)
+ where
+ zidMapFilter = fromList $ map (\x -> (x, ())) ids
+ bibMapFilter = fromList $ map (\(ZettelId t) -> (BibId t, ())) ids
+
main :: IO ()
main = withStderrLogging $ do
(zkOpts, fl) <- getArgs >>= compilerOpts
@@ -345,4 +368,4 @@ main = withStderrLogging $ do
)
(optBibliography zkOpts)
(fromMaybe "output" (optOutput zkOpts))
- (pipeline graph)
+ (filterWithIds (optIndex zkOpts) $ pipeline graph)