initial
This commit is contained in:
parent
2eab8f4654
commit
fd3676a568
5 changed files with 140 additions and 0 deletions
|
@ -458,6 +458,7 @@ library
|
|||
Text.Pandoc.Readers.Odt,
|
||||
Text.Pandoc.Readers.EPUB,
|
||||
Text.Pandoc.Readers.Muse,
|
||||
Text.Pandoc.Readers.Man,
|
||||
Text.Pandoc.Writers,
|
||||
Text.Pandoc.Writers.Native,
|
||||
Text.Pandoc.Writers.Docbook,
|
||||
|
@ -662,6 +663,7 @@ test-suite test-pandoc
|
|||
Tests.Readers.EPUB
|
||||
Tests.Readers.Muse
|
||||
Tests.Readers.Creole
|
||||
Tests.Readers.Man
|
||||
Tests.Writers.Native
|
||||
Tests.Writers.ConTeXt
|
||||
Tests.Writers.Docbook
|
||||
|
|
|
@ -101,6 +101,7 @@ import Text.Pandoc.Readers.TikiWiki
|
|||
import Text.Pandoc.Readers.TWiki
|
||||
import Text.Pandoc.Readers.Txt2Tags
|
||||
import Text.Pandoc.Readers.Vimwiki
|
||||
import Text.Pandoc.Readers.Man
|
||||
import Text.Pandoc.Shared (mapLeft)
|
||||
import qualified Text.Pandoc.UTF8 as UTF8
|
||||
import Text.Parsec.Error
|
||||
|
@ -141,6 +142,7 @@ readers = [ ("native" , TextReader readNative)
|
|||
,("t2t" , TextReader readTxt2Tags)
|
||||
,("epub" , ByteStringReader readEPUB)
|
||||
,("muse" , TextReader readMuse)
|
||||
,("man" , TextReader readMan)
|
||||
]
|
||||
|
||||
-- | Retrieve reader, extensions based on formatSpec (format+extensions).
|
||||
|
|
118
src/Text/Pandoc/Readers/Man.hs
Normal file
118
src/Text/Pandoc/Readers/Man.hs
Normal file
|
@ -0,0 +1,118 @@
|
|||
{-
|
||||
Copyright (C) 2018 Yan Pashkovsky <yanp.bugz@gmail.com>
|
||||
|
||||
This program is free software; you can redistribute it and/or modify
|
||||
it under the terms of the GNU General Public License as published by
|
||||
the Free Software Foundation; either version 2 of the License, or
|
||||
(at your option) any later version.
|
||||
|
||||
This program is distributed in the hope that it will be useful,
|
||||
but WITHOUT ANY WARRANTY; without even the implied warranty of
|
||||
MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
|
||||
GNU General Public License for more details.
|
||||
|
||||
You should have received a copy of the GNU General Public License
|
||||
along with this program; if not, write to the Free Software
|
||||
Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA 02111-1307 USA
|
||||
-}
|
||||
|
||||
{- |
|
||||
Module : Text.Pandoc.Readers.Man
|
||||
Copyright : Copyright (C) 2018 Yan Pashkovsky
|
||||
License : GNU GPL, version 2 or above
|
||||
|
||||
Maintainer : Yan Pashkovsky <yanp.bugz@gmail.com>
|
||||
Stability : WIP
|
||||
Portability : portable
|
||||
|
||||
Conversion of man to 'Pandoc' document.
|
||||
-}
|
||||
module Text.Pandoc.Readers.Man where
|
||||
|
||||
import Control.Monad.Except (liftM2, throwError, guard)
|
||||
import Text.Pandoc.Class (PandocMonad(..))
|
||||
import Text.Pandoc.Definition
|
||||
import Text.Pandoc.Options
|
||||
import Text.Pandoc.Parsing hiding (enclosed)
|
||||
import Text.Pandoc.Shared (crFilter)
|
||||
import Text.Parsec
|
||||
import Text.Parsec.Char
|
||||
import Data.Text (Text)
|
||||
import Data.Map (empty)
|
||||
import qualified Data.Text as T
|
||||
|
||||
|
||||
-- | Read man (troff) from an input string and return a Pandoc document.
|
||||
readMan :: PandocMonad m
|
||||
=> ReaderOptions
|
||||
-> Text
|
||||
-> m Pandoc
|
||||
readMan opts s = do
|
||||
parsed <- readWithM parseMan def{ stateOptions = opts } (T.unpack s)
|
||||
case parsed of
|
||||
Right result -> return result
|
||||
Left e -> throwError e
|
||||
|
||||
type ManParser m = ParserT [Char] ParserState m
|
||||
|
||||
comment :: PandocMonad m => ManParser m String
|
||||
comment = do
|
||||
string ".\\\" "
|
||||
many anyChar
|
||||
|
||||
data Macro = Macro { macroName :: String
|
||||
, macroArgs :: [String]
|
||||
}
|
||||
|
||||
parseMacro :: PandocMonad m => ManParser m Block
|
||||
parseMacro = do
|
||||
m <- macro
|
||||
return $ Plain (map Str $ (macroName m : macroArgs m))
|
||||
|
||||
macro :: PandocMonad m => ManParser m Macro
|
||||
macro = do
|
||||
char '.' <|> char '\''
|
||||
many space
|
||||
name <- many1 letter
|
||||
--args <- many parseArg
|
||||
return $ Macro { macroName = name, macroArgs = [] }
|
||||
|
||||
where
|
||||
|
||||
parseArg :: PandocMonad m => ManParser m String
|
||||
parseArg = do
|
||||
many1 space
|
||||
plainArg
|
||||
|
||||
quotedArg :: PandocMonad m => ManParser m String
|
||||
quotedArg = do
|
||||
char '"'
|
||||
val <- many1 quotedChar
|
||||
char '"'
|
||||
return val
|
||||
|
||||
plainArg :: PandocMonad m => ManParser m String
|
||||
plainArg = do
|
||||
many1 $ noneOf " \t"
|
||||
|
||||
quotedChar :: PandocMonad m => ManParser m Char
|
||||
quotedChar = do
|
||||
noneOf "\""
|
||||
<|> try (string "\"\"" >> return '"')
|
||||
|
||||
parseLine :: PandocMonad m => ManParser m Block
|
||||
parseLine = do
|
||||
str <- many anyChar
|
||||
return $ Plain [Str str]
|
||||
|
||||
parseBlock :: PandocMonad m => ManParser m Block
|
||||
parseBlock = do
|
||||
choice [ parseMacro
|
||||
, parseLine
|
||||
]
|
||||
|
||||
parseMan :: PandocMonad m => ManParser m Pandoc
|
||||
parseMan = do
|
||||
blocks <- parseBlock `sepBy` newline
|
||||
|
||||
return $ Pandoc Meta{unMeta = empty} blocks
|
16
test/Tests/Readers/Man.hs
Normal file
16
test/Tests/Readers/Man.hs
Normal file
|
@ -0,0 +1,16 @@
|
|||
{-# LANGUAGE OverloadedStrings #-}
|
||||
module Tests.Readers.Man (tests) where
|
||||
|
||||
import Data.Text (Text)
|
||||
import qualified Data.Text as T
|
||||
import Test.Tasty
|
||||
import Tests.Helpers
|
||||
import Text.Pandoc
|
||||
import Text.Pandoc.Arbitrary ()
|
||||
import Text.Pandoc.Builder
|
||||
|
||||
creole :: Text -> Pandoc
|
||||
creole = purely $ readCreole def{ readerStandalone = True }
|
||||
|
||||
tests :: [TestTree]
|
||||
tests = []
|
|
@ -19,6 +19,7 @@ import qualified Tests.Readers.Odt
|
|||
import qualified Tests.Readers.Org
|
||||
import qualified Tests.Readers.RST
|
||||
import qualified Tests.Readers.Txt2Tags
|
||||
import qualified Tests.Readers.Man
|
||||
import qualified Tests.Shared
|
||||
import qualified Tests.Writers.AsciiDoc
|
||||
import qualified Tests.Writers.ConTeXt
|
||||
|
@ -73,6 +74,7 @@ tests = testGroup "pandoc tests" [ Tests.Command.tests
|
|||
, testGroup "EPUB" Tests.Readers.EPUB.tests
|
||||
, testGroup "Muse" Tests.Readers.Muse.tests
|
||||
, testGroup "Creole" Tests.Readers.Creole.tests
|
||||
, testGroup "Man" Tests.Readers
|
||||
]
|
||||
, testGroup "Lua filters" Tests.Lua.tests
|
||||
]
|
||||
|
|
Loading…
Add table
Reference in a new issue