{-# LANGUAGE Rank2Types, OverloadedStrings, FlexibleContexts, MultiWayIf #-}
module Text.Pandoc.CrossRef.References.Blocks.CodeBlock where
import Control.Monad.Reader.Class
import qualified Data.Text as T
import Text.Pandoc.Definition
import Text.Pandoc.Shared (stringify)
import qualified Text.Pandoc.Builder as B
import Data.Function ((&))
import Text.Pandoc.CrossRef.References.Monad
import Text.Pandoc.CrossRef.References.Blocks.Util
import Text.Pandoc.CrossRef.Util.Options
import Text.Pandoc.CrossRef.Util.Template
import Text.Pandoc.CrossRef.Util.Util
runCodeBlock :: Attr -> T.Text -> Either T.Text [Inline] -> WS (ReplacedResult Block)
runCodeBlock :: Attr -> Text -> Either Text [Inline] -> WS (ReplacedResult Block)
runCodeBlock (Text
label, [Text]
classes, [(Text, Text)]
attrs) Text
code Either Text [Inline]
eCaption = do
Options
opts <- WS Options
forall r (m :: * -> *). MonadReader r m => m r
ask
if | Options -> Bool
isLatexFormat Options
opts, Options -> Bool
listings Options
opts ->
Either Text [Inline]
eCaption Either Text [Inline]
-> (Either Text [Inline] -> WS (ReplacedResult Block))
-> WS (ReplacedResult Block)
forall a b. a -> (a -> b) -> b
& (Text -> WS (ReplacedResult Block))
-> ([Inline] -> WS (ReplacedResult Block))
-> Either Text [Inline]
-> WS (ReplacedResult Block)
forall a c b. (a -> c) -> (b -> c) -> Either a b -> c
either
(WS (ReplacedResult Block) -> Text -> WS (ReplacedResult Block)
forall a b. a -> b -> a
const WS (ReplacedResult Block)
forall (m :: * -> *) a. Monad m => m (ReplacedResult a)
noReplaceNoRecurse)
(\[Inline]
caption -> Block -> WS (ReplacedResult Block)
forall (m :: * -> *) a. Monad m => a -> m (ReplacedResult a)
replaceNoRecurse (Block -> WS (ReplacedResult Block))
-> Block -> WS (ReplacedResult Block)
forall a b. (a -> b) -> a -> b
$
Attr -> Text -> Block
CodeBlock (Text
label,[Text]
classes,(Text
"caption",Text -> Text
escapeLaTeX (Text -> Text) -> Text -> Text
forall a b. (a -> b) -> a -> b
$ [Inline] -> Text
forall a. Walkable Inline a => a -> Text
stringify [Inline]
caption)(Text, Text) -> [(Text, Text)] -> [(Text, Text)]
forall a. a -> [a] -> [a]
:[(Text, Text)]
attrs) Text
code)
| Options -> Bool
isLatexFormat Options
opts ->
Block -> WS (ReplacedResult Block)
forall (m :: * -> *) a. Monad m => a -> m (ReplacedResult a)
replaceNoRecurse (Block -> WS (ReplacedResult Block))
-> Block -> WS (ReplacedResult Block)
forall a b. (a -> b) -> a -> b
$ Attr -> [Block] -> Block
Div Attr
nullAttr [
Format -> Text -> Block
RawBlock (Text -> Format
Format Text
"latex") (Text -> Block) -> Text -> Block
forall a b. (a -> b) -> a -> b
$ Text
"\\begin{codelisting}"
, [Inline] -> Block
Plain [
Format -> Text -> Inline
RawInline (Text -> Format
Format Text
"latex") Text
"\\caption"
, Attr -> [Inline] -> Inline
Span Attr
nullAttr ([Inline] -> Inline) -> [Inline] -> Inline
forall a b. (a -> b) -> a -> b
$ (Text -> [Inline])
-> ([Inline] -> [Inline]) -> Either Text [Inline] -> [Inline]
forall a c b. (a -> c) -> (b -> c) -> Either a b -> c
either (Inline -> [Inline]
forall a. a -> [a]
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Inline -> [Inline]) -> (Text -> Inline) -> Text -> [Inline]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> Inline
Str) [Inline] -> [Inline]
forall a. a -> a
id Either Text [Inline]
eCaption
, Format -> Text -> Inline
RawInline (Text -> Format
Format Text
"latex") (Text -> Inline) -> Text -> Inline
forall a b. (a -> b) -> a -> b
$ Text -> Text
mkLaTeXLabel Text
label
]
, Attr -> Text -> Block
CodeBlock (Text
"", [Text]
classes, [(Text, Text)]
attrs) Text
code
, Format -> Text -> Block
RawBlock (Text -> Format
Format Text
"latex") Text
"\\end{codelisting}"
]
| Bool
otherwise -> do
let cap :: [Inline]
cap = (Text -> [Inline])
-> ([Inline] -> [Inline]) -> Either Text [Inline] -> [Inline]
forall a c b. (a -> c) -> (b -> c) -> Either a b -> c
either (Many Inline -> [Inline]
forall a. Many a -> [a]
B.toList (Many Inline -> [Inline])
-> (Text -> Many Inline) -> Text -> [Inline]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> Many Inline
B.text) [Inline] -> [Inline]
forall a. a -> a
id Either Text [Inline]
eCaption
[Inline]
idxStr <- Either Text Text
-> [(Text, Text)] -> [Inline] -> SPrefix -> WS [Inline]
replaceAttr (Text -> Either Text Text
forall a b. b -> Either a b
Right Text
label) [(Text, Text)]
attrs [Inline]
cap SPrefix
SPfxLst
let caption' :: [Inline]
caption' = [Inline] -> [Inline] -> Template -> [Inline]
forall a b. MkTemplate a b => [Inline] -> [Inline] -> b -> [a]
applyTemplate [Inline]
idxStr [Inline]
cap (Template -> [Inline]) -> Template -> [Inline]
forall a b. (a -> b) -> a -> b
$ Options -> Template
listingTemplate Options
opts
Block -> WS (ReplacedResult Block)
forall (m :: * -> *) a. Monad m => a -> m (ReplacedResult a)
replaceNoRecurse (Block -> WS (ReplacedResult Block))
-> Block -> WS (ReplacedResult Block)
forall a b. (a -> b) -> a -> b
$ Attr -> [Block] -> Block
Div (Text
label, Text
"listing"Text -> [Text] -> [Text]
forall a. a -> [a] -> [a]
:[Text]
classes, []) [
Options -> Text -> [Inline] -> Block
mkCaption Options
opts Text
"Caption" [Inline]
caption'
, Attr -> Text -> Block
CodeBlock (Text
"", [Text]
classes, ((Text, Text) -> Bool) -> [(Text, Text)] -> [(Text, Text)]
forall a. (a -> Bool) -> [a] -> [a]
filter ((Text -> Text -> Bool
forall a. Eq a => a -> a -> Bool
/=Text
"caption") (Text -> Bool) -> ((Text, Text) -> Text) -> (Text, Text) -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Text, Text) -> Text
forall a b. (a, b) -> a
fst) ([(Text, Text)] -> [(Text, Text)])
-> [(Text, Text)] -> [(Text, Text)]
forall a b. (a -> b) -> a -> b
$ Options -> [Inline] -> [(Text, Text)] -> [(Text, Text)]
setLabel Options
opts [Inline]
idxStr [(Text, Text)]
attrs) Text
code
]