Skip to content
70 changes: 56 additions & 14 deletions IncludeFilter.hs
Original file line number Diff line number Diff line change
@@ -1,5 +1,7 @@
#!/usr/bin/env runhaskell

{-# LANGUAGE ViewPatterns #-}

{-
The MIT License (MIT)

Expand Down Expand Up @@ -51,46 +53,86 @@ will be inserted and not parsed.

Note: the metadata from the included source files are discarded.

Alternatively, use one of the following to increase all the header levels in the
included file. The first option is a shortcut for incrementing the level by 1.
The second demonstrates an increase of 2.

> ```include-indented

> ```{ .include header-change=2 }

If the header level is increased, the title from the included file is inserted at the
beginning of the included file as a header, at the level of the header level change. For
example, if the header is incremented by 1, the title is inserted as a level 1 heading.

-}

import Control.Monad
import Data.List
import qualified Data.Char as C
import qualified Data.Map as Map
import Control.Error (readMay, fromMaybe)
import System.Directory

import Text.Pandoc
import Text.Pandoc.Shared (uniqueIdent, stringify)
import Text.Pandoc.Error
import Text.Pandoc.JSON

stripPandoc :: Either PandocError Pandoc -> [Block]
stripPandoc p =
case p of
Left _ -> [Null]
Right (Pandoc _ blocks) -> blocks
import Text.Pandoc.Walk

stripPandoc :: Int -> Either PandocError Pandoc -> [Block]
stripPandoc _ (Left _) = [Null]
stripPandoc changeInHeaderLevel (Right (Pandoc meta blocks)) = maybe id (:) (title meta) $ modBlocks
where
modBlocks = modifyHeaderLevelBlockWith changeInHeaderLevel <$> blocks
title (Meta (Map.lookup "title" -> Just (MetaInlines inls))) = do
guard $ changeInHeaderLevel > 0
Just $ Header changeInHeaderLevel (titleRef inls,["section-title"],[]) inls
title _ = Nothing
-- WARNING titleRef doesn't check that titles are unique; for that try uniqueIdent.
titleRef = stringify . fmap (lowerCase . dashFromSpace)
dashFromSpace Space = Str "-"
dashFromSpace x = x
lowerCase (Str x) = Str (fmap C.toLower x)
lowerCase x = x

modifyHeaderLevelBlockWith :: Int -> Block -> Block
modifyHeaderLevelBlockWith n (Header int att inls) = Header (int + n) att inls
modifyHeaderLevelBlockWith _ x = x

modifyHeaderLevelWith :: Int -> Pandoc -> Pandoc
modifyHeaderLevelWith n = walk (modifyHeaderLevelBlockWith n)

ioReadMarkdown :: String -> IO(Either PandocError Pandoc)
ioReadMarkdown content = return $! readMarkdown def content

getContent :: String -> IO [Block]
getContent file = do
getContent :: Int -> String -> IO [Block]
getContent changeInHeaderLevel file = do
c <- readFile file
p <- ioReadMarkdown c
return $! stripPandoc p
return $! stripPandoc changeInHeaderLevel p

getProcessableFileList :: String -> IO [String]
getProcessableFileList list = do
let f = lines list
let files = filter (\x -> not $ "#" `isPrefixOf` x) f
filterM doesFileExist files

processFiles :: [String] -> IO [Block]
processFiles toProcess =
fmap concat (mapM getContent toProcess)
processFiles :: Int -> [String] -> IO [Block]
processFiles changeInHeaderLevel toProcess =
fmap concat (getContent changeInHeaderLevel `mapM` toProcess)

doInclude :: Block -> IO [Block]
doInclude (CodeBlock (_, classes, _) list)
doInclude (CodeBlock (_, classes, options) list)
| "include" `elem` classes = do
let toProcess = getProcessableFileList list
processFiles =<< toProcess
changeInHeaderLevel = fromMaybe 0 $ readMay =<< "header-change" `lookup` options
processFiles changeInHeaderLevel =<< toProcess
| "include-indented" `elem` classes =
doInclude $ CodeBlock ("", newClasses, newOptions) list
where
newClasses = ("include" :) . delete "include-indented" $ classes
newOptions = ("header-change","1") : options
doInclude x = return [x]

main :: IO ()
Expand Down
32 changes: 24 additions & 8 deletions README.md
Original file line number Diff line number Diff line change
Expand Up @@ -10,14 +10,11 @@ The Code Blocks like the following will include every file in a new line. The
reference paths should be either absolute or relative to the folder where the
pandoc command will be executed.

```markdown
```include
/absolute/file/path.md
relative/to/the/command/root.md
#do/not/include/this.md
```
```

```include
/absolute/file/path.md
relative/to/the/command/root.md
#do/not/include/this.md
```
If the file does not exist, it will be skipped completely. No warnings, no
residue, nothing. Putting an `#` as the first character in the line will make the
filter skip that file.
Expand All @@ -27,6 +24,19 @@ will be inserted and not parsed.

*Note: the metadata from the included source files are discarded.*

Alternatively, use one of the following to increase all the header levels in the
included file. The first option is a shortcut for incrementing the level by 1.
The second demonstrates an increase of 2.

```include-indented

```{ .include header-change=2 }


If the header level is increased, the title from the included file is inserted at the
beginning of the included file as a header, at the level of the header level change. For
example, if the header is incremented by 1, the title is inserted as a level 1 heading.

## Installation
One could either install it using the Cabal packaging system by running:

Expand All @@ -50,6 +60,12 @@ All this does in the background is pipelining the output of Pandoc and the last
pandoc --from markdown --to json input.md | runhaskell IncludeFilter.hs | pandoc --from json --to latex
```

If using *pandoc-include* together with [*pandoc-citeproc*](https://github.com/jgm/pandoc-citeproc) one has to pay attention to the order of the filters: 1. *pandoc-include*, 2. *pandoc-citeproc*.

```
pandoc -o output.md --filter pandoc-include --filter pandoc-citeproc input.md
```

## License
Copyright ©2015 [Dániel Stein](https://twitter.com/steindani)

Expand Down
6 changes: 5 additions & 1 deletion pandoc-include.cabal
Original file line number Diff line number Diff line change
@@ -1,5 +1,5 @@
Name: pandoc-include
Version: 0.0.1
Version: 0.0.2
Synopsis: Include other Markdown files
Description: A Pandoc filter that replaces include labeled
Code Blocks with the contents of the referenced
Expand All @@ -23,6 +23,8 @@ Source-repository head

Library
Build-Depends: base >= 4.6 && < 5,
containers >= 0.3,
errors >= 2.0.0,
text >= 0.11,
pandoc >= 1.13.0.0,
pandoc-types >= 1.12.0.0,
Expand All @@ -35,6 +37,8 @@ Library

Executable pandoc-include
Build-Depends: base >= 4.6,
containers >= 0.3,
errors >= 2.0.0,
text >= 0.11,
pandoc >= 1.13.0.0,
pandoc-types >= 1.12.0.0,
Expand Down
5 changes: 5 additions & 0 deletions stack.yaml
Original file line number Diff line number Diff line change
@@ -0,0 +1,5 @@
flags: {}
resolver: lts-6.4
packages:
- '.'
extra-deps: []
4 changes: 4 additions & 0 deletions test/alpha.md
Original file line number Diff line number Diff line change
@@ -1,3 +1,7 @@
% The Title is Alpha
% An author
% 11 Aug 2016

# Alpha!

Text from alpha.
Expand Down
8 changes: 8 additions & 0 deletions test/input.md
Original file line number Diff line number Diff line change
Expand Up @@ -11,4 +11,12 @@ gamma.md
beta.md
```

```include-indented
alpha.md
```

```{ .include header-change=2 }
alpha.md
```

text