{-# LANGUAGE OverloadedStrings #-} {-| Module : Columns Description : When a code block has the "include" label, treat it as a list of files to include. Copyright : (c) Amy de Buitléir, 2023 License : BSD--3 Maintainer : amy@nualeargais.ie Stability : experimental Portability : POSIX See for information on how to use this filter. -} module Text.Pandoc.Filters.Include ( transform ) where import Data.Text qualified as T import Network.URI (isURI) import System.FilePath (combine, isAbsolute, isRelative, takeDirectory) import Text.Pandoc qualified as P import Text.Pandoc.UTF8 qualified as U import Text.Pandoc.Walk (walk) transform :: FilePath -> P.Block -> IO [P.Block] transform d b@(P.CodeBlock (_, classes, kvs) s) | "include" `elem` classes = doIncludes d kvs s | otherwise = return [b] transform _ b = return [b] doIncludes :: FilePath -> [(T.Text, T.Text)] -> T.Text -> IO [P.Block] doIncludes d kvs s = concat <$> mapM (doInclude d levelAdjustment) fs where fs = lines $ T.unpack s levelAdjustment = case lookup "level" kvs of Just v -> read $ T.unpack v Nothing -> 0 -- Note: This will terminate automatically when there are no further transformations. doInclude :: FilePath -> Int -> FilePath -> IO [P.Block] doInclude dir levelAdj f = do let path = if isRelative f then combine dir f else f let includeDir = takeDirectory path p <- readMarkdownFromFile path let (P.Pandoc _ bs) = walk (adjustImagePaths includeDir) p bs' <- concat <$> mapM (transform $ takeDirectory path) bs return $ map (adjustHeaderLevel levelAdj) bs' readMarkdownFromFile :: FilePath -> IO P.Pandoc readMarkdownFromFile f = U.readFile f >>= parseMarkdown parseMarkdown :: T.Text -> IO P.Pandoc parseMarkdown s = P.runIO (P.readMarkdown markdownReaderOptions s) >>= P.handleError markdownReaderOptions :: P.ReaderOptions markdownReaderOptions = P.def { P.readerStandalone = True, P.readerExtensions = P.pandocExtensions } adjustHeaderLevel :: Int -> P.Block -> P.Block adjustHeaderLevel n (P.Header m attr xs) | m' <= 0 = P.Para xs | otherwise = P.Header m' attr xs where m' = n + m adjustHeaderLevel _ b = b adjustImagePaths :: FilePath -> P.Inline -> P.Inline adjustImagePaths dir (P.Image attr xs (url, title)) = P.Image attr xs (adjustFilePath dir url, title) adjustImagePaths _ x = x adjustFilePath :: FilePath -> T.Text -> T.Text adjustFilePath dir url | isURI s = url | isAbsolute s = url | otherwise = T.pack $ combine dir s where s = T.unpack url {- Useful for debugging in GHCi :l Text.Pandoc.Filters.Include (P.Pandoc _ bs) <- readMarkdownFromFile "test-files/test.md" concat <$> mapM (transform "test-files") bs -}