{-# LANGUAGE FlexibleInstances, MultiParamTypeClasses, DeriveDataTypeable,
GeneralizedNewtypeDeriving, CPP, StandaloneDeriving, DeriveGeneric,
DeriveTraversable, OverloadedStrings, PatternGuards #-}
module Text.Pandoc.Builder ( module Text.Pandoc.Definition
, Many(..)
, Inlines
, Blocks
, (<>)
, singleton
, toList
, fromList
, isNull
, doc
, ToMetaValue(..)
, HasMeta(..)
, setTitle
, setAuthors
, setDate
, text
, str
, emph
, underline
, strong
, strikeout
, superscript
, subscript
, smallcaps
, singleQuoted
, doubleQuoted
, cite
, codeWith
, code
, space
, softbreak
, linebreak
, math
, displayMath
, rawInline
, link
, linkWith
, image
, imageWith
, note
, spanWith
, trimInlines
, para
, plain
, lineBlock
, codeBlockWith
, codeBlock
, rawBlock
, blockQuote
, bulletList
, orderedListWith
, orderedList
, definitionList
, header
, headerWith
, horizontalRule
, cell
, simpleCell
, emptyCell
, cellWith
, table
, simpleTable
, tableWith
, caption
, simpleCaption
, emptyCaption
, divWith
, normalizeTableHead
, normalizeTableBody
, normalizeTableFoot
, placeRowSection
, clipRows
)
where
import Text.Pandoc.Definition
import Data.String
import qualified Data.Map as M
import Data.Text (Text)
import qualified Data.Text as T
import Data.Sequence (Seq, (|>), viewr, viewl, ViewR(..), ViewL(..))
import qualified Data.Sequence as Seq
import Data.Traversable (Traversable)
import Data.Foldable (Foldable)
import qualified Data.Foldable as F
import Data.Data
import Control.Arrow ((***))
import GHC.Generics (Generic)
import Data.Semigroup (Semigroup(..))
newtype Many a = Many { unMany :: Seq a }
deriving (Data, Ord, Eq, Typeable, Foldable, Traversable, Functor, Show, Read)
deriving instance Generic (Many a)
toList :: Many a -> [a]
toList = F.toList
singleton :: a -> Many a
singleton = Many . Seq.singleton
fromList :: [a] -> Many a
fromList = Many . Seq.fromList
isNull :: Many a -> Bool
isNull = Seq.null . unMany
type Inlines = Many Inline
type Blocks = Many Block
deriving instance Semigroup Blocks
deriving instance Monoid Blocks
instance Semigroup Inlines where
(Many xs) <> (Many ys) =
case (viewr xs, viewl ys) of
(EmptyR, _) -> Many ys
(_, EmptyL) -> Many xs
(xs' :> x, y :< ys') -> Many (meld <> ys')
where meld = case (x, y) of
(Space, Space) -> xs' |> Space
(Space, SoftBreak) -> xs' |> SoftBreak
(SoftBreak, Space) -> xs' |> SoftBreak
(Str t1, Str t2) -> xs' |> Str (t1 <> t2)
(Emph i1, Emph i2) -> xs' |> Emph (i1 <> i2)
(Underline i1, Underline i2) -> xs' |> Underline (i1 <> i2)
(Strong i1, Strong i2) -> xs' |> Strong (i1 <> i2)
(Subscript i1, Subscript i2) -> xs' |> Subscript (i1 <> i2)
(Superscript i1, Superscript i2) -> xs' |> Superscript (i1 <> i2)
(Strikeout i1, Strikeout i2) -> xs' |> Strikeout (i1 <> i2)
(Space, LineBreak) -> xs' |> LineBreak
(LineBreak, Space) -> xs' |> LineBreak
(SoftBreak, LineBreak) -> xs' |> LineBreak
(LineBreak, SoftBreak) -> xs' |> LineBreak
(SoftBreak, SoftBreak) -> xs' |> SoftBreak
_ -> xs' |> x |> y
instance Monoid Inlines where
mempty = Many mempty
mappend = (<>)
instance IsString Inlines where
fromString = text . T.pack
trimInlines :: Inlines -> Inlines
#if MIN_VERSION_containers(0,4,0)
trimInlines (Many ils) = Many $ Seq.dropWhileL isSp $
Seq.dropWhileR isSp $ ils
#else
trimInlines (Many ils) = Many $ Seq.dropWhileL isSp $
Seq.reverse $ Seq.dropWhileL isSp $
Seq.reverse ils
#endif
where isSp Space = True
isSp SoftBreak = True
isSp _ = False
doc :: Blocks -> Pandoc
doc = Pandoc nullMeta . toList
class ToMetaValue a where
toMetaValue :: a -> MetaValue
instance ToMetaValue MetaValue where
toMetaValue = id
instance ToMetaValue Blocks where
toMetaValue = MetaBlocks . toList
instance ToMetaValue Inlines where
toMetaValue = MetaInlines . toList
instance ToMetaValue Bool where
toMetaValue = MetaBool
instance ToMetaValue Text where
toMetaValue = MetaString
instance {-# OVERLAPPING #-} ToMetaValue String where
toMetaValue = MetaString . T.pack
instance ToMetaValue a => ToMetaValue [a] where
toMetaValue = MetaList . map toMetaValue
instance ToMetaValue a => ToMetaValue (M.Map Text a) where
toMetaValue = MetaMap . M.map toMetaValue
instance ToMetaValue a => ToMetaValue (M.Map String a) where
toMetaValue = MetaMap . M.map toMetaValue . M.mapKeys T.pack
class HasMeta a where
setMeta :: ToMetaValue b => Text -> b -> a -> a
deleteMeta :: Text -> a -> a
instance HasMeta Meta where
setMeta key val (Meta ms) = Meta $ M.insert key (toMetaValue val) ms
deleteMeta key (Meta ms) = Meta $ M.delete key ms
instance HasMeta Pandoc where
setMeta key val (Pandoc (Meta ms) bs) =
Pandoc (Meta $ M.insert key (toMetaValue val) ms) bs
deleteMeta key (Pandoc (Meta ms) bs) =
Pandoc (Meta $ M.delete key ms) bs
setTitle :: Inlines -> Pandoc -> Pandoc
setTitle = setMeta "title"
setAuthors :: [Inlines] -> Pandoc -> Pandoc
setAuthors = setMeta "author"
setDate :: Inlines -> Pandoc -> Pandoc
setDate = setMeta "date"
text :: Text -> Inlines
text = fromList . map conv . breakBySpaces
where breakBySpaces = T.groupBy sameCategory
sameCategory x y = is_space x == is_space y
conv xs | T.all is_space xs =
if T.any is_newline xs
then SoftBreak
else Space
conv xs = Str xs
is_space ' ' = True
is_space '\r' = True
is_space '\n' = True
is_space '\t' = True
is_space _ = False
is_newline '\r' = True
is_newline '\n' = True
is_newline _ = False
str :: Text -> Inlines
str = singleton . Str
emph :: Inlines -> Inlines
emph = singleton . Emph . toList
underline :: Inlines -> Inlines
underline = singleton . Underline . toList
strong :: Inlines -> Inlines
strong = singleton . Strong . toList
strikeout :: Inlines -> Inlines
strikeout = singleton . Strikeout . toList
superscript :: Inlines -> Inlines
superscript = singleton . Superscript . toList
subscript :: Inlines -> Inlines
subscript = singleton . Subscript . toList
smallcaps :: Inlines -> Inlines
smallcaps = singleton . SmallCaps . toList
singleQuoted :: Inlines -> Inlines
singleQuoted = quoted SingleQuote
doubleQuoted :: Inlines -> Inlines
doubleQuoted = quoted DoubleQuote
quoted :: QuoteType -> Inlines -> Inlines
quoted qt = singleton . Quoted qt . toList
cite :: [Citation] -> Inlines -> Inlines
cite cts = singleton . Cite cts . toList
codeWith :: Attr -> Text -> Inlines
codeWith attrs = singleton . Code attrs
code :: Text -> Inlines
code = codeWith nullAttr
space :: Inlines
space = singleton Space
softbreak :: Inlines
softbreak = singleton SoftBreak
linebreak :: Inlines
linebreak = singleton LineBreak
math :: Text -> Inlines
math = singleton . Math InlineMath
displayMath :: Text -> Inlines
displayMath = singleton . Math DisplayMath
rawInline :: Text -> Text -> Inlines
rawInline format = singleton . RawInline (Format format)
link :: Text
-> Text
-> Inlines
-> Inlines
link = linkWith nullAttr
linkWith :: Attr
-> Text
-> Text
-> Inlines
-> Inlines
linkWith attr url title x = singleton $ Link attr (toList x) (url, title)
image :: Text
-> Text
-> Inlines
-> Inlines
image = imageWith nullAttr
imageWith :: Attr
-> Text
-> Text
-> Inlines
-> Inlines
imageWith attr url title x = singleton $ Image attr (toList x) (url, title)
note :: Blocks -> Inlines
note = singleton . Note . toList
spanWith :: Attr -> Inlines -> Inlines
spanWith attr = singleton . Span attr . toList
para :: Inlines -> Blocks
para = singleton . Para . toList
plain :: Inlines -> Blocks
plain ils = if isNull ils
then mempty
else singleton . Plain . toList $ ils
lineBlock :: [Inlines] -> Blocks
lineBlock = singleton . LineBlock . map toList
codeBlockWith :: Attr -> Text -> Blocks
codeBlockWith attrs = singleton . CodeBlock attrs
codeBlock :: Text -> Blocks
codeBlock = codeBlockWith nullAttr
rawBlock :: Text -> Text -> Blocks
rawBlock format = singleton . RawBlock (Format format)
blockQuote :: Blocks -> Blocks
blockQuote = singleton . BlockQuote . toList
orderedListWith :: ListAttributes -> [Blocks] -> Blocks
orderedListWith attrs = singleton . OrderedList attrs . map toList
orderedList :: [Blocks] -> Blocks
orderedList = orderedListWith (1, DefaultStyle, DefaultDelim)
bulletList :: [Blocks] -> Blocks
bulletList = singleton . BulletList . map toList
definitionList :: [(Inlines, [Blocks])] -> Blocks
definitionList = singleton . DefinitionList . map (toList *** map toList)
header :: Int
-> Inlines
-> Blocks
header = headerWith nullAttr
headerWith :: Attr -> Int -> Inlines -> Blocks
headerWith attr level = singleton . Header level attr . toList
horizontalRule :: Blocks
horizontalRule = singleton HorizontalRule
cellWith :: Attr
-> Alignment
-> RowSpan
-> ColSpan
-> Blocks
-> Cell
cellWith at a r c = Cell at a r c . toList
cell :: Alignment
-> RowSpan
-> ColSpan
-> Blocks
-> Cell
cell = cellWith nullAttr
simpleCell :: Blocks -> Cell
simpleCell = cell AlignDefault 1 1
emptyCell :: Cell
emptyCell = simpleCell mempty
table :: Caption
-> [ColSpec]
-> TableHead
-> [TableBody]
-> TableFoot
-> Blocks
table = tableWith nullAttr
tableWith :: Attr
-> Caption
-> [ColSpec]
-> TableHead
-> [TableBody]
-> TableFoot
-> Blocks
tableWith attr capt specs th tbs tf
= singleton $ Table attr capt specs th' tbs' tf'
where
twidth = length specs
th' = normalizeTableHead twidth th
tbs' = map (normalizeTableBody twidth) tbs
tf' = normalizeTableFoot twidth tf
simpleTable :: [Blocks]
-> [[Blocks]]
-> Blocks
simpleTable headers rows =
table emptyCaption (replicate numcols defaults) th [tb] tf
where defaults = (AlignDefault, ColWidthDefault)
numcols = case headers:rows of
[] -> 0
xs -> maximum (map length xs)
toRow = Row nullAttr . map simpleCell
toHeaderRow l
| null l = []
| otherwise = [toRow headers]
th = TableHead nullAttr (toHeaderRow headers)
tb = TableBody nullAttr 0 [] $ map toRow rows
tf = TableFoot nullAttr []
caption :: Maybe ShortCaption -> Blocks -> Caption
caption x = Caption x . toList
simpleCaption :: Blocks -> Caption
simpleCaption = caption Nothing
emptyCaption :: Caption
emptyCaption = simpleCaption mempty
divWith :: Attr -> Blocks -> Blocks
divWith attr = singleton . Div attr . toList
normalizeTableHead :: Int -> TableHead -> TableHead
normalizeTableHead twidth (TableHead attr rows)
= TableHead attr $ normalizeHeaderSection twidth rows
normalizeTableBody :: Int -> TableBody -> TableBody
normalizeTableBody twidth (TableBody attr rhc th tb)
= TableBody attr rhc' (normBody th) (normBody tb)
where
rhc' = max 0 $ min (RowHeadColumns twidth) rhc
normBody = normalizeBodySection twidth rhc'
normalizeTableFoot :: Int -> TableFoot -> TableFoot
normalizeTableFoot twidth (TableFoot attr rows)
= TableFoot attr $ normalizeHeaderSection twidth rows
normalizeHeaderSection :: Int
-> [Row]
-> [Row]
normalizeHeaderSection twidth rows
= normalizeRows' (replicate twidth 1) $ clipRows rows
where
normalizeRows' oldHang (Row attr cells:rs)
= let (newHang, cells', _) = placeRowSection oldHang $ cells <> repeat emptyCell
rs' = normalizeRows' newHang rs
in Row attr cells' : rs'
normalizeRows' _ [] = []
normalizeBodySection :: Int
-> RowHeadColumns
-> [Row]
-> [Row]
normalizeBodySection twidth (RowHeadColumns rhc) rows
= normalizeRows' (replicate rhc 1) (replicate rbc 1) $ clipRows rows
where
rbc = twidth - rhc
normalizeRows' headHang bodyHang (Row attr cells:rs)
= let (headHang', rowHead, cells') = placeRowSection headHang $ cells <> repeat emptyCell
(bodyHang', rowBody, _) = placeRowSection bodyHang cells'
rs' = normalizeRows' headHang' bodyHang' rs
in Row attr (rowHead <> rowBody) : rs'
normalizeRows' _ _ [] = []
placeRowSection :: [RowSpan]
-> [Cell]
-> ([RowSpan], [Cell], [Cell])
placeRowSection oldHang cellStream
| o:os <- oldHang
, o > 1 = let (newHang, newCell, cellStream') = placeRowSection os cellStream
in (o - 1 : newHang, newCell, cellStream')
| c:cellStream' <- cellStream
, (h, w) <- getDim c
, w' <- max 1 w
, (n, oldHang') <- dropAtMostWhile (== 1) (getColSpan w') oldHang
, n > 0
= let w'' = min (ColSpan n) w'
c' = setW w'' c
(newHang, newCell, remainCell) = placeRowSection oldHang' cellStream'
in (replicate (getColSpan w'') h <> newHang, c' : newCell, remainCell)
| otherwise = ([], [], cellStream)
where
getColSpan (ColSpan w) = w
getDim (Cell _ _ h w _) = (h, w)
setW w (Cell a ma h _ b) = Cell a ma h w b
dropAtMostWhile :: (a -> Bool) -> Int -> [a] -> (Int, [a])
dropAtMostWhile p n = go 0
where
go acc (l:ls) | p l && acc < n = go (acc+1) ls
go acc l = (acc, l)
clipRows :: [Row] -> [Row]
clipRows rows
= let totalHeight = RowSpan $ length rows
in zipWith clipRowH [totalHeight, totalHeight - 1..1] rows
where
getH (Cell _ _ h _ _) = h
setH h (Cell a ma _ w body) = Cell a ma h w body
clipH low high c = let h = getH c in setH (min high $ max low h) c
clipRowH high (Row attr cells) = Row attr $ map (clipH 1 high) cells