2011-01-20 08:41:53 -08:00
|
|
|
{-# LANGUAGE OverloadedStrings #-}
|
2010-07-04 13:55:48 -07:00
|
|
|
{-
|
2015-04-26 10:18:29 -07:00
|
|
|
Copyright (C) 2006-2015 John MacFarlane <jgm@berkeley.edu>
|
2010-07-04 13:55:48 -07:00
|
|
|
|
|
|
|
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.Writers.Native
|
2015-04-26 10:18:29 -07:00
|
|
|
Copyright : Copyright (C) 2006-2015 John MacFarlane
|
2012-07-26 22:32:53 -07:00
|
|
|
License : GNU GPL, version 2 or above
|
2010-07-04 13:55:48 -07:00
|
|
|
|
|
|
|
Maintainer : John MacFarlane <jgm@berkeley.edu>
|
|
|
|
Stability : alpha
|
|
|
|
Portability : portable
|
|
|
|
|
2011-01-21 09:00:05 -08:00
|
|
|
Conversion of a 'Pandoc' document to a string representation.
|
2010-07-04 13:55:48 -07:00
|
|
|
-}
|
|
|
|
module Text.Pandoc.Writers.Native ( writeNative )
|
|
|
|
where
|
2015-12-11 15:58:11 -08:00
|
|
|
import Text.Pandoc.Options ( WriterOptions(..), WrapOption(..) )
|
2011-01-20 08:41:53 -08:00
|
|
|
import Data.List ( intersperse )
|
2010-07-04 13:55:48 -07:00
|
|
|
import Text.Pandoc.Definition
|
2011-01-20 08:41:53 -08:00
|
|
|
import Text.Pandoc.Pretty
|
2016-11-26 08:46:28 -05:00
|
|
|
import Text.Pandoc.Class (PandocMonad)
|
2010-07-04 13:55:48 -07:00
|
|
|
|
2011-01-20 08:41:53 -08:00
|
|
|
prettyList :: [Doc] -> Doc
|
|
|
|
prettyList ds =
|
2011-01-20 20:48:06 -08:00
|
|
|
"[" <> (cat $ intersperse (cr <> ",") $ map (nest 1) ds) <> "]"
|
2010-07-04 13:55:48 -07:00
|
|
|
|
|
|
|
-- | Prettyprint Pandoc block element.
|
2011-01-20 08:41:53 -08:00
|
|
|
prettyBlock :: Block -> Doc
|
2016-10-13 08:46:44 +02:00
|
|
|
prettyBlock (LineBlock lines') =
|
|
|
|
"LineBlock" $$ prettyList (map (text . show) lines')
|
2011-01-20 08:41:53 -08:00
|
|
|
prettyBlock (BlockQuote blocks) =
|
|
|
|
"BlockQuote" $$ prettyList (map prettyBlock blocks)
|
2012-07-26 22:32:53 -07:00
|
|
|
prettyBlock (OrderedList attribs blockLists) =
|
2011-01-20 08:41:53 -08:00
|
|
|
"OrderedList" <> space <> text (show attribs) $$
|
|
|
|
(prettyList $ map (prettyList . map prettyBlock) blockLists)
|
2012-07-26 22:32:53 -07:00
|
|
|
prettyBlock (BulletList blockLists) =
|
2011-01-20 08:41:53 -08:00
|
|
|
"BulletList" $$
|
|
|
|
(prettyList $ map (prettyList . map prettyBlock) blockLists)
|
|
|
|
prettyBlock (DefinitionList items) = "DefinitionList" $$
|
|
|
|
(prettyList $ map deflistitem items)
|
|
|
|
where deflistitem (term, defs) = "(" <> text (show term) <> "," <> cr <>
|
|
|
|
nest 1 (prettyList $ map (prettyList . map prettyBlock) defs) <> ")"
|
2012-07-26 22:32:53 -07:00
|
|
|
prettyBlock (Table caption aligns widths header rows) =
|
2011-01-20 08:41:53 -08:00
|
|
|
"Table " <> text (show caption) <> " " <> text (show aligns) <> " " <>
|
2011-01-20 20:48:06 -08:00
|
|
|
text (show widths) $$
|
|
|
|
prettyRow header $$
|
2011-01-20 08:41:53 -08:00
|
|
|
prettyList (map prettyRow rows)
|
|
|
|
where prettyRow cols = prettyList (map (prettyList . map prettyBlock) cols)
|
2015-10-11 15:14:35 -07:00
|
|
|
prettyBlock (Div attr blocks) =
|
|
|
|
text ("Div " <> show attr) $$ prettyList (map prettyBlock blocks)
|
2011-01-20 08:41:53 -08:00
|
|
|
prettyBlock block = text $ show block
|
2010-07-04 13:55:48 -07:00
|
|
|
|
|
|
|
-- | Prettyprint Pandoc document.
|
2016-11-26 08:46:28 -05:00
|
|
|
writeNative :: PandocMonad m => WriterOptions -> Pandoc -> m String
|
|
|
|
writeNative opts (Pandoc meta blocks) = return $
|
2015-12-11 15:58:11 -08:00
|
|
|
let colwidth = if writerWrapText opts == WrapAuto
|
2011-01-20 08:41:53 -08:00
|
|
|
then Just $ writerColumns opts
|
|
|
|
else Nothing
|
2016-11-30 15:34:58 +01:00
|
|
|
withHead = case writerTemplate opts of
|
|
|
|
Just _ -> \bs -> text ("Pandoc (" ++ show meta ++ ")") $$
|
2013-05-10 22:53:35 -07:00
|
|
|
bs $$ cr
|
2016-11-30 15:34:58 +01:00
|
|
|
Nothing -> id
|
2011-01-20 08:41:53 -08:00
|
|
|
in render colwidth $ withHead $ prettyList $ map prettyBlock blocks
|