--------------------------------------------------------------------------------
{-# LANGUAGE CPP               #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE RecordWildCards   #-}
module Patat.Presentation.Display
    ( Size
    , getDisplaySize

    , Display (..)
    , displayPresentation
    , displayPresentationError
    , dumpPresentation
    ) where


--------------------------------------------------------------------------------
import           Control.Monad                        (mplus)
import qualified Data.Aeson.Extended                  as A
import           Data.Char.WCWidth.Extended           (wcstrwidth)
import           Data.Data.Extended                   (grecQ)
import qualified Data.List                            as L
import           Data.Maybe                           (fromMaybe, listToMaybe,
                                                       maybeToList)
import qualified Data.Text                            as T
import           Patat.Presentation.Display.CodeBlock
import           Patat.Presentation.Display.Table
import           Patat.Presentation.Internal
import           Patat.PrettyPrint                    ((<$$>), (<+>))
import qualified Patat.PrettyPrint                    as PP
import           Patat.Theme                          (Theme (..))
import qualified Patat.Theme                          as Theme
import           Prelude
import qualified System.Console.Terminal.Size         as Terminal
import qualified Text.Pandoc.Extended                 as Pandoc
import qualified Text.Pandoc.Writers.Shared           as Pandoc


--------------------------------------------------------------------------------
data Size = Size {Size -> Int
sRows :: Int, Size -> Int
sCols :: Int} deriving (Int -> Size -> ShowS
[Size] -> ShowS
Size -> String
(Int -> Size -> ShowS)
-> (Size -> String) -> ([Size] -> ShowS) -> Show Size
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Size] -> ShowS
$cshowList :: [Size] -> ShowS
show :: Size -> String
$cshow :: Size -> String
showsPrec :: Int -> Size -> ShowS
$cshowsPrec :: Int -> Size -> ShowS
Show)


--------------------------------------------------------------------------------
getDisplaySize :: Presentation -> IO Size
getDisplaySize :: Presentation -> IO Size
getDisplaySize Presentation {String
[Breadcrumbs]
[Inline]
[Slide]
Index
PresentationSettings
pActiveFragment :: Presentation -> Index
pBreadcrumbs :: Presentation -> [Breadcrumbs]
pSlides :: Presentation -> [Slide]
pSettings :: Presentation -> PresentationSettings
pAuthor :: Presentation -> [Inline]
pTitle :: Presentation -> [Inline]
pFilePath :: Presentation -> String
pActiveFragment :: Index
pBreadcrumbs :: [Breadcrumbs]
pSlides :: [Slide]
pSettings :: PresentationSettings
pAuthor :: [Inline]
pTitle :: [Inline]
pFilePath :: String
..} = do
    Maybe (Window Int)
mbWindow <- IO (Maybe (Window Int))
forall n. Integral n => IO (Maybe (Window n))
Terminal.size
    let sRows :: Int
sRows = Int -> Maybe Int -> Int
forall a. a -> Maybe a -> a
fromMaybe Int
24 (Maybe Int -> Int) -> Maybe Int -> Int
forall a b. (a -> b) -> a -> b
$
            (FlexibleNum Int -> Int
forall a. FlexibleNum a -> a
A.unFlexibleNum (FlexibleNum Int -> Int) -> Maybe (FlexibleNum Int) -> Maybe Int
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> PresentationSettings -> Maybe (FlexibleNum Int)
psRows PresentationSettings
pSettings) Maybe Int -> Maybe Int -> Maybe Int
forall (m :: * -> *) a. MonadPlus m => m a -> m a -> m a
`mplus`
            (Window Int -> Int
forall a. Window a -> a
Terminal.height (Window Int -> Int) -> Maybe (Window Int) -> Maybe Int
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Maybe (Window Int)
mbWindow)
        sCols :: Int
sCols = Int -> Maybe Int -> Int
forall a. a -> Maybe a -> a
fromMaybe Int
72 (Maybe Int -> Int) -> Maybe Int -> Int
forall a b. (a -> b) -> a -> b
$
            (FlexibleNum Int -> Int
forall a. FlexibleNum a -> a
A.unFlexibleNum (FlexibleNum Int -> Int) -> Maybe (FlexibleNum Int) -> Maybe Int
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> PresentationSettings -> Maybe (FlexibleNum Int)
psColumns PresentationSettings
pSettings) Maybe Int -> Maybe Int -> Maybe Int
forall (m :: * -> *) a. MonadPlus m => m a -> m a -> m a
`mplus`
            (Window Int -> Int
forall a. Window a -> a
Terminal.width  (Window Int -> Int) -> Maybe (Window Int) -> Maybe Int
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Maybe (Window Int)
mbWindow)
    Size -> IO Size
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Size -> IO Size) -> Size -> IO Size
forall a b. (a -> b) -> a -> b
$ Size :: Int -> Int -> Size
Size {Int
sCols :: Int
sRows :: Int
sCols :: Int
sRows :: Int
..}


--------------------------------------------------------------------------------
data Display = DisplayDoc PP.Doc | DisplayImage FilePath deriving (Int -> Display -> ShowS
[Display] -> ShowS
Display -> String
(Int -> Display -> ShowS)
-> (Display -> String) -> ([Display] -> ShowS) -> Show Display
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Display] -> ShowS
$cshowList :: [Display] -> ShowS
show :: Display -> String
$cshow :: Display -> String
showsPrec :: Int -> Display -> ShowS
$cshowsPrec :: Int -> Display -> ShowS
Show)


--------------------------------------------------------------------------------
-- | Display something within the presentation borders that draw the title and
-- the active slide number and so on.
displayWithBorders
    :: Size -> Presentation -> (Size -> Theme -> PP.Doc) -> PP.Doc
displayWithBorders :: Size -> Presentation -> (Size -> Theme -> Doc) -> Doc
displayWithBorders (Size Int
rows Int
columns) Presentation {String
[Breadcrumbs]
[Inline]
[Slide]
Index
PresentationSettings
pActiveFragment :: Index
pBreadcrumbs :: [Breadcrumbs]
pSlides :: [Slide]
pSettings :: PresentationSettings
pAuthor :: [Inline]
pTitle :: [Inline]
pFilePath :: String
pActiveFragment :: Presentation -> Index
pBreadcrumbs :: Presentation -> [Breadcrumbs]
pSlides :: Presentation -> [Slide]
pSettings :: Presentation -> PresentationSettings
pAuthor :: Presentation -> [Inline]
pTitle :: Presentation -> [Inline]
pFilePath :: Presentation -> String
..} Size -> Theme -> Doc
f =
    (if String -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null String
title
        then Doc
forall a. Monoid a => a
mempty
        else
            let titleRemainder :: Int
titleRemainder = Int
columns Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
titleWidth Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
titleOffset
                wrappedTitle :: Doc
wrappedTitle = Int -> Doc
PP.spaces Int
titleOffset Doc -> Doc -> Doc
forall a. Semigroup a => a -> a -> a
<> String -> Doc
PP.string String
title Doc -> Doc -> Doc
forall a. Semigroup a => a -> a -> a
<> Int -> Doc
PP.spaces Int
titleRemainder in
        Doc -> Doc
borders Doc
wrappedTitle Doc -> Doc -> Doc
forall a. Semigroup a => a -> a -> a
<> Doc
PP.hardline Doc -> Doc -> Doc
forall a. Semigroup a => a -> a -> a
<> Doc
PP.hardline) Doc -> Doc -> Doc
forall a. Semigroup a => a -> a -> a
<>
    PresentationSettings -> Doc -> Doc
formatWith PresentationSettings
settings (Size -> Theme -> Doc
f Size
canvasSize Theme
theme) Doc -> Doc -> Doc
forall a. Semigroup a => a -> a -> a
<> Doc
PP.hardline Doc -> Doc -> Doc
forall a. Semigroup a => a -> a -> a
<>
    Int -> Doc
PP.goToLine (Int
rows Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
2) Doc -> Doc -> Doc
forall a. Semigroup a => a -> a -> a
<>
    Doc -> Doc
borders (Doc
PP.space Doc -> Doc -> Doc
forall a. Semigroup a => a -> a -> a
<> String -> Doc
PP.string String
author Doc -> Doc -> Doc
forall a. Semigroup a => a -> a -> a
<> Doc
middleSpaces Doc -> Doc -> Doc
forall a. Semigroup a => a -> a -> a
<> String -> Doc
PP.string String
active Doc -> Doc -> Doc
forall a. Semigroup a => a -> a -> a
<> Doc
PP.space) Doc -> Doc -> Doc
forall a. Semigroup a => a -> a -> a
<>
    Doc
PP.hardline
  where
    -- Get terminal width/title
    (Int
sidx, Int
_)   = Index
pActiveFragment
    settings :: PresentationSettings
settings    = PresentationSettings
pSettings {psColumns :: Maybe (FlexibleNum Int)
psColumns = FlexibleNum Int -> Maybe (FlexibleNum Int)
forall a. a -> Maybe a
Just (FlexibleNum Int -> Maybe (FlexibleNum Int))
-> FlexibleNum Int -> Maybe (FlexibleNum Int)
forall a b. (a -> b) -> a -> b
$ Int -> FlexibleNum Int
forall a. a -> FlexibleNum a
A.FlexibleNum Int
columns}
    theme :: Theme
theme       = Theme -> Maybe Theme -> Theme
forall a. a -> Maybe a -> a
fromMaybe Theme
Theme.defaultTheme (PresentationSettings -> Maybe Theme
psTheme PresentationSettings
settings)

    -- Compute title.
    breadcrumbs :: Breadcrumbs
breadcrumbs = Breadcrumbs -> Maybe Breadcrumbs -> Breadcrumbs
forall a. a -> Maybe a -> a
fromMaybe [] (Maybe Breadcrumbs -> Breadcrumbs)
-> ([Breadcrumbs] -> Maybe Breadcrumbs)
-> [Breadcrumbs]
-> Breadcrumbs
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Breadcrumbs] -> Maybe Breadcrumbs
forall a. [a] -> Maybe a
listToMaybe ([Breadcrumbs] -> Breadcrumbs) -> [Breadcrumbs] -> Breadcrumbs
forall a b. (a -> b) -> a -> b
$ Int -> [Breadcrumbs] -> [Breadcrumbs]
forall a. Int -> [a] -> [a]
drop Int
sidx [Breadcrumbs]
pBreadcrumbs
    plainTitle :: String
plainTitle  = Doc -> String
PP.toString (Doc -> String) -> Doc -> String
forall a b. (a -> b) -> a -> b
$ Theme -> [Inline] -> Doc
prettyInlines Theme
theme [Inline]
pTitle
    breadTitle :: String
breadTitle  = String -> ShowS
forall a. Monoid a => a -> a -> a
mappend String
plainTitle ShowS -> ShowS
forall a b. (a -> b) -> a -> b
$ [String] -> String
forall a. Monoid a => [a] -> a
mconcat
        [ String
s
        | Doc
b <- ((Int, [Inline]) -> Doc) -> Breadcrumbs -> [Doc]
forall a b. (a -> b) -> [a] -> [b]
map (Theme -> [Inline] -> Doc
prettyInlines Theme
theme ([Inline] -> Doc)
-> ((Int, [Inline]) -> [Inline]) -> (Int, [Inline]) -> Doc
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Int, [Inline]) -> [Inline]
forall a b. (a, b) -> b
snd) Breadcrumbs
breadcrumbs
        , String
