@@ -53,44 +53,56 @@ Note: the metadata from the included source files are discarded.
53
53
54
54
-}
55
55
56
+ {-# LANGUAGE BangPatterns #-}
57
+
56
58
import Control.Monad
57
59
import Data.List
58
60
import System.Directory
61
+ import System.IO
59
62
60
63
import Text.Pandoc
61
64
import Text.Pandoc.Error
62
65
import Text.Pandoc.JSON
66
+ import qualified Text.Pandoc.Builder as B
67
+
63
68
64
69
stripPandoc :: Either PandocError Pandoc -> [Block ]
65
70
stripPandoc p =
66
71
case p of
67
72
Left _ -> [Null ]
68
73
Right (Pandoc _ blocks) -> blocks
69
74
70
- ioReadMarkdown :: String -> IO (Either PandocError Pandoc )
71
- ioReadMarkdown content = return $! readMarkdown def content
72
-
73
75
getContent :: String -> IO [Block ]
74
76
getContent file = do
75
- c <- readFile file
76
- p <- ioReadMarkdown c
77
- return $! stripPandoc p
77
+ let handle = openFile file ReadMode
78
+ ! contents <- fmap hGetContents handle
79
+ fmap hClose handle
80
+ let p = fmap (readMarkdown def) contents
81
+ fmap stripPandoc p
78
82
79
- getProcessableFileList :: String -> IO [String ]
83
+ getProcessableFileList :: String -> [String ]
80
84
getProcessableFileList list = do
81
85
let f = lines list
82
- let files = filter (\ x -> not $ " #" `isPrefixOf` x) f
83
- filterM doesFileExist files
86
+ filter (\ x -> not $ " #" `isPrefixOf` x) f
84
87
85
88
processFiles :: [String ] -> IO [Block ]
86
89
processFiles toProcess =
87
90
fmap concat (mapM getContent toProcess)
88
91
92
+ simpleInclude :: String -> IO [Block ]
93
+ simpleInclude list = do
94
+ let toProcess = getProcessableFileList list
95
+ processFiles toProcess
96
+
89
97
doInclude :: Block -> IO [Block ]
90
98
doInclude (CodeBlock (_, classes, _) list)
91
- | " include" `elem` classes = do
92
- let toProcess = getProcessableFileList list
93
- processFiles =<< toProcess
99
+ | " code" `elem` classes = do
100
+ let filePath = head $ lines list
101
+ let content = withFile filePath ReadMode hGetContents
102
+ let newclasses = filter (\ x -> " include" `isPrefixOf` x || " code" `isPrefixOf` x) classes
103
+ let blocks = fmap (B. codeBlockWith (" " , newclasses, [] )) content
104
+ fmap B. toList blocks
105
+ | " include" `elem` classes = simpleInclude list
94
106
doInclude x = return [x]
95
107
96
108
main :: IO ()
0 commit comments