diff options
| -rw-r--r-- | src/Text/Pandoc/Parsing.hs | 61 | ||||
| -rw-r--r-- | src/Text/Pandoc/Readers/Org/Blocks.hs | 3 | ||||
| -rw-r--r-- | src/Text/Pandoc/Readers/Org/Parsing.hs | 3 | 
3 files changed, 34 insertions, 33 deletions
| diff --git a/src/Text/Pandoc/Parsing.hs b/src/Text/Pandoc/Parsing.hs index 11c4c7a62..cbe9993c6 100644 --- a/src/Text/Pandoc/Parsing.hs +++ b/src/Text/Pandoc/Parsing.hs @@ -121,7 +121,6 @@ module Text.Pandoc.Parsing ( module Text.Pandoc.Sources,                               (<+?>),                               extractIdClass,                               insertIncludedFile, -                             insertIncludedFileF,                               -- * Re-exports from Text.Parsec                               Stream,                               runParser, @@ -1638,12 +1637,15 @@ extractIdClass (ident, cls, kvs) = (ident', cls', kvs')      cls'   = maybe cls T.words $ lookup "class" kvs      kvs'   = filter (\(k,_) -> k /= "id" || k /= "class") kvs -insertIncludedFile' :: (PandocMonad m, HasIncludeFiles st) -                    => ParserT a st m (mf Blocks) -                    -> (Text -> a) -                    -> [FilePath] -> FilePath -                    -> ParserT a st m (mf Blocks) -insertIncludedFile' blocks totoks dirs f = do +insertIncludedFile :: (PandocMonad m, HasIncludeFiles st) +                   => ParserT a st m b -- ^ parser to apply +                   -> (Text -> a) -- ^ convert Text to stream type +                   -> [FilePath]  -- ^ search path (directories) +                   -> FilePath    -- ^ path of file to include +                   -> Maybe Int   -- ^ start line (negative counts from end) +                   -> Maybe Int   -- ^ end line (negative counts from end) +                   -> ParserT a st m b +insertIncludedFile parser toStream dirs f mbstartline mbendline = do    oldPos <- getPosition    oldInput <- getInput    containers <- getIncludeFiles <$> getState @@ -1652,33 +1654,32 @@ insertIncludedFile' blocks totoks dirs f = do    updateState $ addIncludeFile $ T.pack f    mbcontents <- readFileFromDirs dirs f    contents <- case mbcontents of -                   Just s -> return s +                   Just s -> return $ exciseLines mbstartline mbendline s                     Nothing -> do                       report $ CouldNotLoadIncludeFile (T.pack f) oldPos                       return "" -  setPosition $ newPos f 1 1 -  setInput $ totoks contents -  bs <- blocks +  setInput $ toStream contents +  setPosition $ newPos f (fromMaybe 1 mbstartline) 1 +  result <- parser    setInput oldInput    setPosition oldPos    updateState dropLatestIncludeFile -  return bs +  return result + +exciseLines :: Maybe Int -> Maybe Int -> Text -> Text +exciseLines Nothing Nothing t = t +exciseLines mbstartline mbendline t = +  T.unlines $ take (endline' - (startline' - 1)) +            $ drop (startline' - 1) contentLines + where +  contentLines = T.lines t +  numLines = length contentLines +  startline' = case mbstartline of +                 Nothing -> 1 +                 Just x | x >= 0 -> x +                        | otherwise -> numLines + x -- negative from end +  endline' = case mbendline of +                 Nothing -> numLines +                 Just x | x >= 0 -> x +                        | otherwise -> numLines + x -- negative from end --- | Parse content of include file as blocks. Circular includes result in an --- @PandocParseError@. -insertIncludedFile :: (PandocMonad m, HasIncludeFiles st) -                   => ParserT [a] st m Blocks -                   -> (Text -> [a]) -                   -> [FilePath] -> FilePath -                   -> ParserT [a] st m Blocks -insertIncludedFile blocks totoks dirs f = -  runIdentity <$> insertIncludedFile' (Identity <$> blocks) totoks dirs f - --- TODO: replace this with something using addToSources. --- | Parse content of include file as future blocks. Circular includes result in --- an @PandocParseError@. -insertIncludedFileF :: (PandocMonad m, HasIncludeFiles st) -                    => ParserT Sources st m (Future st Blocks) -                    -> [FilePath] -> FilePath -                    -> ParserT Sources st m (Future st Blocks) -insertIncludedFileF p = insertIncludedFile' p (\t -> Sources [(initialPos "",t)]) diff --git a/src/Text/Pandoc/Readers/Org/Blocks.hs b/src/Text/Pandoc/Readers/Org/Blocks.hs index 883434cdc..5e15c2c36 100644 --- a/src/Text/Pandoc/Readers/Org/Blocks.hs +++ b/src/Text/Pandoc/Readers/Org/Blocks.hs @@ -44,6 +44,7 @@ import Data.List.NonEmpty (nonEmpty)  import qualified Data.Text as T  import qualified Text.Pandoc.Builder as B  import qualified Text.Pandoc.Walk as Walk +import Text.Pandoc.Sources (ToSources(..))  --  -- parsing blocks @@ -527,7 +528,7 @@ include = try $ do                       _ -> nullAttr          return $ pure . B.codeBlockWith attr <$> parseRaw        _ -> return $ return . B.fromList . blockFilter params <$> blockList -  insertIncludedFileF blocksParser ["."] filename +  insertIncludedFile blocksParser toSources ["."] filename Nothing Nothing   where    includeTarget :: PandocMonad m => OrgParser m FilePath    includeTarget = do diff --git a/src/Text/Pandoc/Readers/Org/Parsing.hs b/src/Text/Pandoc/Readers/Org/Parsing.hs index c7ea02815..701bf3398 100644 --- a/src/Text/Pandoc/Readers/Org/Parsing.hs +++ b/src/Text/Pandoc/Readers/Org/Parsing.hs @@ -63,8 +63,7 @@ module Text.Pandoc.Readers.Org.Parsing    , ellipses    , citeKey    , gridTableWith -  , insertIncludedFileF -  -- * Re-exports from Text.Pandoc.Parsec +  , insertIncludedFile    , runParser    , runParserT    , getInput | 