s <- [String
" > ", Doc -> String
PP.toString Doc
b]
        ]
    title :: String
title
        | Bool -> Bool
not (Bool -> Bool) -> (Maybe Bool -> Bool) -> Maybe Bool -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Bool -> Maybe Bool -> Bool
forall a. a -> Maybe a -> a
fromMaybe Bool
True (Maybe Bool -> Bool) -> Maybe Bool -> Bool
forall a b. (a -> b) -> a -> b
$ PresentationSettings -> Maybe Bool
psBreadcrumbs PresentationSettings
settings = String
plainTitle
        | String -> Int
wcstrwidth String
breadTitle Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
> Int
columns               = String
plainTitle
        | Bool
otherwise                                     = String
breadTitle

    -- Dimensions of title.
    titleWidth :: Int
titleWidth  = String -> Int
wcstrwidth String
title
    titleOffset :: Int
titleOffset = (Int
columns Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
titleWidth) Int -> Int -> Int
forall a. Integral a => a -> a -> a
`div` Int
2
    borders :: Doc -> Doc
borders     = Maybe Style -> Doc -> Doc
themed (Theme -> Maybe Style
themeBorders Theme
theme)

    -- Room left for content
    canvasSize :: Size
canvasSize = Int -> Int -> Size
Size (Int
rows Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
2) Int
columns

    -- Compute footer.
    active :: String
active       = Int -> String
forall a. Show a => a -> String
show (Int
sidx Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
1) String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
" / " String -> ShowS
forall a. [a] -> [a] -> [a]
++ Int -> String
forall a. Show a => a -> String
show ([Slide] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length [Slide]
pSlides)
    activeWidth :: Int
activeWidth  = String -> Int
wcstrwidth String
active
    author :: String
author       = Doc -> String
PP.toString (Theme -> [Inline] -> Doc
prettyInlines Theme
theme [Inline]
pAuthor)
    authorWidth :: Int
authorWidth  = String -> Int
wcstrwidth String
author
    middleSpaces :: Doc
middleSpaces = Int -> Doc
PP.spaces (Int -> Doc) -> Int -> Doc
forall a b. (a -> b) -> a -> b
$ Int
columns Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
activeWidth Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
authorWidth Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
2


--------------------------------------------------------------------------------
displayPresentation :: Size -> Presentation -> Display
displayPresentation :: Size -> Presentation -> Display
displayPresentation Size
size pres :: Presentation
pres@Presentation {String
[Breadcrumbs]
[Inline]
[Slide]
Index
PresentationSettings
pActiveFragment :: Index
pBreadcrumbs :: [Breadcrumbs]
pSlides :: [Slide]
pSettings :: PresentationSettings
pAuthor :: [Inline]
pTitle :: [Inline]
pFilePath :: String
pActiveFragment :: Presentation -> Index
pBreadcrumbs :: Presentation -> [Breadcrumbs]
pSlides :: Presentation -> [Slide]
pSettings :: Presentation -> PresentationSettings
pAuthor :: Presentation -> [Inline]
pTitle :: Presentation -> [Inline]
pFilePath :: Presentation -> String
..} =
     case Presentation -> Maybe ActiveFragment
getActiveFragment Presentation
pres of
        Maybe ActiveFragment
Nothing -> Doc -> Display
DisplayDoc (Doc -> Display) -> Doc -> Display
forall a b. (a -> b) -> a -> b
$ Size -> Presentation -> (Size -> Theme -> Doc) -> Doc
displayWithBorders Size
size Presentation
pres Size -> Theme -> Doc
forall a. Monoid a => a
mempty
        Just (ActiveContent Fragment
fragment)
                | Just ImageSettings
_ <- PresentationSettings -> Maybe ImageSettings
psImages PresentationSettings
pSettings
                , Just Text
image <- Fragment -> Maybe Text
onlyImage Fragment
fragment ->
            String -> Display
DisplayImage (String -> Display) -> String -> Display
forall a b. (a -> b) -> a -> b
$ Text -> String
T.unpack Text
image
        Just (ActiveContent Fragment
fragment) -> Doc -> Display
DisplayDoc (Doc -> Display) -> Doc -> Display
forall a b. (a -> b) -> a -> b
$
            Size -> Presentation -> (Size -> Theme -> Doc) -> Doc
displayWithBorders Size
size Presentation
pres ((Size -> Theme -> Doc) -> Doc) -> (Size -> Theme -> Doc) -> Doc
forall a b. (a -> b) -> a -> b
$ \Size
_canvasSize Theme
theme ->
                Theme -> Fragment -> Doc
prettyFragment Theme
theme Fragment
fragment
        Just (ActiveTitle Block
block) -> Doc -> Display
DisplayDoc (Doc -> Display) -> Doc -> Display
forall a b. (a -> b) -> a -> b
$
            Size -> Presentation -> (Size -> Theme -> Doc) -> Doc
displayWithBorders Size
size Presentation
pres ((Size -> Theme -> Doc) -> Doc) -> (Size -> Theme -> Doc) -> Doc
forall a b. (a -> b) -> a -> b
$ \Size
canvasSize Theme
theme ->
            let pblock :: Doc
pblock          = Theme -> Block -> Doc
prettyBlock Theme
theme Block
block
                (Int
prows, Int
pcols)  = Doc -> Index
PP.dimensions Doc
pblock
                (Int
mLeft, Int
mRight) = PresentationSettings -> Index
marginsOf PresentationSettings
pSettings
                offsetRow :: Int
offsetRow       = (Size -> Int
sRows Size
canvasSize Int -> Int -> Int
forall a. Integral a => a -> a -> a
`div` Int
2) Int -> Int -> Int
forall a. Num a => a -> a -> a
- (Int
prows Int -> Int -> Int
forall a. Integral a => a -> a -> a
`div` Int
2)
                offsetCol :: Int
offsetCol       = ((Size -> Int
sCols Size
canvasSize Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
mLeft Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
mRight) Int -> Int -> Int
forall a. Integral a => a -> a -> a
`div` Int
2) Int -> Int -> Int
forall a. Num a => a -> a -> a
- (Int
pcols Int -> Int -> Int
forall a. Integral a => a -> a -> a
`div` Int
2)
                spaces :: Trimmable Doc
spaces          = Doc -> Trimmable Doc
forall a. a -> Trimmable a
PP.NotTrimmable (Doc -> Trimmable Doc) -> Doc -> Trimmable Doc
forall a b. (a -> b) -> a -> b
$ Int -> Doc
PP.spaces Int
offsetCol in
            [Doc] -> Doc
forall a. Monoid a => [a] -> a
mconcat (Int -> Doc -> [Doc]
forall a. Int -> a -> [a]
replicate (Int
offsetRow Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
3) Doc
PP.hardline) Doc -> Doc -> Doc
<$$>
            Trimmable Doc -> Trimmable Doc -> Doc -> Doc
PP.indent Trimmable Doc
spaces Trimmable Doc
spaces Doc
pblock

  where
    -- Check if the fragment consists of just a single image, or a header and
    -- some image.
    onlyImage :: Fragment -> Maybe Text
onlyImage (Fragment [Block]
blocks)
            | [Pandoc.Para [Inline]
para] <- (Block -> Bool) -> [Block] -> [Block]
forall a. (a -> Bool) -> [a] -> [a]
filter Block -> Bool
isVisibleBlock [Block]
blocks
            , [Pandoc.Image Attr
_ [Inline]
_ (Text
target, Text
_)] <- [Inline]
para =
        Text -> Maybe Text
forall a. a -> Maybe a
Just Text
target
    onlyImage (Fragment [Block]
blocks)
            | [Pandoc.Header Int
_ Attr
_ [Inline]
_, Pandoc.Para [Inline]
para] <- (Block -> Bool) -> [Block] -> [Block]
forall a. (a -> Bool) -> [a] -> [a]
filter Block -> Bool
isVisibleBlock [Block]
blocks
            , [Pandoc.Image Attr
_ [Inline]
_ (Text
target, Text
_)] <- [Inline]
para =
        Text -> Maybe Text
forall a. a -> Maybe a
Just Text
target
    onlyImage Fragment
_ = Maybe Text
forall a. Maybe a
Nothing


--------------------------------------------------------------------------------
-- | Displays an error in the place of the presentation.  This is useful if we
-- want to display an error but keep the presentation running.
displayPresentationError :: Size -> Presentation -> String -> PP.Doc
displayPresentationError :: Size -> Presentation -> String -> Doc
displayPresentationError Size
size Presentation
pres String
err =
    Size -> Presentation -> (Size -> Theme -> Doc) -> Doc
displayWithBorders Size
size Presentation
pres ((Size -> Theme -> Doc) -> Doc) -> (Size -> Theme -> Doc) -> Doc
forall a b. (a -> b) -> a -> b
$ \Size
_ Theme {Maybe Text
Maybe SyntaxHighlighting
Maybe Style
themeSyntaxHighlighting :: Theme -> Maybe SyntaxHighlighting
themeImageTarget :: Theme -> Maybe Style
themeImageText :: Theme -> Maybe Style
themeMath :: Theme -> Maybe Style
themeQuoted :: Theme -> Maybe Style
themeStrikeout :: Theme -> Maybe Style
themeLinkTarget :: Theme -> Maybe Style
themeLinkText :: Theme -> Maybe Style
themeCode :: Theme -> Maybe Style
themeUnderline :: Theme -> Maybe Style
themeStrong :: Theme -> Maybe Style
themeEmph :: Theme -> Maybe Style
themeLineBlock :: Theme -> Maybe Style
themeTableSeparator :: Theme -> Maybe Style
themeTableHeader :: Theme -> Maybe Style
themeDefinitionList :: Theme -> Maybe Style
themeDefinitionTerm :: Theme -> Maybe Style
themeBlockQuote :: Theme -> Maybe Style
themeOrderedList :: Theme -> Maybe Style
themeBulletListMarkers :: Theme -> Maybe Text
themeBulletList :: Theme -> Maybe Style
themeCodeBlock :: Theme -> Maybe Style
themeHeader :: Theme -> Maybe Style
themeSyntaxHighlighting :: Maybe SyntaxHighlighting
themeImageTarget :: Maybe Style
themeImageText :: Maybe Style
themeMath :: Maybe Style
themeQuoted :: Maybe Style
themeStrikeout :: Maybe Style
themeLinkTarget :: Maybe Style
themeLinkText :: Maybe Style
themeCode :: Maybe Style
themeUnderline :: Maybe Style
themeStrong :: Maybe Style
themeEmph :: Maybe Style
themeLineBlock :: Maybe Style
themeTableSeparator :: Maybe Style
themeTableHeader :: Maybe Style
themeDefinitionList :: Maybe Style
themeDefinitionTerm :: Maybe Style
themeBlockQuote :: Maybe Style
themeOrderedList :: Maybe Style
themeBulletListMarkers :: Maybe Text
themeBulletList :: Maybe Style
themeCodeBlock :: Maybe Style
themeHeader :: Maybe Style
themeBorders :: Maybe Style
themeBorders :: Theme -> Maybe Style
..} ->
        Maybe Style -> Doc -> Doc
themed Maybe Style
themeStrong Doc
"Error occurred in the presentation:" Doc -> Doc -> Doc
<$$>
        Doc
"" Doc -> Doc -> Doc
<$$>
        (String -> Doc
PP.string String
err)


--------------------------------------------------------------------------------
dumpPresentation :: Presentation -> IO ()
dumpPresentation :: Presentation -> IO ()
dumpPresentation pres :: Presentation
pres@Presentation {String
[Breadcrumbs]
[Inline]
[Slide]
Index
PresentationSettings
pActiveFragment :: Index
pBreadcrumbs :: [Breadcrumbs]
pSlides :: [Slide]
pSettings :: PresentationSettings
pAuthor :: [Inline]
pTitle :: [Inline]
pFilePath :: String
pActiveFragment :: Presentation -> Index
pBreadcrumbs :: Presentation -> [Breadcrumbs]
pSlides :: Presentation -> [Slide]
pSettings :: Presentation -> PresentationSettings
pAuthor :: Presentation -> [Inline]
pTitle :: Presentation -> [Inline]
pFilePath :: Presentation -> String
..} =
    let sRows :: Int
sRows = Int -> Maybe Int -> Int
forall a. a -> Maybe a -> a
fromMaybe Int
24 (Maybe Int -> Int) -> Maybe Int -> Int
forall a b. (a -> b) -> a -> b
$ FlexibleNum Int -> Int
forall a. FlexibleNum a -> a
A.unFlexibleNum (FlexibleNum Int -> Int) -> Maybe (FlexibleNum Int) -> Maybe Int
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> PresentationSettings -> Maybe (FlexibleNum Int)
psRows PresentationSettings
pSettings
        sCols :: Int
sCols = Int -> Maybe Int -> Int
forall a. a -> Maybe a -> a
fromMaybe Int
72 (Maybe Int -> Int) -> Maybe Int -> Int
forall a b. (a -> b) -> a -> b
$ FlexibleNum Int -> Int
forall a. FlexibleNum a -> a
A.unFlexibleNum (FlexibleNum Int -> Int) -> Maybe (FlexibleNum Int) -> Maybe Int
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> PresentationSettings -> Maybe (FlexibleNum Int)
psColumns PresentationSettings
pSettings
        size :: Size
size  = Size :: Int -> Int -> Size
Size {Int
sCols :: Int
sRows :: Int
sCols :: Int
sRows :: Int
..} in
    Doc -> IO ()
PP.putDoc (Doc -> IO ()) -> Doc -> IO ()
forall a b. (a -> b) -> a -> b
$ Doc -> Doc
PP.removeControls (Doc -> Doc) -> Doc -> Doc
forall a b. (a -> b) -> a -> b
$ PresentationSettings -> Doc -> Doc
formatWith PresentationSettings
pSettings (Doc -> Doc) -> Doc -> Doc
forall a b. (a -> b) -> a -> b
$
    [Doc] -> Doc
PP.vcat ([Doc] -> Doc) -> [Doc] -> Doc
forall a b. (a -> b) -> a -> b
$ Doc -> [Doc] -> [Doc]
forall a. a -> [a] -> [a]
L.intersperse Doc
"----------" ([Doc] -> [Doc]) -> [Doc] -> [Doc]
forall a b. (a -> b) -> a -> b
$ do
        Int
i <- [Int
0 .. [Slide] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length [Slide]
pSlides Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
1]
        Slide
slide <- Maybe Slide -> [Slide]
forall a. Maybe a -> [a]
maybeToList (Maybe Slide -> [Slide]) -> Maybe Slide -> [Slide]
forall a b. (a -> b) -> a -> b
$ Int -> Presentation -> Maybe Slide
getSlide Int
i Presentation
pres
        Int
j <- [Int
0 .. Slide -> Int
numFragments Slide
slide Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
1]
        case Size -> Presentation -> Display
displayPresentation Size
size Presentation
pres {pActiveFragment :: Index
pActiveFragment = (Int
i, Int
j)} of
            DisplayDoc Doc
doc -> [Doc
doc]
            DisplayImage String
_ -> []


--------------------------------------------------------------------------------
formatWith :: PresentationSettings -> PP.Doc -> PP.Doc
formatWith :: PresentationSettings -> Doc -> Doc
formatWith PresentationSettings
ps = Doc -> Doc
wrap (Doc -> Doc) -> (Doc -> Doc) -> Doc -> Doc
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Doc -> Doc
indent
  where
    (Int
marginLeft, Int
marginRight) = PresentationSettings -> Index
marginsOf PresentationSettings
ps
    wrap :: Doc -> Doc
wrap = case (PresentationSettings -> Maybe Bool
psWrap PresentationSettings
ps, PresentationSettings -> Maybe (FlexibleNum Int)
psColumns PresentationSettings
ps) of
        (Just Bool
True,  Just (A.FlexibleNum Int
col)) -> Maybe Int -> Doc -> Doc
PP.wrapAt (Int -> Maybe Int
forall a. a -> Maybe a
Just (Int -> Maybe Int) -> Int -> Maybe Int
forall a b. (a -> b) -> a -> b
$ Int
col Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
marginRight)
        (Maybe Bool, Maybe (FlexibleNum Int))
_                                      -> Doc -> Doc
forall a. a -> a
id
    spaces :: Trimmable Doc
spaces = Doc -> Trimmable Doc
forall a. a -> Trimmable a
PP.NotTrimmable (Doc -> Trimmable Doc) -> Doc -> Trimmable Doc
forall a b. (a -> b) -> a -> b
$ Int -> Doc
PP.spaces Int
marginLeft
    indent :: Doc -> Doc
indent = Trimmable Doc -> Trimmable Doc -> Doc -> Doc
PP.indent Trimmable Doc
spaces Trimmable Doc
spaces


--------------------------------------------------------------------------------
prettyFragment :: Theme -> Fragment -> PP.Doc
prettyFragment :: Theme -> Fragment -> Doc
prettyFragment Theme
theme (Fragment [Block]
blocks) =
    Theme -> [Block] -> Doc
prettyBlocks Theme
theme [Block]
blocks Doc -> Doc -> Doc
forall a. Semigroup a => a -> a -> a
<>
    case Theme -> [Block] -> [Doc]
prettyReferences Theme
theme [Block]
blocks of
        []   -> Doc
forall a. Monoid a => a
mempty
        [Doc]
refs -> Doc
PP.hardline Doc -> Doc -> Doc
forall a. Semigroup a => a -> a -> a
<> [Doc] -> Doc
PP.vcat [Doc]
refs


--------------------------------------------------------------------------------
prettyBlock :: Theme -> Pandoc.Block -> PP.Doc

prettyBlock :: Theme -> Block -> Doc
prettyBlock Theme
theme (Pandoc.Plain [Inline]
inlines) = Theme -> [Inline] -> Doc
prettyInlines Theme
theme [Inline]
inlines

prettyBlock Theme
theme (Pandoc.Para [Inline]
inlines) =
    Theme -> [Inline] -> Doc
prettyInlines Theme
theme [Inline]
inlines Doc -> Doc -> Doc
forall a. Semigroup a => a -> a -> a
<> Doc
PP.hardline

prettyBlock theme :: Theme
theme@Theme {Maybe Text
Maybe SyntaxHighlighting
Maybe Style
themeSyntaxHighlighting :: Maybe SyntaxHighlighting
themeImageTarget :: Maybe Style
themeImageText :: Maybe Style
themeMath :: Maybe Style
themeQuoted :: Maybe Style
themeStrikeout :: Maybe Style
themeLinkTarget :: Maybe Style
themeLinkText :: Maybe Style
themeCode :: Maybe Style
themeUnderline :: Maybe Style
themeStrong :: Maybe Style
themeEmph :: Maybe Style
themeLineBlock :: Maybe Style
themeTableSeparator :: Maybe Style
themeTableHeader :: Maybe Style
themeDefinitionList :: Maybe Style
themeDefinitionTerm :: Maybe Style
themeBlockQuote :: Maybe Style
themeOrderedList :: Maybe Style
themeBulletListMarkers :: Maybe Text
themeBulletList :: Maybe Style
themeCodeBlock :: Maybe Style
themeHeader :: Maybe Style
themeBorders :: Maybe Style
themeSyntaxHighlighting :: Theme -> Maybe SyntaxHighlighting
themeImageTarget :: Theme -> Maybe Style
themeImageText :: Theme -> Maybe Style
themeMath :: Theme -> Maybe Style
themeQuoted :: Theme -> Maybe Style
themeStrikeout :: Theme -> Maybe Style
themeLinkTarget :: Theme -> Maybe Style
themeLinkText :: Theme -> Maybe Style
themeCode :: Theme -> Maybe Style
themeUnderline :: Theme -> Maybe Style
themeStrong :: Theme -> Maybe Style
themeEmph :: Theme -> Maybe Style
themeLineBlock :: Theme -> Maybe Style
themeTableSeparator :: Theme -> Maybe Style
themeTableHeader :: Theme -> Maybe Style
themeDefinitionList :: Theme -> Maybe Style
themeDefinitionTerm :: Theme -> Maybe Style
themeBlockQuote :: Theme -> Maybe Style
themeOrderedList :: Theme -> Maybe Style
themeBulletListMarkers :: Theme -> Maybe Text
themeBulletList :: Theme -> Maybe Style
themeCodeBlock :: Theme -> Maybe Style
themeHeader :: Theme -> Maybe Style
themeBorders :: Theme -> Maybe Style
..} (Pandoc.Header Int
i Attr
_ [Inline]
inlines) =
    Maybe Style -> Doc -> Doc
themed Maybe Style
themeHeader (String -> Doc
PP.string (Int -> Char -> String
forall a. Int -> a -> [a]
replicate Int
i Char
'#') Doc -> Doc -> Doc
<+> Theme -> [Inline] -> Doc
prettyInlines Theme
theme [Inline]
inlines) Doc -> Doc -> Doc
forall a. Semigroup a => a -> a -> a
<>
    Doc
PP.hardline

prettyBlock Theme
theme (Pandoc.CodeBlock (Text
_, [Text]
classes, [(Text, Text)]
_) Text
txt) =
    Theme -> [Text] -> Text -> Doc
prettyCodeBlock Theme
theme [Text]
classes Text
txt

prettyBlock Theme
theme (Pandoc.BulletList [[Block]]
bss) = [Doc] -> Doc
PP.vcat
    [ Trimmable Doc -> Trimmable Doc -> Doc -> Doc
PP.indent
        (Doc -> Trimmable Doc
forall a. a -> Trimmable a
PP.NotTrimmable (Doc -> Trimmable Doc) -> Doc -> Trimmable Doc
forall a b. (a -> b) -> a -> b
$ Maybe Style -> Doc -> Doc
themed (Theme -> Maybe Style
themeBulletList Theme
theme) Doc
prefix)
        (Doc -> Trimmable Doc
forall a. a -> Trimmable a
PP.Trimmable Doc
"    ")
        (Theme -> [Block] -> Doc
prettyBlocks Theme
theme' [Block]
bs)
    | [Block]
bs <- [[Block]]
bss
    ] Doc -> Doc -> Doc
forall a. Semigroup a => a -> a -> a
<> Doc
PP.hardline
  where
    prefix :: Doc
prefix = Doc
"  " Doc -> Doc -> Doc
forall a. Semigroup a => a -> a -> a
<> String -> Doc
PP.string [Char
marker] Doc -> Doc -> Doc
forall a. Semigroup a => a -> a -> a
<> Doc
" "
    marker :: Char
marker = case Text -> String
T.unpack (Text -> String) -> Maybe Text -> Maybe String
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Theme -> Maybe Text
themeBulletListMarkers Theme
theme of
        Just (Char
x : String
_) -> Char
x
        Maybe String
_            -> Char
'-'

    -- Cycle the markers.
    theme' :: Theme
theme' = Theme
theme
        { themeBulletListMarkers :: Maybe Text
themeBulletListMarkers =
            (\Text
ls -> Int -> Text -> Text
T.drop Int
1 Text
ls Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Int -> Text -> Text
T.take Int
1 Text
ls) (Text -> Text) -> Maybe Text -> Maybe Text
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Theme -> Maybe Text
themeBulletListMarkers Theme
theme
        }

prettyBlock theme :: Theme
theme@Theme {Maybe Text
Maybe SyntaxHighlighting
Maybe Style
themeSyntaxHighlighting :: Maybe SyntaxHighlighting
themeImageTarget :: Maybe Style
themeImageText :: Maybe Style
themeMath :: Maybe Style
themeQuoted :: Maybe Style
themeStrikeout :: Maybe Style
themeLinkTarget :: Maybe Style
themeLinkText :: Maybe Style
themeCode :: Maybe Style
themeUnderline :: Maybe Style
themeStrong :: Maybe Style
themeEmph :: Maybe Style
themeLineBlock :: Maybe Style
themeTableSeparator :: Maybe Style
themeTableHeader :: Maybe Style
themeDefinitionList :: Maybe Style
themeDefinitionTerm :: Maybe Style
themeBlockQuote :: Maybe Style
themeOrderedList :: Maybe Style
themeBulletListMarkers :: Maybe Text
themeBulletList :: Maybe Style
themeCodeBlock :: Maybe Style
themeHeader :: Maybe Style
themeBorders :: Maybe Style
themeSyntaxHighlighting :: Theme -> Maybe SyntaxHighlighting
themeImageTarget :: Theme -> Maybe Style
themeImageText :: Theme -> Maybe Style
themeMath :: Theme -> Maybe Style
themeQuoted :: Theme -> Maybe Style
themeStrikeout :: Theme -> Maybe Style
themeLinkTarget :: Theme -> Maybe Style
themeLinkText :: Theme -> Maybe Style
themeCode :: Theme -> Maybe Style
themeUnderline :: Theme -> Maybe Style
themeStrong :: Theme -> Maybe Style
themeEmph :: Theme -> Maybe Style
themeLineBlock :: Theme -> Maybe Style
themeTableSeparator :: Theme -> Maybe Style
themeTableHeader :: Theme -> Maybe Style
themeDefinitionList :: Theme -> Maybe Style
themeDefinitionTerm :: Theme -> Maybe Style
themeBlockQuote :: Theme -> Maybe Style
themeOrderedList :: Theme -> Maybe Style
themeBulletListMarkers :: Theme -> Maybe Text
themeBulletList :: Theme -> Maybe Style
themeCodeBlock :: Theme -> Maybe Style
themeHeader :: Theme -> Maybe Style
themeBorders :: Theme -> Maybe Style
..} (Pandoc.OrderedList ListAttributes
_ [[Block]]
bss) = [Doc] -> Doc
PP.vcat
    [ Trimmable Doc -> Trimmable Doc -> Doc -> Doc
PP.indent
        (Doc -> Trimmable Doc
forall a. a -> Trimmable a
PP.NotTrimmable (Doc -> Trimmable Doc) -> Doc -> Trimmable Doc
forall a b. (a -> b) -> a -> b
$ Maybe Style -> Doc -> Doc
themed Maybe Style
themeOrderedList (Doc -> Doc) -> Doc -> Doc
forall a b. (a -> b) -> a -> b
$ String -> Doc
PP.string String
prefix)
        (Doc -> Trimmable Doc
forall a. a -> Trimmable a
PP.Trimmable Doc
"    ")
        (Theme -> [Block] -> Doc
prettyBlocks Theme
theme [Block]
bs)
    | (String
prefix, [Block]
bs) <- [String] -> [[Block]] -> [(String, [Block])]
forall a b. [a] -> [b] -> [(a, b)]
zip [String]
padded [[Block]]
bss
    ] Doc -> Doc -> Doc
forall a. Semigroup a => a -> a -> a
<> Doc
PP.hardline
  where
    padded :: [String]
padded  = [String
n String -> ShowS
forall a. [a] -> [a] -> [a]
++ Int -> Char -> String
forall a. Int -> a -> [a]
replicate (Int
4 Int -> Int -> Int
forall a. Num a => a -> a -> a
- String -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length String
n) Char
' ' | String
n <- [String]
numbers]
    numbers :: [String]
numbers =
        [ Int -> String
forall a. Show a => a -> String
show Int
i String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
"."
        | Int
i <- [Int
1 .. [[Block]] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length [[Block]]
bss]
        ]

prettyBlock Theme
_theme (Pandoc.RawBlock Format
_ Text
t) = Text -> Doc
PP.text Text
t Doc -> Doc -> Doc
forall a. Semigroup a => a -> a -> a
<> Doc
PP.hardline

prettyBlock Theme
_theme Block
Pandoc.HorizontalRule = Doc
"---"

prettyBlock theme :: Theme
theme@Theme {Maybe Text
Maybe SyntaxHighlighting
Maybe Style
themeSyntaxHighlighting :: Maybe SyntaxHighlighting
themeImageTarget :: Maybe Style
themeImageText :: Maybe Style
themeMath :: Maybe Style
themeQuoted :: Maybe Style
themeStrikeout :: Maybe Style
themeLinkTarget :: Maybe Style
themeLinkText :: Maybe Style
themeCode :: Maybe Style
themeUnderline :: Maybe Style
themeStrong :: Maybe Style
themeEmph :: Maybe Style
themeLineBlock :: Maybe Style
themeTableSeparator :: Maybe Style
themeTableHeader :: Maybe Style
themeDefinitionList :: Maybe Style
themeDefinitionTerm :: Maybe Style
themeBlockQuote :: Maybe Style
themeOrderedList :: Maybe Style
themeBulletListMarkers :: Maybe Text
themeBulletList :: Maybe Style
themeCodeBlock :: Maybe Style
themeHeader :: Maybe Style
themeBorders :: Maybe Style
themeSyntaxHighlighting :: Theme -> Maybe SyntaxHighlighting
themeImageTarget :: Theme -> Maybe Style
themeImageText :: Theme -> Maybe Style
themeMath :: Theme -> Maybe Style
themeQuoted :: Theme -> Maybe Style
themeStrikeout :: Theme -> Maybe Style
themeLinkTarget :: Theme -> Maybe Style
themeLinkText :: Theme -> Maybe Style
themeCode :: Theme -> Maybe Style
themeUnderline :: Theme -> Maybe Style
themeStrong :: Theme -> Maybe Style
themeEmph :: Theme -> Maybe Style
themeLineBlock :: Theme -> Maybe Style
themeTableSeparator :: Theme -> Maybe Style
themeTableHeader :: Theme -> Maybe Style
themeDefinitionList :: Theme -> Maybe Style
themeDefinitionTerm :: Theme -> Maybe Style
themeBlockQuote :: Theme -> Maybe Style
themeOrderedList :: Theme -> Maybe Style
themeBulletListMarkers :: Theme -> Maybe Text
themeBulletList :: Theme -> Maybe Style
themeCodeBlock :: Theme -> Maybe Style
themeHeader :: Theme -> Maybe Style
themeBorders :: Theme -> Maybe Style
..} (Pandoc.BlockQuote [Block]
bs) =
    let quote :: Trimmable Doc
quote = Doc -> Trimmable Doc
forall a. a -> Trimmable a
PP.NotTrimmable (Maybe Style -> Doc -> Doc
themed Maybe Style
themeBlockQuote Doc
"> ") in
    Trimmable Doc -> Trimmable Doc -> Doc -> Doc
PP.indent Trimmable Doc
quote Trimmable Doc
quote (Theme -> [Block] -> Doc
prettyBlocks Theme
theme [Block]
bs)

prettyBlock theme :: Theme
theme@Theme {Maybe Text
Maybe SyntaxHighlighting
Maybe Style
themeSyntaxHighlighting :: Maybe SyntaxHighlighting
themeImageTarget :: Maybe Style
themeImageText :: Maybe Style
themeMath :: Maybe Style
themeQuoted :: Maybe Style
themeStrikeout :: Maybe Style
themeLinkTarget :: Maybe Style
themeLinkText :: Maybe Style
themeCode :: Maybe Style
themeUnderline :: Maybe Style
themeStrong :: Maybe Style
themeEmph :: Maybe Style
themeLineBlock :: Maybe Style
themeTableSeparator :: Maybe Style
themeTableHeader :: Maybe Style
themeDefinitionList :: Maybe Style
themeDefinitionTerm :: Maybe Style
themeBlockQuote :: Maybe Style
themeOrderedList :: Maybe Style
themeBulletListMarkers :: Maybe Text
themeBulletList :: Maybe Style
themeCodeBlock :: Maybe Style
themeHeader :: Maybe Style
themeBorders :: Maybe Style
themeSyntaxHighlighting :: Theme -> Maybe SyntaxHighlighting
themeImageTarget :: Theme -> Maybe Style
themeImageText :: Theme -> Maybe Style
themeMath :: Theme -> Maybe Style
themeQuoted :: Theme -> Maybe Style
themeStrikeout :: Theme -> Maybe Style
themeLinkTarget :: Theme -> Maybe Style
themeLinkText :: Theme -> Maybe Style
themeCode :: Theme -> Maybe Style
themeUnderline :: Theme -> Maybe Style
themeStrong :: Theme -> Maybe Style
themeEmph :: Theme -> Maybe Style
themeLineBlock :: Theme -> Maybe Style
themeTableSeparator :: Theme -> Maybe Style
themeTableHeader :: Theme -> Maybe Style
themeDefinitionList :: Theme -> Maybe Style
themeDefinitionTerm :: Theme -> Maybe Style
themeBlockQuote :: Theme -> Maybe Style
themeOrderedList :: Theme -> Maybe Style
themeBulletListMarkers :: Theme -> Maybe Text
themeBulletList :: Theme -> Maybe Style
themeCodeBlock :: Theme -> Maybe Style
themeHeader :: Theme -> Maybe Style
themeBorders :: Theme -> Maybe Style
..} (Pandoc.DefinitionList [([Inline], [[Block]])]
terms) =
    [Doc] -> Doc
PP.vcat ([Doc] -> Doc) -> [Doc] -> Doc
forall a b. (a -> b) -> a -> b
$ (([Inline], [[Block]]) -> Doc) -> [([Inline], [[Block]])] -> [Doc]
forall a b. (a -> b) -> [a] -> [b]
map ([Inline], [[Block]]) -> Doc
prettyDefinition [([Inline], [[Block]])]
terms
  where
    prettyDefinition :: ([Inline], [[Block]]) -> Doc
prettyDefinition ([Inline]
term, [[Block]]
definitions) =
        Maybe Style -> Doc -> Doc
themed Maybe Style
themeDefinitionTerm (Theme -> [Inline] -> Doc
prettyInlines Theme
theme [Inline]
term) Doc -> Doc -> Doc
<$$>
        Doc
PP.hardline Doc -> Doc -> Doc
forall a. Semigroup a => a -> a -> a
<> [Doc] -> Doc
PP.vcat
        [ Trimmable Doc -> Trimmable Doc -> Doc -> Doc
PP.indent
            (Doc -> Trimmable Doc
forall a. a -> Trimmable a
PP.NotTrimmable (Maybe Style -> Doc -> Doc
themed Maybe Style
themeDefinitionList Doc
":   "))
            (Doc -> Trimmable Doc
forall a. a -> Trimmable a
PP.Trimmable Doc
"    ") (Doc -> Doc) -> Doc -> Doc
forall a b. (a -> b) -> a -> b
$
            Theme -> [Block] -> Doc
prettyBlocks Theme
theme ([Block] -> [Block]
Pandoc.plainToPara [Block]
definition)
        | [Block]
definition <- [[Block]]
definitions
        ]

prettyBlock Theme
theme (Pandoc.Table Attr
_ Caption
caption [ColSpec]
specs TableHead
thead [TableBody]
tbodies TableFoot
tfoot) =
    Maybe Int -> Doc -> Doc
PP.wrapAt Maybe Int
forall a. Maybe a
Nothing (Doc -> Doc) -> Doc -> Doc
forall a b. (a -> b) -> a -> b
$
    Theme -> Table -> Doc
prettyTable Theme
theme Table :: Doc -> [Alignment] -> [Doc] -> [[Doc]] -> Table
Table
        { tCaption :: Doc
tCaption = Theme -> [Inline] -> Doc
prettyInlines Theme
theme [Inline]
caption'
        , tAligns :: [Alignment]
tAligns  = (Alignment -> Alignment) -> [Alignment] -> [Alignment]
forall a b. (a -> b) -> [a] -> [b]
map Alignment -> Alignment
align [Alignment]
aligns
        , tHeaders :: [Doc]
tHeaders = ([Block] -> Doc) -> [[Block]] -> [Doc]
forall a b. (a -> b) -> [a] -> [b]
map (Theme -> [Block] -> Doc
prettyBlocks Theme
theme) [[Block]]
headers
        , tRows :: [[Doc]]
tRows    = ([[Block]] -> [Doc]) -> [[[Block]]] -> [[Doc]]
forall a b. (a -> b) -> [a] -> [b]
map (([Block] -> Doc) -> [[Block]] -> [Doc]
forall a b. (a -> b) -> [a] -> [b]
map (Theme -> [Block] -> Doc
prettyBlocks Theme
theme)) [[[Block]]]
rows
        }
  where
    ([Inline]
caption', [Alignment]
aligns, [Double]
_, [[Block]]
headers, [[[Block]]]
rows) = Caption
-> [ColSpec]
-> TableHead
-> [TableBody]
-> TableFoot
-> ([Inline], [Alignment], [Double], [[Block]], [[[Block]]])
Pandoc.toLegacyTable
        Caption
caption [ColSpec]
specs TableHead
thead [TableBody]
tbodies TableFoot
tfoot

    align :: Alignment -> Alignment
align Alignment
Pandoc.AlignLeft    = Alignment
PP.AlignLeft
    align Alignment
Pandoc.AlignCenter  = Alignment
PP.AlignCenter
    align Alignment
Pandoc.AlignDefault = Alignment
PP.AlignLeft
    align Alignment
Pandoc.AlignRight   = Alignment
PP.AlignRight

prettyBlock Theme
theme (Pandoc.Div Attr
_attrs [Block]
blocks) = Theme -> [Block] -> Doc
prettyBlocks Theme
theme [Block]
blocks

prettyBlock Theme
_theme Block
Pandoc.Null = Doc
forall a. Monoid a => a
mempty

#if MIN_VERSION_pandoc(1,18,0)
-- 'LineBlock' elements are new in pandoc-1.18
prettyBlock theme :: Theme
theme@Theme {Maybe Text
Maybe SyntaxHighlighting
Maybe Style
themeSyntaxHighlighting :: Maybe SyntaxHighlighting
themeImageTarget :: Maybe Style
themeImageText :: Maybe Style
themeMath :: Maybe Style
themeQuoted :: Maybe Style
themeStrikeout :: Maybe Style
themeLinkTarget :: Maybe Style
themeLinkText :: Maybe Style
themeCode :: Maybe Style
themeUnderline :: Maybe Style
themeStrong :: Maybe Style
themeEmph :: Maybe Style
themeLineBlock :: Maybe Style
themeTableSeparator :: Maybe Style
themeTableHeader :: Maybe Style
themeDefinitionList :: Maybe Style
themeDefinitionTerm :: Maybe Style
themeBlockQuote :: Maybe Style
themeOrderedList :: Maybe Style
themeBulletListMarkers :: Maybe Text
themeBulletList :: Maybe Style
themeCodeBlock :: Maybe Style
themeHeader :: Maybe Style
themeBorders :: Maybe Style
themeSyntaxHighlighting :: Theme -> Maybe SyntaxHighlighting
themeImageTarget :: Theme -> Maybe Style
themeImageText :: Theme -> Maybe Style
themeMath :: Theme -> Maybe Style
themeQuoted :: Theme -> Maybe Style
themeStrikeout :: Theme -> Maybe Style
themeLinkTarget :: Theme -> Maybe Style
themeLinkText :: Theme -> Maybe Style
themeCode :: Theme -> Maybe Style
themeUnderline :: Theme -> Maybe Style
themeStrong :: Theme -> Maybe Style
themeEmph :: Theme -> Maybe Style
themeLineBlock :: Theme -> Maybe Style
themeTableSeparator :: Theme -> Maybe Style
themeTableHeader :: Theme -> Maybe Style
themeDefinitionList :: Theme -> Maybe Style
themeDefinitionTerm :: Theme -> Maybe Style
themeBlockQuote :: Theme -> Maybe Style
themeOrderedList :: Theme -> Maybe Style
themeBulletListMarkers :: Theme -> Maybe Text
themeBulletList :: Theme -> Maybe Style
themeCodeBlock :: Theme -> Maybe Style
themeHeader :: Theme -> Maybe Style
themeBorders :: Theme -> Maybe Style
..} (Pandoc.LineBlock [[Inline]]
inliness) =
    let ind :: Trimmable Doc
ind = Doc -> Trimmable Doc
forall a. a -> Trimmable a
PP.NotTrimmable (Maybe Style -> Doc -> Doc
themed Maybe Style
themeLineBlock Doc
"| ") in
    Maybe Int -> Doc -> Doc
PP.wrapAt Maybe Int
forall a. Maybe a
Nothing (Doc -> Doc) -> Doc -> Doc
forall a b. (a -> b) -> a -> b
$
    Trimmable Doc -> Trimmable Doc -> Doc -> Doc
PP.indent Trimmable Doc
ind Trimmable Doc
ind (Doc -> Doc) -> Doc -> Doc
forall a b. (a -> b) -> a -> b
$
    [Doc] -> Doc
PP.vcat ([Doc] -> Doc) -> [Doc] -> Doc
forall a b. (a -> b) -> a -> b
$
    ([Inline] -> Doc) -> [[Inline]] -> [Doc]
forall a b. (a -> b) -> [a] -> [b]
map (Theme -> [Inline] -> Doc
prettyInlines Theme
theme) [[Inline]]
inliness
#endif


--------------------------------------------------------------------------------
prettyBlocks :: Theme -> [Pandoc.Block] -> PP.Doc
prettyBlocks :: Theme -> [Block] -> Doc
prettyBlocks Theme
theme = [Doc] -> Doc
PP.vcat ([Doc] -> Doc) -> ([Block] -> [Doc]) -> [Block] -> Doc
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Block -> Doc) -> [Block] -> [Doc]
forall a b. (a -> b) -> [a] -> [b]
map (Theme -> Block -> Doc
prettyBlock Theme
theme) ([Block] -> [Doc]) -> ([Block] -> [Block]) -> [Block] -> [Doc]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Block -> Bool) -> [Block] -> [Block]
forall a. (a -> Bool) -> [a] -> [a]
filter Block -> Bool
isVisibleBlock


--------------------------------------------------------------------------------
prettyInline :: Theme -> Pandoc.Inline -> PP.Doc

prettyInline :: Theme -> Inline -> Doc
prettyInline Theme
_theme Inline
Pandoc.Space = Doc
PP.space

prettyInline Theme
_theme (Pandoc.Str Text
str) = Text -> Doc
PP.text Text
str

prettyInline theme :: Theme
theme@Theme {Maybe Text
Maybe SyntaxHighlighting
Maybe Style
themeSyntaxHighlighting :: Maybe SyntaxHighlighting
themeImageTarget :: Maybe Style
themeImageText :: Maybe Style
themeMath :: Maybe Style
themeQuoted :: Maybe Style
themeStrikeout :: Maybe Style
themeLinkTarget :: Maybe Style
themeLinkText :: Maybe Style
themeCode :: Maybe Style
themeUnderline :: Maybe Style
themeStrong :: Maybe Style
themeEmph :: Maybe Style
themeLineBlock :: Maybe Style
themeTableSeparator :: Maybe Style
themeTableHeader :: Maybe Style
themeDefinitionList :: Maybe Style
themeDefinitionTerm :: Maybe Style
themeBlockQuote :: Maybe Style
themeOrderedList :: Maybe Style
themeBulletListMarkers :: Maybe Text
themeBulletList :: Maybe Style
themeCodeBlock :: Maybe Style
themeHeader :: Maybe Style
themeBorders :: Maybe Style
themeSyntaxHighlighting :: Theme -> Maybe SyntaxHighlighting
themeImageTarget :: Theme -> Maybe Style
themeImageText :: Theme -> Maybe Style
themeMath :: Theme -> Maybe Style
themeQuoted :: Theme -> Maybe Style
themeStrikeout :: Theme -> Maybe Style
themeLinkTarget :: Theme -> Maybe Style
themeLinkText :: Theme -> Maybe Style
themeCode :: Theme -> Maybe Style
themeUnderline :: Theme -> Maybe Style
themeStrong :: Theme -> Maybe Style
themeEmph :: Theme -> Maybe Style
themeLineBlock :: Theme -> Maybe Style
themeTableSeparator :: Theme -> Maybe Style
themeTableHeader :: Theme -> Maybe Style
themeDefinitionList :: Theme -> Maybe Style
themeDefinitionTerm :: Theme -> Maybe Style
themeBlockQuote :: Theme -> Maybe Style
themeOrderedList :: Theme -> Maybe Style
themeBulletListMarkers :: Theme -> Maybe Text
themeBulletList :: Theme -> Maybe Style
themeCodeBlock :: Theme -> Maybe Style
themeHeader :: Theme -> Maybe Style
themeBorders :: Theme -> Maybe Style
..} (Pandoc.Emph [Inline]
inlines) =
    Maybe Style -> Doc -> Doc
themed Maybe Style
themeEmph (Doc -> Doc) -> Doc -> Doc
forall a b. (a -> b) -> a -> b
$
    Theme -> [Inline] -> Doc
prettyInlines Theme
theme [Inline]
inlines

prettyInline theme :: Theme
theme@Theme {Maybe Text
Maybe SyntaxHighlighting
Maybe Style
themeSyntaxHighlighting :: Maybe SyntaxHighlighting
themeImageTarget :: Maybe Style
themeImageText :: Maybe Style
themeMath :: Maybe Style
themeQuoted :: Maybe Style
themeStrikeout :: Maybe Style
themeLinkTarget :: Maybe Style
themeLinkText :: Maybe Style
themeCode :: Maybe Style
themeUnderline :: Maybe Style
themeStrong :: Maybe Style
themeEmph :: Maybe Style
themeLineBlock :: Maybe Style
themeTableSeparator :: Maybe Style
themeTableHeader :: Maybe Style
themeDefinitionList :: Maybe Style
themeDefinitionTerm :: Maybe Style
themeBlockQuote :: Maybe Style
themeOrderedList :: Maybe Style
themeBulletListMarkers :: Maybe Text
themeBulletList :: Maybe Style
themeCodeBlock :: Maybe Style
themeHeader :: Maybe Style
themeBorders :: Maybe Style
themeSyntaxHighlighting :: Theme -> Maybe SyntaxHighlighting
themeImageTarget :: Theme -> Maybe Style
themeImageText :: Theme -> Maybe Style
themeMath :: Theme -> Maybe Style
themeQuoted :: Theme -> Maybe Style
themeStrikeout :: Theme -> Maybe Style
themeLinkTarget :: Theme -> Maybe Style
themeLinkText :: Theme -> Maybe Style
themeCode :: Theme -> Maybe Style
themeUnderline :: Theme -> Maybe Style
themeStrong :: Theme -> Maybe Style
themeEmph :: Theme -> Maybe Style
themeLineBlock :: Theme -> Maybe Style
themeTableSeparator :: Theme -> Maybe Style
themeTableHeader :: Theme -> Maybe Style
themeDefinitionList :: Theme -> Maybe Style
themeDefinitionTerm :: Theme -> Maybe Style
themeBlockQuote :: Theme -> Maybe Style
themeOrderedList :: Theme -> Maybe Style
themeBulletListMarkers :: Theme -> Maybe Text
themeBulletList :: Theme -> Maybe Style
themeCodeBlock :: Theme -> Maybe Style
themeHeader :: Theme -> Maybe Style
themeBorders :: Theme -> Maybe Style
..} (Pandoc.Strong [Inline]
inlines) =
    Maybe Style -> Doc -> Doc
themed Maybe Style
themeStrong (Doc -> Doc) -> Doc -> Doc
forall a b. (a -> b) -> a -> b
$
    Theme -> [Inline] -> Doc
prettyInlines Theme
theme [Inline]
inlines

prettyInline theme :: Theme
theme@Theme {Maybe Text
Maybe SyntaxHighlighting
Maybe Style
themeSyntaxHighlighting :: Maybe SyntaxHighlighting
themeImageTarget :: Maybe Style
themeImageText :: Maybe Style
themeMath :: Maybe Style
themeQuoted :: Maybe Style
themeStrikeout :: Maybe Style
themeLinkTarget :: Maybe Style
themeLinkText :: Maybe Style
themeCode :: Maybe Style
themeUnderline :: Maybe Style
themeStrong :: Maybe Style
themeEmph :: Maybe Style
themeLineBlock :: Maybe Style
themeTableSeparator :: Maybe Style
themeTableHeader :: Maybe Style
themeDefinitionList :: Maybe Style
themeDefinitionTerm :: Maybe Style
themeBlockQuote :: Maybe Style
themeOrderedList :: Maybe Style
themeBulletListMarkers :: Maybe Text
themeBulletList :: Maybe Style
themeCodeBlock :: Maybe Style
themeHeader :: Maybe Style
themeBorders :: Maybe Style
themeSyntaxHighlighting :: Theme -> Maybe SyntaxHighlighting
themeImageTarget :: Theme -> Maybe Style
themeImageText :: Theme -> Maybe Style
themeMath :: Theme -> Maybe Style
themeQuoted :: Theme -> Maybe Style
themeStrikeout :: Theme -> Maybe Style
themeLinkTarget :: Theme -> Maybe Style
themeLinkText :: Theme -> Maybe Style
themeCode :: Theme -> Maybe Style
themeUnderline :: Theme -> Maybe Style
themeStrong :: Theme -> Maybe Style
themeEmph :: Theme -> Maybe Style
themeLineBlock :: Theme -> Maybe Style
themeTableSeparator :: Theme -> Maybe Style
themeTableHeader :: Theme -> Maybe Style
themeDefinitionList :: Theme -> Maybe Style
themeDefinitionTerm :: Theme -> Maybe Style
themeBlockQuote :: Theme -> Maybe Style
themeOrderedList :: Theme -> Maybe Style
themeBulletListMarkers :: Theme -> Maybe Text
themeBulletList :: Theme -> Maybe Style
themeCodeBlock :: Theme -> Maybe Style
themeHeader :: Theme -> Maybe Style
themeBorders :: Theme -> Maybe Style
..} (Pandoc.Underline [Inline]
inlines) =
    Maybe Style -> Doc -> Doc
themed Maybe Style
themeUnderline (Doc -> Doc) -> Doc -> Doc
forall a b. (a -> b) -> a -> b
$
    Theme -> [Inline] -> Doc
prettyInlines Theme
theme [Inline]
inlines

prettyInline Theme {Maybe Text
Maybe SyntaxHighlighting
Maybe Style
themeSyntaxHighlighting :: Maybe SyntaxHighlighting
themeImageTarget :: Maybe Style
themeImageText :: Maybe Style
themeMath :: Maybe Style
themeQuoted :: Maybe Style
themeStrikeout :: Maybe Style
themeLinkTarget :: Maybe Style
themeLinkText :: Maybe Style
themeCode :: Maybe Style
themeUnderline :: Maybe Style
themeStrong :: Maybe Style
themeEmph :: Maybe Style
themeLineBlock :: Maybe Style
themeTableSeparator :: Maybe Style
themeTableHeader :: Maybe Style
themeDefinitionList :: Maybe Style
themeDefinitionTerm :: Maybe Style
themeBlockQuote :: Maybe Style
themeOrderedList :: Maybe Style
themeBulletListMarkers :: Maybe Text
themeBulletList :: Maybe Style
themeCodeBlock :: Maybe Style
themeHeader :: Maybe Style
themeBorders :: Maybe Style
themeSyntaxHighlighting :: Theme -> Maybe SyntaxHighlighting
themeImageTarget :: Theme -> Maybe Style
themeImageText :: Theme -> Maybe Style
themeMath :: Theme -> Maybe Style
themeQuoted :: Theme -> Maybe Style
themeStrikeout :: Theme -> Maybe Style
themeLinkTarget :: Theme -> Maybe Style
themeLinkText :: Theme -> Maybe Style
themeCode :: Theme -> Maybe Style
themeUnderline :: Theme -> Maybe Style
themeStrong :: Theme -> Maybe Style
themeEmph :: Theme -> Maybe Style
themeLineBlock :: Theme -> Maybe Style
themeTableSeparator :: Theme -> Maybe Style
themeTableHeader :: Theme -> Maybe Style
themeDefinitionList :: Theme -> Maybe Style
themeDefinitionTerm :: Theme -> Maybe Style
themeBlockQuote :: Theme -> Maybe Style
themeOrderedList :: Theme -> Maybe Style
themeBulletListMarkers :: Theme -> Maybe Text
themeBulletList :: Theme -> Maybe Style
themeCodeBlock :: Theme -> Maybe Style
themeHeader :: Theme -> Maybe Style
themeBorders :: Theme -> Maybe Style
..} (Pandoc.Code Attr
_ Text
txt) =
    Maybe Style -> Doc -> Doc
themed Maybe Style
themeCode (Doc -> Doc) -> Doc -> Doc
forall a b. (a -> b) -> a -> b
$
    Text -> Doc
PP.text (Text
" " Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
txt Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
" ")

prettyInline theme :: Theme
theme@Theme {Maybe Text
Maybe SyntaxHighlighting
Maybe Style
themeSyntaxHighlighting :: Maybe SyntaxHighlighting
themeImageTarget :: Maybe Style
themeImageText :: Maybe Style
themeMath :: Maybe Style
themeQuoted :: Maybe Style
themeStrikeout :: Maybe Style
themeLinkTarget :: Maybe Style
themeLinkText :: Maybe Style
themeCode :: Maybe Style
themeUnderline :: Maybe Style
themeStrong :: Maybe Style
themeEmph :: Maybe Style
themeLineBlock :: Maybe Style
themeTableSeparator :: Maybe Style
themeTableHeader :: Maybe Style
themeDefinitionList :: Maybe Style
themeDefinitionTerm :: Maybe Style
themeBlockQuote :: Maybe Style
themeOrderedList :: Maybe Style
themeBulletListMarkers :: Maybe Text
themeBulletList :: Maybe Style
themeCodeBlock :: Maybe Style
themeHeader :: Maybe Style
themeBorders :: Maybe Style
themeSyntaxHighlighting :: Theme -> Maybe SyntaxHighlighting
themeImageTarget :: Theme -> Maybe Style
themeImageText :: Theme -> Maybe Style
themeMath :: Theme -> Maybe Style
themeQuoted :: Theme -> Maybe Style
themeStrikeout :: Theme -> Maybe Style
themeLinkTarget :: Theme -> Maybe Style
themeLinkText :: Theme -> Maybe Style
themeCode :: Theme -> Maybe Style
themeUnderline :: Theme -> Maybe Style
themeStrong :: Theme -> Maybe Style
themeEmph :: Theme -> Maybe Style
themeLineBlock :: Theme -> Maybe Style
themeTableSeparator :: Theme -> Maybe Style
themeTableHeader :: Theme -> Maybe Style
themeDefinitionList :: Theme -> Maybe Style
themeDefinitionTerm :: Theme -> Maybe Style
themeBlockQuote :: Theme -> Maybe Style
themeOrderedList :: Theme -> Maybe Style
themeBulletListMarkers :: Theme -> Maybe Text
themeBulletList :: Theme -> Maybe Style
themeCodeBlock :: Theme -> Maybe Style
themeHeader :: Theme -> Maybe Style
themeBorders :: Theme -> Maybe Style
..} link :: Inline
link@(Pandoc.Link Attr
_attrs [Inline]
text (Text
target, Text
_title))
    | Inline -> Bool
isReferenceLink Inline
link =
        Doc
"[" Doc -> Doc -> Doc
forall a. Semigroup a => a -> a -> a
<> Maybe Style -> Doc -> Doc
themed Maybe Style
themeLinkText (Theme -> [Inline] -> Doc
prettyInlines Theme
theme [Inline]
text) Doc -> Doc -> Doc
forall a. Semigroup a => a -> a -> a
<> Doc
"]"
    | Bool
otherwise =
        Doc
"<" Doc -> Doc -> Doc
forall a. Semigroup a => a -> a -> a
<> Maybe Style -> Doc -> Doc
themed Maybe Style
themeLinkTarget (Text -> Doc
PP.text Text
target) Doc -> Doc -> Doc
forall a. Semigroup a => a -> a -> a
<> Doc
">"

prettyInline Theme
_theme Inline
Pandoc.SoftBreak = Doc
PP.softline

prettyInline Theme
_theme Inline
Pandoc.LineBreak = Doc
PP.hardline

prettyInline theme :: Theme
theme@Theme {Maybe Text
Maybe SyntaxHighlighting
Maybe Style
themeSyntaxHighlighting :: Maybe SyntaxHighlighting
themeImageTarget :: Maybe Style
themeImageText :: Maybe Style
themeMath :: Maybe Style
themeQuoted :: Maybe Style
themeStrikeout :: Maybe Style
themeLinkTarget :: Maybe Style
themeLinkText :: Maybe Style
themeCode :: Maybe Style
themeUnderline :: Maybe Style
themeStrong :: Maybe Style
themeEmph :: Maybe Style
themeLineBlock :: Maybe Style
themeTableSeparator :: Maybe Style
themeTableHeader :: Maybe Style
themeDefinitionList :: Maybe Style
themeDefinitionTerm :: Maybe Style
themeBlockQuote :: Maybe Style
themeOrderedList :: Maybe Style
themeBulletListMarkers :: Maybe Text
themeBulletList :: Maybe Style
themeCodeBlock :: Maybe Style
themeHeader :: Maybe Style
themeBorders :: Maybe Style
themeSyntaxHighlighting :: Theme -> Maybe SyntaxHighlighting
themeImageTarget :: Theme -> Maybe Style
themeImageText :: Theme -> Maybe Style
themeMath :: Theme -> Maybe Style
themeQuoted :: Theme -> Maybe Style
themeStrikeout :: Theme -> Maybe Style
themeLinkTarget :: Theme -> Maybe Style
themeLinkText :: Theme -> Maybe Style
themeCode :: Theme -> Maybe Style
themeUnderline :: Theme -> Maybe Style
themeStrong :: Theme -> Maybe Style
themeEmph :: Theme -> Maybe Style
themeLineBlock :: Theme -> Maybe Style
themeTableSeparator :: Theme -> Maybe Style
themeTableHeader :: Theme -> Maybe Style
themeDefinitionList :: Theme -> Maybe Style
themeDefinitionTerm :: Theme -> Maybe Style
themeBlockQuote :: Theme -> Maybe Style
themeOrderedList :: Theme -> Maybe Style
themeBulletListMarkers :: Theme -> Maybe Text
themeBulletList :: Theme -> Maybe Style
themeCodeBlock :: Theme -> Maybe Style
themeHeader :: Theme -> Maybe Style
themeBorders :: Theme -> Maybe Style
..} (Pandoc.Strikeout [Inline]
t) =
    Doc
"~~" Doc -> Doc -> Doc
forall a. Semigroup a => a -> a -> a
<> Maybe Style -> Doc -> Doc
themed Maybe Style
themeStrikeout (Theme -> [Inline] -> Doc
prettyInlines Theme
theme [Inline]
t) Doc -> Doc -> Doc
forall a. Semigroup a => a -> a -> a
<> Doc
"~~"

prettyInline theme :: Theme
theme@Theme {Maybe Text
Maybe SyntaxHighlighting
Maybe Style
themeSyntaxHighlighting :: Maybe SyntaxHighlighting
themeImageTarget :: Maybe Style
themeImageText :: Maybe Style
themeMath :: Maybe Style
themeQuoted :: Maybe Style
themeStrikeout :: Maybe Style
themeLinkTarget :: Maybe Style
themeLinkText :: Maybe Style
themeCode :: Maybe Style
themeUnderline :: Maybe Style
themeStrong :: Maybe Style
themeEmph :: Maybe Style
themeLineBlock :: Maybe Style
themeTableSeparator :: Maybe Style
themeTableHeader :: Maybe Style
themeDefinitionList :: Maybe Style
themeDefinitionTerm :: Maybe Style
themeBlockQuote :: Maybe Style
themeOrderedList :: Maybe Style
themeBulletListMarkers :: Maybe Text
themeBulletList :: Maybe Style
themeCodeBlock :: Maybe Style
themeHeader :: Maybe Style
themeBorders :: Maybe Style
themeSyntaxHighlighting :: Theme -> Maybe SyntaxHighlighting
themeImageTarget :: Theme -> Maybe Style
themeImageText :: Theme -> Maybe Style
themeMath :: Theme -> Maybe Style
themeQuoted :: Theme -> Maybe Style
themeStrikeout :: Theme -> Maybe Style
themeLinkTarget :: Theme -> Maybe Style
themeLinkText :: Theme -> Maybe Style
themeCode :: Theme -> Maybe Style
themeUnderline :: Theme -> Maybe Style
themeStrong :: Theme -> Maybe Style
themeEmph :: Theme -> Maybe Style
themeLineBlock :: Theme -> Maybe Style
themeTableSeparator :: Theme -> Maybe Style
themeTableHeader :: Theme -> Maybe Style
themeDefinitionList :: Theme -> Maybe Style
themeDefinitionTerm :: Theme -> Maybe Style
themeBlockQuote :: Theme -> Maybe Style
themeOrderedList :: Theme -> Maybe Style
themeBulletListMarkers :: Theme -> Maybe Text
themeBulletList :: Theme -> Maybe Style
themeCodeBlock :: Theme -> Maybe Style
themeHeader :: Theme -> Maybe Style
themeBorders :: Theme -> Maybe Style
..} (Pandoc.Quoted QuoteType
Pandoc.SingleQuote [Inline]
t) =
    Doc
"'" Doc -> Doc -> Doc
forall a. Semigroup a => a -> a -> a
<> Maybe Style -> Doc -> Doc
themed Maybe Style
themeQuoted (Theme -> [Inline] -> Doc
prettyInlines Theme
theme [Inline]
t) Doc -> Doc -> Doc
forall a. Semigroup a => a -> a -> a
<> Doc
"'"
prettyInline theme :: Theme
theme@Theme {Maybe Text
Maybe SyntaxHighlighting
Maybe Style
themeSyntaxHighlighting :: Maybe SyntaxHighlighting
themeImageTarget :: Maybe Style
themeImageText :: Maybe Style
themeMath :: Maybe Style
themeQuoted :: Maybe Style
themeStrikeout :: Maybe Style
themeLinkTarget :: Maybe Style
themeLinkText :: Maybe Style
themeCode :: Maybe Style
themeUnderline :: Maybe Style
themeStrong :: Maybe Style
themeEmph :: Maybe Style
themeLineBlock :: Maybe Style
themeTableSeparator :: Maybe Style
themeTableHeader :: Maybe Style
themeDefinitionList :: Maybe Style
themeDefinitionTerm :: Maybe Style
themeBlockQuote :: Maybe Style
themeOrderedList :: Maybe Style
themeBulletListMarkers :: Maybe Text
themeBulletList :: Maybe Style
themeCodeBlock :: Maybe Style
themeHeader :: Maybe Style
themeBorders :: Maybe Style
themeSyntaxHighlighting :: Theme -> Maybe SyntaxHighlighting
themeImageTarget :: Theme -> Maybe Style
themeImageText :: Theme -> Maybe Style
themeMath :: Theme -> Maybe Style
themeQuoted :: Theme -> Maybe Style
themeStrikeout :: Theme -> Maybe Style
themeLinkTarget :: Theme -> Maybe Style
themeLinkText :: Theme -> Maybe Style
themeCode :: Theme -> Maybe Style
themeUnderline :: Theme -> Maybe Style
themeStrong :: Theme -> Maybe Style
themeEmph :: Theme -> Maybe Style
themeLineBlock :: Theme -> Maybe Style
themeTableSeparator :: Theme -> Maybe Style
themeTableHeader :: Theme -> Maybe Style
themeDefinitionList :: Theme -> Maybe Style
themeDefinitionTerm :: Theme -> Maybe Style
themeBlockQuote :: Theme -> Maybe Style
themeOrderedList :: Theme -> Maybe Style
themeBulletListMarkers :: Theme -> Maybe Text
themeBulletList :: Theme -> Maybe Style
themeCodeBlock :: Theme -> Maybe Style
themeHeader :: Theme -> Maybe Style
themeBorders :: Theme -> Maybe Style
..} (Pandoc.Quoted QuoteType
Pandoc.DoubleQuote [Inline]
t) =
    Doc
"'" Doc -> Doc -> Doc
forall a. Semigroup a => a -> a -> a
<> Maybe Style -> Doc -> Doc
themed Maybe Style
themeQuoted (Theme -> [Inline] -> Doc
prettyInlines Theme
theme [Inline]
t) Doc -> Doc -> Doc
forall a. Semigroup a => a -> a -> a
<> Doc
"'"

prettyInline Theme {Maybe Text
Maybe SyntaxHighlighting
Maybe Style
themeSyntaxHighlighting :: Maybe SyntaxHighlighting
themeImageTarget :: Maybe Style
themeImageText :: Maybe Style
themeMath :: Maybe Style
themeQuoted :: Maybe Style
themeStrikeout :: Maybe Style
themeLinkTarget :: Maybe Style
themeLinkText :: Maybe Style
themeCode :: Maybe Style
themeUnderline :: Maybe Style
themeStrong :: Maybe Style
themeEmph :: Maybe Style
themeLineBlock :: Maybe Style
themeTableSeparator :: Maybe Style
themeTableHeader :: Maybe Style
themeDefinitionList :: Maybe Style
themeDefinitionTerm :: Maybe Style
themeBlockQuote :: Maybe Style
themeOrderedList :: Maybe Style
themeBulletListMarkers :: Maybe Text
themeBulletList :: Maybe Style
themeCodeBlock :: Maybe Style
themeHeader :: Maybe Style
themeBorders :: Maybe Style
themeSyntaxHighlighting :: Theme -> Maybe SyntaxHighlighting
themeImageTarget :: Theme -> Maybe Style
themeImageText :: Theme -> Maybe Style
themeMath :: Theme -> Maybe Style
themeQuoted :: Theme -> Maybe Style
themeStrikeout :: Theme -> Maybe Style
themeLinkTarget :: Theme -> Maybe Style
themeLinkText :: Theme -> Maybe Style
themeCode :: Theme -> Maybe Style
themeUnderline :: Theme -> Maybe Style
themeStrong :: Theme -> Maybe Style
themeEmph :: Theme -> Maybe Style
themeLineBlock :: Theme -> Maybe Style
themeTableSeparator :: Theme -> Maybe Style
themeTableHeader :: Theme -> Maybe Style
themeDefinitionList :: Theme -> Maybe Style
themeDefinitionTerm :: Theme -> Maybe Style
themeBlockQuote :: Theme -> Maybe Style
themeOrderedList :: Theme -> Maybe Style
themeBulletListMarkers :: Theme -> Maybe Text
themeBulletList :: Theme -> Maybe Style
themeCodeBlock :: Theme -> Maybe Style
themeHeader :: Theme -> Maybe Style
themeBorders :: Theme -> Maybe Style
..} (Pandoc.Math MathType
_ Text
t) =
    Maybe Style -> Doc -> Doc
themed Maybe Style
themeMath (Text -> Doc
PP.text Text
t)

prettyInline theme :: Theme
theme@Theme {Maybe Text
Maybe SyntaxHighlighting
Maybe Style
themeSyntaxHighlighting :: Maybe SyntaxHighlighting
themeImageTarget :: Maybe Style
themeImageText :: Maybe Style
themeMath :: Maybe Style
themeQuoted :: Maybe Style
themeStrikeout :: Maybe Style
themeLinkTarget :: Maybe Style
themeLinkText :: Maybe Style
themeCode :: Maybe Style
themeUnderline :: Maybe Style
themeStrong :: Maybe Style
themeEmph :: Maybe Style
themeLineBlock :: Maybe Style
themeTableSeparator :: Maybe Style
themeTableHeader :: Maybe Style
themeDefinitionList :: Maybe Style
themeDefinitionTerm :: Maybe Style
themeBlockQuote :: Maybe Style
themeOrderedList :: Maybe Style
themeBulletListMarkers :: Maybe Text
themeBulletList :: Maybe Style
themeCodeBlock :: Maybe Style
themeHeader :: Maybe Style
themeBorders :: Maybe Style
themeSyntaxHighlighting :: Theme -> Maybe SyntaxHighlighting
themeImageTarget :: Theme -> Maybe Style
themeImageText :: Theme -> Maybe Style
themeMath :: Theme -> Maybe Style
themeQuoted :: Theme -> Maybe Style
themeStrikeout :: Theme -> Maybe Style
themeLinkTarget :: Theme -> Maybe Style
themeLinkText :: Theme -> Maybe Style
themeCode :: Theme -> Maybe Style
themeUnderline :: Theme -> Maybe Style
themeStrong :: Theme -> Maybe Style
themeEmph :: Theme -> Maybe Style
themeLineBlock :: Theme -> Maybe Style
themeTableSeparator :: Theme -> Maybe Style
themeTableHeader :: Theme -> Maybe Style
themeDefinitionList :: Theme -> Maybe Style
themeDefinitionTerm :: Theme -> Maybe Style
themeBlockQuote :: Theme -> Maybe Style
themeOrderedList :: Theme -> Maybe Style
themeBulletListMarkers :: Theme -> Maybe Text
themeBulletList :: Theme -> Maybe Style
themeCodeBlock :: Theme -> Maybe Style
themeHeader :: Theme -> Maybe Style
themeBorders :: Theme -> Maybe Style
..} (Pandoc.Image Attr
_attrs [Inline]
text (Text
target, Text
_title)) =
    Doc
"![" Doc -> Doc -> Doc
forall a. Semigroup a => a -> a -> a
<> Maybe Style -> Doc -> Doc
themed Maybe Style
themeImageText (Theme -> [Inline] -> Doc
prettyInlines Theme
theme [Inline]
text) Doc -> Doc -> Doc
forall a. Semigroup a => a -> a -> a
<> Doc
"](" Doc -> Doc -> Doc
forall a. Semigroup a => a -> a -> a
<>
    Maybe Style -> Doc -> Doc
themed Maybe Style
themeImageTarget (Text -> Doc
PP.text Text
target) Doc -> Doc -> Doc
forall a. Semigroup a => a -> a -> a
<> Doc
")"

-- These elements aren't really supported.
prettyInline Theme
theme  (Pandoc.Cite      [Citation]
_ [Inline]
t) = Theme -> [Inline] -> Doc
prettyInlines Theme
theme [Inline]
t
prettyInline Theme
theme  (Pandoc.Span      Attr
_ [Inline]
t) = Theme -> [Inline] -> Doc
prettyInlines Theme
theme [Inline]
t
prettyInline Theme
_theme (Pandoc.RawInline Format
_ Text
t) = Text -> Doc
PP.text Text
t
prettyInline Theme
theme  (Pandoc.Note        [Block]
t) = Theme -> [Block] -> Doc
prettyBlocks  Theme
theme [Block]
t
prettyInline Theme
theme  (Pandoc.Superscript [Inline]
t) = Theme -> [Inline] -> Doc
prettyInlines Theme
theme [Inline]
t
prettyInline Theme
theme  (Pandoc.Subscript   [Inline]
t) = Theme -> [Inline] -> Doc
prettyInlines Theme
theme [Inline]
t
prettyInline Theme
theme  (Pandoc.SmallCaps   [Inline]
t) = Theme -> [Inline] -> Doc
prettyInlines Theme
theme [Inline]
t
-- prettyInline unsupported = PP.ondullred $ PP.string $ show unsupported


--------------------------------------------------------------------------------
prettyInlines :: Theme -> [Pandoc.Inline] -> PP.Doc
prettyInlines :: Theme -> [Inline] -> Doc
prettyInlines Theme
theme = [Doc] -> Doc
forall a. Monoid a => [a] -> a
mconcat ([Doc] -> Doc) -> ([Inline] -> [Doc]) -> [Inline] -> Doc
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Inline -> Doc) -> [Inline] -> [Doc]
forall a b. (a -> b) -> [a] -> [b]
map (Theme -> Inline -> Doc
prettyInline Theme
theme)


--------------------------------------------------------------------------------
prettyReferences :: Theme -> [Pandoc.Block] -> [PP.Doc]
prettyReferences :: Theme -> [Block] -> [Doc]
prettyReferences theme :: Theme
theme@Theme {Maybe Text
Maybe SyntaxHighlighting
Maybe Style
themeSyntaxHighlighting :: Maybe SyntaxHighlighting
themeImageTarget :: Maybe Style
themeImageText :: Maybe Style
themeMath :: Maybe Style
themeQuoted :: Maybe Style
themeStrikeout :: Maybe Style
themeLinkTarget :: Maybe Style
themeLinkText :: Maybe Style
themeCode :: Maybe Style
themeUnderline :: Maybe Style
themeStrong :: Maybe Style
themeEmph :: Maybe Style
themeLineBlock :: Maybe Style
themeTableSeparator :: Maybe Style
themeTableHeader :: Maybe Style
themeDefinitionList :: Maybe Style
themeDefinitionTerm :: Maybe Style
themeBlockQuote :: Maybe Style
themeOrderedList :: Maybe Style
themeBulletListMarkers :: Maybe Text
themeBulletList :: Maybe Style
themeCodeBlock :: Maybe Style
themeHeader :: Maybe Style
themeBorders :: Maybe Style
themeSyntaxHighlighting :: Theme -> Maybe SyntaxHighlighting
themeImageTarget :: Theme -> Maybe Style
themeImageText :: Theme -> Maybe Style
themeMath :: Theme -> Maybe Style
themeQuoted :: Theme -> Maybe Style
themeStrikeout :: Theme -> Maybe Style
themeLinkTarget :: Theme -> Maybe Style
themeLinkText :: Theme -> Maybe Style
themeCode :: Theme -> Maybe Style
themeUnderline :: Theme -> Maybe Style
themeStrong :: Theme -> Maybe Style
themeEmph :: Theme -> Maybe Style
themeLineBlock :: Theme -> Maybe Style
themeTableSeparator :: Theme -> Maybe Style
themeTableHeader :: Theme -> Maybe Style
themeDefinitionList :: Theme -> Maybe Style
themeDefinitionTerm :: Theme -> Maybe Style
themeBlockQuote :: Theme -> Maybe Style
themeOrderedList :: Theme -> Maybe Style
themeBulletListMarkers :: Theme -> Maybe Text
themeBulletList :: Theme -> Maybe Style
themeCodeBlock :: Theme -> Maybe Style
themeHeader :: Theme -> Maybe Style
themeBorders :: Theme -> Maybe Style
..} =
    (Inline -> Doc) -> [Inline] -> [Doc]
forall a b. (a -> b) -> [a] -> [b]
map Inline -> Doc
prettyReference ([Inline] -> [Doc]) -> ([Block] -> [Inline]) -> [Block] -> [Doc]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Block] -> [Inline]
getReferences
  where
    getReferences :: [Pandoc.Block] -> [Pandoc.Inline]
    getReferences :: [Block] -> [Inline]
getReferences = (Inline -> Bool) -> [Inline] -> [Inline]
forall a. (a -> Bool) -> [a] -> [a]
filter Inline -> Bool
isReferenceLink ([Inline] -> [Inline])
-> ([Block] -> [Inline]) -> [Block] -> [Inline]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Block] -> [Inline]
forall a b. (Data a, Data b) => a -> [b]
grecQ

    prettyReference :: Pandoc.Inline -> PP.Doc
    prettyReference :: Inline -> Doc
prettyReference (Pandoc.Link Attr
_attrs [Inline]
text (Text
target, Text
title)) =
        Doc
"[" Doc -> Doc -> Doc
forall a. Semigroup a => a -> a -> a
<>
        Maybe Style -> Doc -> Doc
themed Maybe Style
themeLinkText (Theme -> [Inline] -> Doc
prettyInlines Theme
theme ([Inline] -> Doc) -> [Inline] -> Doc
forall a b. (a -> b) -> a -> b
$ [Inline] -> [Inline]
Pandoc.newlineToSpace [Inline]
text) Doc -> Doc -> Doc
forall a. Semigroup a => a -> a -> a
<>
        Doc
"](" Doc -> Doc -> Doc
forall a. Semigroup a => a -> a -> a
<>
        Maybe Style -> Doc -> Doc
themed Maybe Style
themeLinkTarget (Text -> Doc
PP.text Text
target) Doc -> Doc -> Doc
forall a. Semigroup a => a -> a -> a
<>
        (if Text -> Bool
T.null Text
title
            then Doc
forall a. Monoid a => a
mempty
            else Doc
PP.space Doc -> Doc -> Doc
forall a. Semigroup a => a -> a -> a
<> Doc
"\"" Doc -> Doc -> Doc
forall a. Semigroup a => a -> a -> a
<> Text -> Doc
PP.text Text
title Doc -> Doc -> Doc
forall a. Semigroup a => a -> a -> a
<> Doc
"\"")
        Doc -> Doc -> Doc
forall a. Semigroup a => a -> a -> a
<> Doc
")"
    prettyReference Inline
_ = Doc
forall a. Monoid a => a
mempty


--------------------------------------------------------------------------------
isReferenceLink :: Pandoc.Inline -> Bool
isReferenceLink :: Inline -> Bool
isReferenceLink (Pandoc.Link Attr
_attrs [Inline]
text (Text
target, Text
_)) =
    [Text -> Inline
Pandoc.Str Text
target] [Inline] -> [Inline] -> Bool
forall a. Eq a => a -> a -> Bool
/= [Inline]
text
isReferenceLink Inline
_ = Bool
False


--------------------------------------------------------------------------------
isVisibleBlock :: Pandoc.Block -> Bool
isVisibleBlock :: Block -> Bool
isVisibleBlock Block
Pandoc.Null = Bool
False
isVisibleBlock (Pandoc.RawBlock (Pandoc.Format Text
"html") Text
t) =
    Bool -> Bool
not (Text
"<!--" Text -> Text -> Bool
`T.isPrefixOf` Text
t Bool -> Bool -> Bool
&& Text
"-->" Text -> Text -> Bool
`T.isSuffixOf` Text
t)
isVisibleBlock Block
_ = Bool
True