{-# LANGUAGE FlexibleInstances, MultiParamTypeClasses, DeriveDataTypeable,
    GeneralizedNewtypeDeriving, CPP, StandaloneDeriving, DeriveGeneric,
    DeriveTraversable, OverloadedStrings, PatternGuards #-}

{-
Copyright (C) 2010-2019 John MacFarlane

All rights reserved.

Redistribution and use in source and binary forms, with or without
modification, are permitted provided that the following conditions are met:

    * Redistributions of source code must retain the above copyright
      notice, this list of conditions and the following disclaimer.

    * Redistributions in binary form must reproduce the above
      copyright notice, this list of conditions and the following
      disclaimer in the documentation and/or other materials provided
      with the distribution.

    * Neither the name of John MacFarlane nor the names of other
      contributors may be used to endorse or promote products derived
      from this software without specific prior written permission.

THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS
"AS IS" AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT
LIMITED TO, THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS FOR
A PARTICULAR PURPOSE ARE DISCLAIMED. IN NO EVENT SHALL THE COPYRIGHT
OWNER OR CONTRIBUTORS BE LIABLE FOR ANY DIRECT, INDIRECT, INCIDENTAL,
SPECIAL, EXEMPLARY, OR CONSEQUENTIAL DAMAGES (INCLUDING, BUT NOT
LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS OR SERVICES; LOSS OF USE,
DATA, OR PROFITS; OR BUSINESS INTERRUPTION) HOWEVER CAUSED AND ON ANY
THEORY OF LIABILITY, WHETHER IN CONTRACT, STRICT LIABILITY, OR TORT
(INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN ANY WAY OUT OF THE USE
OF THIS SOFTWARE, EVEN IF ADVISED OF THE POSSIBILITY OF SUCH DAMAGE.
-}

{- |
   Module      : Text.Pandoc.Builder
   Copyright   : Copyright (C) 2010-2019 John MacFarlane
   License     : BSD3

   Maintainer  : John MacFarlane <jgm@berkeley.edu>
   Stability   : alpha
   Portability : portable

Convenience functions for building pandoc documents programmatically.

Example of use (with @OverloadedStrings@ pragma):

> import Text.Pandoc.Builder
>
> myDoc :: Pandoc
> myDoc = setTitle "My title" $ doc $
>   para "This is the first paragraph" <>
>   para ("And " <> emph "another" <> ".") <>
>   bulletList [ para "item one" <> para "continuation"
>              , plain ("item two and a " <>
>                  link "/url" "go to url" "link")
>              ]

Isn't that nicer than writing the following?

> import Text.Pandoc.Definition
> import Data.Map (fromList)
>
> myDoc :: Pandoc
> myDoc = Pandoc (Meta {unMeta = fromList [("title",
>           MetaInlines [Str "My",Space,Str "title"])]})
>         [Para [Str "This",Space,Str "is",Space,Str "the",Space,Str "first",
>          Space,Str "paragraph"],Para [Str "And",Space,Emph [Str "another"],
>          Str "."]
>         ,BulletList [
>           [Para [Str "item",Space,Str "one"]
>           ,Para [Str "continuation"]]
>          ,[Plain [Str "item",Space,Str "two",Space,Str "and",Space,
>                   Str "a",Space,Link nullAttr [Str "link"] ("/url","go to url")]]]]

And of course, you can use Haskell to define your own builders:

> import Text.Pandoc.Builder
> import Text.JSON
> import Control.Arrow ((***))
> import Data.Monoid (mempty)
>
> -- | Converts a JSON document into 'Blocks'.
> json :: String -> Blocks
> json x =
>   case decode x of
>        Ok y    -> jsValueToBlocks y
>        Error y -> error y
>    where jsValueToBlocks x =
>           case x of
>            JSNull         -> mempty
>            JSBool x       -> plain $ text $ show x
>            JSRational _ x -> plain $ text $ show x
>            JSString x     -> plain $ text $ fromJSString x
>            JSArray xs     -> bulletList $ map jsValueToBlocks xs
>            JSObject x     -> definitionList $
>                               map (text *** (:[]) . jsValueToBlocks) $
>                               fromJSObject x

-}

module Text.Pandoc.Builder ( module Text.Pandoc.Definition
                           , Many(..)
                           , Inlines
                           , Blocks
                           , (<>)
                           , singleton
                           , toList
                           , fromList
                           , isNull
                           -- * Document builders
                           , doc
                           , ToMetaValue(..)
                           , HasMeta(..)
                           , setTitle
                           , setAuthors
                           , setDate
                           -- * Inline list builders
                           , 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
                           -- * Block list builders
                           , para
                           , plain
                           , lineBlock
                           , codeBlockWith
                           , codeBlock
                           , rawBlock
                           , blockQuote
                           , bulletList
                           , orderedListWith
                           , orderedList
                           , definitionList
                           , header
                           , headerWith
                           , horizontalRule
                           , cell
                           , simpleCell
                           , emptyCell
                           , cellWith
                           , table
                           , simpleTable
                           , tableWith
                           , caption
                           , simpleCaption
                           , emptyCaption
                           , simpleFigureWith
                           , simpleFigure
                           , divWith
                           -- * Table processing
                           , 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 { Many a -> Seq a
unMany :: Seq a }
                 deriving (Typeable (Many a)
DataType
Constr
Typeable (Many a) =>
(forall (c :: * -> *).
 (forall d b. Data d => c (d -> b) -> d -> c b)
 -> (forall g. g -> c g) -> Many a -> c (Many a))
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c (Many a))
-> (Many a -> Constr)
-> (Many a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
    Typeable t =>
    (forall d. Data d => c (t d)) -> Maybe (c (Many a)))
-> (forall (t :: * -> * -> *) (c :: * -> *).
    Typeable t =>
    (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Many a)))
-> ((forall b. Data b => b -> b) -> Many a -> Many a)
-> (forall r r'.
    (r -> r' -> r)
    -> r -> (forall d. Data d => d -> r') -> Many a -> r)
-> (forall r r'.
    (r' -> r -> r)
    -> r -> (forall d. Data d => d -> r') -> Many a -> r)
-> (forall u. (forall d. Data d => d -> u) -> Many a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> Many a -> u)
-> (forall (m :: * -> *).
    Monad m =>
    (forall d. Data d => d -> m d) -> Many a -> m (Many a))
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> Many a -> m (Many a))
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> Many a -> m (Many a))
-> Data (Many a)
Many a -> DataType
Many a -> Constr
(forall d. Data d => c (t d)) -> Maybe (c (Many a))
(forall b. Data b => b -> b) -> Many a -> Many a
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Many a -> c (Many a)
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (Many a)
forall a. Data a => Typeable (Many a)
forall a. Data a => Many a -> DataType
forall a. Data a => Many a -> Constr
forall a.
Data a =>
(forall b. Data b => b -> b) -> Many a -> Many a
forall a u.
Data a =>
Int -> (forall d. Data d => d -> u) -> Many a -> u
forall a u. Data a => (forall d. Data d => d -> u) -> Many a -> [u]
forall a r r'.
Data a =>
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Many a -> r
forall a r r'.
Data a =>
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Many a -> r
forall a (m :: * -> *).
(Data a, Monad m) =>
(forall d. Data d => d -> m d) -> Many a -> m (Many a)
forall a (m :: * -> *).
(Data a, MonadPlus m) =>
(forall d. Data d => d -> m d) -> Many a -> m (Many a)
forall a (c :: * -> *).
Data a =>
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (Many a)
forall a (c :: * -> *).
Data a =>
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Many a -> c (Many a)
forall a (t :: * -> *) (c :: * -> *).
(Data a, Typeable t) =>
(forall d. Data d => c (t d)) -> Maybe (c (Many a))
forall a (t :: * -> * -> *) (c :: * -> *).
(Data a, Typeable t) =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Many a))
forall a.
Typeable a =>
(forall (c :: * -> *).
 (forall d b. Data d => c (d -> b) -> d -> c b)
 -> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
    Typeable t =>
    (forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
    Typeable t =>
    (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
    (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
    (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
    Monad m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u. Int -> (forall d. Data d => d -> u) -> Many a -> u
forall u. (forall d. Data d => d -> u) -> Many a -> [u]
forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Many a -> r
forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Many a -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Many a -> m (Many a)
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Many a -> m (Many a)
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (Many a)
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Many a -> c (Many a)
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c (Many a))
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Many a))
$cMany :: Constr
$tMany :: DataType
gmapMo :: (forall d. Data d => d -> m d) -> Many a -> m (Many a)
$cgmapMo :: forall a (m :: * -> *).
(Data a, MonadPlus m) =>
(forall d. Data d => d -> m d) -> Many a -> m (Many a)
gmapMp :: (forall d. Data d => d -> m d) -> Many a -> m (Many a)
$cgmapMp :: forall a (m :: * -> *).
(Data a, MonadPlus m) =>
(forall d. Data d => d -> m d) -> Many a -> m (Many a)
gmapM :: (forall d. Data d => d -> m d) -> Many a -> m (Many a)
$cgmapM :: forall a (m :: * -> *).
(Data a, Monad m) =>
(forall d. Data d => d -> m d) -> Many a -> m (Many a)
gmapQi :: Int -> (forall d. Data d => d -> u) -> Many a -> u
$cgmapQi :: forall a u.
Data a =>
Int -> (forall d. Data d => d -> u) -> Many a -> u
gmapQ :: (forall d. Data d => d -> u) -> Many a -> [u]
$cgmapQ :: forall a u. Data a => (forall d. Data d => d -> u) -> Many a -> [u]
gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Many a -> r
$cgmapQr :: forall a r r'.
Data a =>
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Many a -> r
gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Many a -> r
$cgmapQl :: forall a r r'.
Data a =>
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Many a -> r
gmapT :: (forall b. Data b => b -> b) -> Many a -> Many a
$cgmapT :: forall a.
Data a =>
(forall b. Data b => b -> b) -> Many a -> Many a
dataCast2 :: (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Many a))
$cdataCast2 :: forall a (t :: * -> * -> *) (c :: * -> *).
(Data a, Typeable t) =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Many a))
dataCast1 :: (forall d. Data d => c (t d)) -> Maybe (c (Many a))
$cdataCast1 :: forall a (t :: * -> *) (c :: * -> *).
(Data a, Typeable t) =>
(forall d. Data d => c (t d)) -> Maybe (c (Many a))
dataTypeOf :: Many a -> DataType
$cdataTypeOf :: forall a. Data a => Many a -> DataType
toConstr :: Many a -> Constr
$ctoConstr :: forall a. Data a => Many a -> Constr
gunfold :: (forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (Many a)
$cgunfold :: forall a (c :: * -> *).
Data a =>
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (Many a)
gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Many a -> c (Many a)
$cgfoldl :: forall a (c :: * -> *).
Data a =>
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Many a -> c (Many a)
$cp1Data :: forall a. Data a => Typeable (Many a)
Data, Eq (Many a)
Eq (Many a) =>
(Many a -> Many a -> Ordering)
-> (Many a -> Many a -> Bool)
-> (Many a -> Many a -> Bool)
-> (Many a -> Many a -> Bool)
-> (Many a -> Many a -> Bool)
-> (Many a -> Many a -> Many a)
-> (Many a -> Many a -> Many a)
-> Ord (Many a)
Many a -> Many a -> Bool
Many a -> Many a -> Ordering
Many a -> Many a -> Many a
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
forall a. Ord a => Eq (Many a)
forall a. Ord a => Many a -> Many a -> Bool
forall a. Ord a => Many a -> Many a -> Ordering
forall a. Ord a => Many a -> Many a -> Many a
min :: Many a -> Many a -> Many a
$cmin :: forall a. Ord a => Many a -> Many a -> Many a
max :: Many a -> Many a -> Many a
$cmax :: forall a. Ord a => Many a -> Many a -> Many a
>= :: Many a -> Many a -> Bool
$c>= :: forall a. Ord a => Many a -> Many a -> Bool
> :: Many a -> Many a -> Bool
$c> :: forall a. Ord a => Many a -> Many a -> Bool
<= :: Many a -> Many a -> Bool
$c<= :: forall a. Ord a => Many a -> Many a -> Bool
< :: Many a -> Many a -> Bool
$c< :: forall a. Ord a => Many a -> Many a -> Bool
compare :: Many a -> Many a -> Ordering
$ccompare :: forall a. Ord a => Many a -> Many a -> Ordering
$cp1Ord :: forall a. Ord a => Eq (Many a)
Ord, Many a -> Many a -> Bool
(Many a -> Many a -> Bool)
-> (Many a -> Many a -> Bool) -> Eq (Many a)
forall a. Eq a => Many a -> Many a -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Many a -> Many a -> Bool
$c/= :: forall a. Eq a => Many a -> Many a -> Bool
== :: Many a -> Many a -> Bool
$c== :: forall a. Eq a => Many a -> Many a -> Bool
Eq, Typeable, a -> Many a -> Bool
Many m -> m
Many a -> [a]
Many a -> Bool
Many a -> Int
Many a -> a
Many a -> a
Many a -> a
Many a -> a
(a -> m) -> Many a -> m
(a -> m) -> Many a -> m
(a -> b -> b) -> b -> Many a -> b
(a -> b -> b) -> b -> Many a -> b
(b -> a -> b) -> b -> Many a -> b
(b -> a -> b) -> b -> Many a -> b
(a -> a -> a) -> Many a -> a
(a -> a -> a) -> Many a -> a
(forall m. Monoid m => Many m -> m)
-> (forall m a. Monoid m => (a -> m) -> Many a -> m)
-> (forall m a. Monoid m => (a -> m) -> Many a -> m)
-> (forall a b. (a -> b -> b) -> b -> Many a -> b)
-> (forall a b. (a -> b -> b) -> b -> Many a -> b)
-> (forall b a. (b -> a -> b) -> b -> Many a -> b)
-> (forall b a. (b -> a -> b) -> b -> Many a -> b)
-> (forall a. (a -> a -> a) -> Many a -> a)
-> (forall a. (a -> a -> a) -> Many a -> a)
-> (forall a. Many a -> [a])
-> (forall a. Many a -> Bool)
-> (forall a. Many a -> Int)
-> (forall a. Eq a => a -> Many a -> Bool)
-> (forall a. Ord a => Many a -> a)
-> (forall a. Ord a => Many a -> a)
-> (forall a. Num a => Many a -> a)
-> (forall a. Num a => Many a -> a)
-> Foldable Many
forall a. Eq a => a -> Many a -> Bool
forall a. Num a => Many a -> a
forall a. Ord a => Many a -> a
forall m. Monoid m => Many m -> m
forall a. Many a -> Bool
forall a. Many a -> Int
forall a. Many a -> [a]
forall a. (a -> a -> a) -> Many a -> a
forall m a. Monoid m => (a -> m) -> Many a -> m
forall b a. (b -> a -> b) -> b -> Many a -> b
forall a b. (a -> b -> b) -> b -> Many a -> b
forall (t :: * -> *).
(forall m. Monoid m => t m -> m)
-> (forall m a. Monoid m => (a -> m) -> t a -> m)
-> (forall m a. Monoid m => (a -> m) -> t a -> m)
-> (forall a b. (a -> b -> b) -> b -> t a -> b)
-> (forall a b. (a -> b -> b) -> b -> t a -> b)
-> (forall b a. (b -> a -> b) -> b -> t a -> b)
-> (forall b a. (b -> a -> b) -> b -> t a -> b)
-> (forall a. (a -> a -> a) -> t a -> a)
-> (forall a. (a -> a -> a) -> t a -> a)
-> (forall a. t a -> [a])
-> (forall a. t a -> Bool)
-> (forall a. t a -> Int)
-> (forall a. Eq a => a -> t a -> Bool)
-> (forall a. Ord a => t a -> a)
-> (forall a. Ord a => t a -> a)
-> (forall a. Num a => t a -> a)
-> (forall a. Num a => t a -> a)
-> Foldable t
product :: Many a -> a
$cproduct :: forall a. Num a => Many a -> a
sum :: Many a -> a
$csum :: forall a. Num a => Many a -> a
minimum :: Many a -> a
$cminimum :: forall a. Ord a => Many a -> a
maximum :: Many a -> a
$cmaximum :: forall a. Ord a => Many a -> a
elem :: a -> Many a -> Bool
$celem :: forall a. Eq a => a -> Many a -> Bool
length :: Many a -> Int
$clength :: forall a. Many a -> Int
null :: Many a -> Bool
$cnull :: forall a. Many a -> Bool
toList :: Many a -> [a]
$ctoList :: forall a. Many a -> [a]
foldl1 :: (a -> a -> a) -> Many a -> a
$cfoldl1 :: forall a. (a -> a -> a) -> Many a -> a
foldr1 :: (a -> a -> a) -> Many a -> a
$cfoldr1 :: forall a. (a -> a -> a) -> Many a -> a
foldl' :: (b -> a -> b) -> b -> Many a -> b
$cfoldl' :: forall b a. (b -> a -> b) -> b -> Many a -> b
foldl :: (b -> a -> b) -> b -> Many a -> b
$cfoldl :: forall b a. (b -> a -> b) -> b -> Many a -> b
foldr' :: (a -> b -> b) -> b -> Many a -> b
$cfoldr' :: forall a b. (a -> b -> b) -> b -> Many a -> b
foldr :: (a -> b -> b) -> b -> Many a -> b
$cfoldr :: forall a b. (a -> b -> b) -> b -> Many a -> b
foldMap' :: (a -> m) -> Many a -> m
$cfoldMap' :: forall m a. Monoid m => (a -> m) -> Many a -> m
foldMap :: (a -> m) -> Many a -> m
$cfoldMap :: forall m a. Monoid m => (a -> m) -> Many a -> m
fold :: Many m -> m
$cfold :: forall m. Monoid m => Many m -> m
Foldable, Functor Many
Foldable Many
(Functor Many, Foldable Many) =>
(forall (f :: * -> *) a b.
 Applicative f =>
 (a -> f b) -> Many a -> f (Many b))
-> (forall (f :: * -> *) a.
    Applicative f =>
    Many (f a) -> f (Many a))
-> (forall (m :: * -> *) a b.
    Monad m =>
    (a -> m b) -> Many a -> m (Many b))
-> (forall (m :: * -> *) a. Monad m => Many (m a) -> m (Many a))
-> Traversable Many
(a -> f b) -> Many a -> f (Many b)
forall (t :: * -> *).
(Functor t, Foldable t) =>
(forall (f :: * -> *) a b.
 Applicative f =>
 (a -> f b) -> t a -> f (t b))
-> (forall (f :: * -> *) a. Applicative f => t (f a) -> f (t a))
-> (forall (m :: * -> *) a b.
    Monad m =>
    (a -> m b) -> t a -> m (t b))
-> (forall (m :: * -> *) a. Monad m => t (m a) -> m (t a))
-> Traversable t
forall (m :: * -> *) a. Monad m => Many (m a) -> m (Many a)
forall (f :: * -> *) a. Applicative f => Many (f a) -> f (Many a)
forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> Many a -> m (Many b)
forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> Many a -> f (Many b)
sequence :: Many (m a) -> m (Many a)
$csequence :: forall (m :: * -> *) a. Monad m => Many (m a) -> m (Many a)
mapM :: (a -> m b) -> Many a -> m (Many b)
$cmapM :: forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> Many a -> m (Many b)
sequenceA :: Many (f a) -> f (Many a)
$csequenceA :: forall (f :: * -> *) a. Applicative f => Many (f a) -> f (Many a)
traverse :: (a -> f b) -> Many a -> f (Many b)
$ctraverse :: forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> Many a -> f (Many b)
$cp2Traversable :: Foldable Many
$cp1Traversable :: Functor Many
Traversable, a -> Many b -> Many a
(a -> b) -> Many a -> Many b
(forall a b. (a -> b) -> Many a -> Many b)
-> (forall a b. a -> Many b -> Many a) -> Functor Many
forall a b. a -> Many b -> Many a
forall a b. (a -> b) -> Many a -> Many b
forall (f :: * -> *).
(forall a b. (a -> b) -> f a -> f b)
-> (forall a b. a -> f b -> f a) -> Functor f
<$ :: a -> Many b -> Many a
$c<$ :: forall a b. a -> Many b -> Many a
fmap :: (a -> b) -> Many a -> Many b
$cfmap :: forall a b. (a -> b) -> Many a -> Many b
Functor, Int -> Many a -> ShowS
[Many a] -> ShowS
Many a -> String
(Int -> Many a -> ShowS)
-> (Many a -> String) -> ([Many a] -> ShowS) -> Show (Many a)
forall a. Show a => Int -> Many a -> ShowS
forall a. Show a => [Many a] -> ShowS
forall a. Show a => Many a -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Many a] -> ShowS
$cshowList :: forall a. Show a => [Many a] -> ShowS
show :: Many a -> String
$cshow :: forall a. Show a => Many a -> String
showsPrec :: Int -> Many a -> ShowS
$cshowsPrec :: forall a. Show a => Int -> Many a -> ShowS
Show, ReadPrec [Many a]
ReadPrec (Many a)
Int -> ReadS (Many a)
ReadS [Many a]
(Int -> ReadS (Many a))
-> ReadS [Many a]
-> ReadPrec (Many a)
-> ReadPrec [Many a]
-> Read (Many a)
forall a. Read a => ReadPrec [Many a]
forall a. Read a => ReadPrec (Many a)
forall a. Read a => Int -> ReadS (Many a)
forall a. Read a => ReadS [Many a]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [Many a]
$creadListPrec :: forall a. Read a => ReadPrec [Many a]
readPrec :: ReadPrec (Many a)
$creadPrec :: forall a. Read a => ReadPrec (Many a)
readList :: ReadS [Many a]
$creadList :: forall a. Read a => ReadS [Many a]
readsPrec :: Int -> ReadS (Many a)
$creadsPrec :: forall a. Read a => Int -> ReadS (Many a)
Read)

deriving instance Generic (Many a)

toList :: Many a -> [a]
toList :: Many a -> [a]
toList = Many a -> [a]
forall (t :: * -> *) a. Foldable t => t a -> [a]
F.toList

singleton :: a -> Many a
singleton :: a -> Many a
singleton = Seq a -> Many a
forall a. Seq a -> Many a
Many (Seq a -> Many a) -> (a -> Seq a) -> a -> Many a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. a -> Seq a
forall a. a -> Seq a
Seq.singleton

fromList :: [a] -> Many a
fromList :: [a] -> Many a
fromList = Seq a -> Many a
forall a. Seq a -> Many a
Many (Seq a -> Many a) -> ([a] -> Seq a) -> [a] -> Many a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [a] -> Seq a
forall a. [a] -> Seq a
Seq.fromList

{-# DEPRECATED isNull "Use null instead" #-}
isNull :: Many a -> Bool
isNull :: Many a -> Bool
isNull = Seq a -> Bool
forall a. Seq a -> Bool
Seq.null (Seq a -> Bool) -> (Many a -> Seq a) -> Many a -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Many a -> Seq a
forall a. Many a -> Seq a
unMany

type Inlines = Many Inline
type Blocks  = Many Block

deriving instance Semigroup Blocks
deriving instance Monoid Blocks

instance Semigroup Inlines where
  (Many xs :: Seq Inline
xs) <> :: Inlines -> Inlines -> Inlines
<> (Many ys :: Seq Inline
ys) =
    case (Seq Inline -> ViewR Inline
forall a. Seq a -> ViewR a
viewr Seq Inline
xs, Seq Inline -> ViewL Inline
forall a. Seq a -> ViewL a
viewl Seq Inline
ys) of
      (EmptyR, _) -> Seq Inline -> Inlines
forall a. Seq a -> Many a
Many Seq Inline
ys
      (_, EmptyL) -> Seq Inline -> Inlines
forall a. Seq a -> Many a
Many Seq Inline
xs
      (xs' :: Seq Inline
xs' :> x :: Inline
x, y :: Inline
y :< ys' :: Seq Inline
ys') -> Seq Inline -> Inlines
forall a. Seq a -> Many a
Many (Seq Inline
meld Seq Inline -> Seq Inline -> Seq Inline
forall a. Semigroup a => a -> a -> a
<> Seq Inline
ys')
        where meld :: Seq Inline
meld = case (Inline
x, Inline
y) of
                          (Space, Space)     -> Seq Inline
xs' Seq Inline -> Inline -> Seq Inline
forall a. Seq a -> a -> Seq a
|> Inline
Space
                          (Space, SoftBreak) -> Seq Inline
xs' Seq Inline -> Inline -> Seq Inline
forall a. Seq a -> a -> Seq a
|> Inline
SoftBreak
                          (SoftBreak, Space) -> Seq Inline
xs' Seq Inline -> Inline -> Seq Inline
forall a. Seq a -> a -> Seq a
|> Inline
SoftBreak
                          (Str t1 :: Text
t1, Str t2 :: Text
t2)   -> Seq Inline
xs' Seq Inline -> Inline -> Seq Inline
forall a. Seq a -> a -> Seq a
|> Text -> Inline
Str (Text
t1 Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
t2)
                          (Emph i1 :: [Inline]
i1, Emph i2 :: [Inline]
i2) -> Seq Inline
xs' Seq Inline -> Inline -> Seq Inline
forall a. Seq a -> a -> Seq a
|> [Inline] -> Inline
Emph ([Inline]
i1 [Inline] -> [Inline] -> [Inline]
forall a. Semigroup a => a -> a -> a
<> [Inline]
i2)
                          (Underline i1 :: [Inline]
i1, Underline i2 :: [Inline]
i2) -> Seq Inline
xs' Seq Inline -> Inline -> Seq Inline
forall a. Seq a -> a -> Seq a
|> [Inline] -> Inline
Underline ([Inline]
i1 [Inline] -> [Inline] -> [Inline]
forall a. Semigroup a => a -> a -> a
<> [Inline]
i2)
                          (Strong i1 :: [Inline]
i1, Strong i2 :: [Inline]
i2) -> Seq Inline
xs' Seq Inline -> Inline -> Seq Inline
forall a. Seq a -> a -> Seq a
|> [Inline] -> Inline
Strong ([Inline]
i1 [Inline] -> [Inline] -> [Inline]
forall a. Semigroup a => a -> a -> a
<> [Inline]
i2)
                          (Subscript i1 :: [Inline]
i1, Subscript i2 :: [Inline]
i2) -> Seq Inline
xs' Seq Inline -> Inline -> Seq Inline
forall a. Seq a -> a -> Seq a
|> [Inline] -> Inline
Subscript ([Inline]
i1 [Inline] -> [Inline] -> [Inline]
forall a. Semigroup a => a -> a -> a
<> [Inline]
i2)
                          (Superscript i1 :: [Inline]
i1, Superscript i2 :: [Inline]
i2) -> Seq Inline
xs' Seq Inline -> Inline -> Seq Inline
forall a. Seq a -> a -> Seq a
|> [Inline] -> Inline
Superscript ([Inline]
i1 [Inline] -> [Inline] -> [Inline]
forall a. Semigroup a => a -> a -> a
<> [Inline]
i2)
                          (Strikeout i1 :: [Inline]
i1, Strikeout i2 :: [Inline]
i2) -> Seq Inline
xs' Seq Inline -> Inline -> Seq Inline
forall a. Seq a -> a -> Seq a
|> [Inline] -> Inline
Strikeout ([Inline]
i1 [Inline] -> [Inline] -> [Inline]
forall a. Semigroup a => a -> a -> a
<> [Inline]
i2)
                          (Space, LineBreak) -> Seq Inline
xs' Seq Inline -> Inline -> Seq Inline
forall a. Seq a -> a -> Seq a
|> Inline
LineBreak
                          (LineBreak, Space) -> Seq Inline
xs' Seq Inline -> Inline -> Seq Inline
forall a. Seq a -> a -> Seq a
|> Inline
LineBreak
                          (SoftBreak, LineBreak) -> Seq Inline
xs' Seq Inline -> Inline -> Seq Inline
forall a. Seq a -> a -> Seq a
|> Inline
LineBreak
                          (LineBreak, SoftBreak) -> Seq Inline
xs' Seq Inline -> Inline -> Seq Inline
forall a. Seq a -> a -> Seq a
|> Inline
LineBreak
                          (SoftBreak, SoftBreak) -> Seq Inline
xs' Seq Inline -> Inline -> Seq Inline
forall a. Seq a -> a -> Seq a
|> Inline
SoftBreak
                          _                  -> Seq Inline
xs' Seq Inline -> Inline -> Seq Inline
forall a. Seq a -> a -> Seq a
|> Inline
x Seq Inline -> Inline -> Seq Inline
forall a. Seq a -> a -> Seq a
|> Inline
y
instance Monoid Inlines where
  mempty :: Inlines
mempty = Seq Inline -> Inlines
forall a. Seq a -> Many a
Many Seq Inline
forall a. Monoid a => a
mempty
  mappend :: Inlines -> Inlines -> Inlines
mappend = Inlines -> Inlines -> Inlines
forall a. Semigroup a => a -> a -> a
(<>)

instance IsString Inlines where
   fromString :: String -> Inlines
fromString = Text -> Inlines
text (Text -> Inlines) -> (String -> Text) -> String -> Inlines
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> Text
T.pack

-- | Trim leading and trailing spaces and softbreaks from an Inlines.
trimInlines :: Inlines -> Inlines
#if MIN_VERSION_containers(0,4,0)
trimInlines :: Inlines -> Inlines
trimInlines (Many ils :: Seq Inline
ils) = Seq Inline -> Inlines
forall a. Seq a -> Many a
Many (Seq Inline -> Inlines) -> Seq Inline -> Inlines
forall a b. (a -> b) -> a -> b
$ (Inline -> Bool) -> Seq Inline -> Seq Inline
forall a. (a -> Bool) -> Seq a -> Seq a
Seq.dropWhileL Inline -> Bool
isSp (Seq Inline -> Seq Inline) -> Seq Inline -> Seq Inline
forall a b. (a -> b) -> a -> b
$
                            (Inline -> Bool) -> Seq Inline -> Seq Inline
forall a. (a -> Bool) -> Seq a -> Seq a
Seq.dropWhileR Inline -> Bool
isSp (Seq Inline -> Seq Inline) -> Seq Inline -> Seq Inline
forall a b. (a -> b) -> a -> b
$ Seq Inline
ils
#else
-- for GHC 6.12, we need to workaround a bug in dropWhileR
-- see http://hackage.haskell.org/trac/ghc/ticket/4157
trimInlines (Many ils) = Many $ Seq.dropWhileL isSp $
                            Seq.reverse $ Seq.dropWhileL isSp $
                            Seq.reverse ils
#endif
  where isSp :: Inline -> Bool
isSp Space = Bool
True
        isSp SoftBreak = Bool
True
        isSp _ = Bool
False

-- Document builders

doc :: Blocks -> Pandoc
doc :: Many Block -> Pandoc
doc = Meta -> [Block] -> Pandoc
Pandoc Meta
nullMeta ([Block] -> Pandoc)
-> (Many Block -> [Block]) -> Many Block -> Pandoc
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Many Block -> [Block]
forall a. Many a -> [a]
toList

class ToMetaValue a where
  toMetaValue :: a -> MetaValue

instance ToMetaValue MetaValue where
  toMetaValue :: MetaValue -> MetaValue
toMetaValue = MetaValue -> MetaValue
forall a. a -> a
id

instance ToMetaValue Blocks where
  toMetaValue :: Many Block -> MetaValue
toMetaValue = [Block] -> MetaValue
MetaBlocks ([Block] -> MetaValue)
-> (Many Block -> [Block]) -> Many Block -> MetaValue
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Many Block -> [Block]
forall a. Many a -> [a]
toList

instance ToMetaValue Inlines where
  toMetaValue :: Inlines -> MetaValue
toMetaValue = [Inline] -> MetaValue
MetaInlines ([Inline] -> MetaValue)
-> (Inlines -> [Inline]) -> Inlines -> MetaValue
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Inlines -> [Inline]
forall a. Many a -> [a]
toList

instance ToMetaValue Bool where
  toMetaValue :: Bool -> MetaValue
toMetaValue = Bool -> MetaValue
MetaBool

instance ToMetaValue Text where
  toMetaValue :: Text -> MetaValue
toMetaValue = Text -> MetaValue
MetaString

instance {-# OVERLAPPING #-} ToMetaValue String where
  toMetaValue :: String -> MetaValue
toMetaValue = Text -> MetaValue
MetaString (Text -> MetaValue) -> (String -> Text) -> String -> MetaValue
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> Text
T.pack

instance ToMetaValue a => ToMetaValue [a] where
  toMetaValue :: [a] -> MetaValue
toMetaValue = [MetaValue] -> MetaValue
MetaList ([MetaValue] -> MetaValue)
-> ([a] -> [MetaValue]) -> [a] -> MetaValue
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (a -> MetaValue) -> [a] -> [MetaValue]
forall a b. (a -> b) -> [a] -> [b]
map a -> MetaValue
forall a. ToMetaValue a => a -> MetaValue
toMetaValue

instance ToMetaValue a => ToMetaValue (M.Map Text a) where
  toMetaValue :: Map Text a -> MetaValue
toMetaValue = Map Text MetaValue -> MetaValue
MetaMap (Map Text MetaValue -> MetaValue)
-> (Map Text a -> Map Text MetaValue) -> Map Text a -> MetaValue
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (a -> MetaValue) -> Map Text a -> Map Text MetaValue
forall a b k. (a -> b) -> Map k a -> Map k b
M.map a -> MetaValue
forall a. ToMetaValue a => a -> MetaValue
toMetaValue

instance ToMetaValue a => ToMetaValue (M.Map String a) where
  toMetaValue :: Map String a -> MetaValue
toMetaValue = Map Text MetaValue -> MetaValue
MetaMap (Map Text MetaValue -> MetaValue)
-> (Map String a -> Map Text MetaValue)
-> Map String a
-> MetaValue
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (a -> MetaValue) -> Map Text a -> Map Text MetaValue
forall a b k. (a -> b) -> Map k a -> Map k b
M.map a -> MetaValue
forall a. ToMetaValue a => a -> MetaValue
toMetaValue (Map Text a -> Map Text MetaValue)
-> (Map String a -> Map Text a)
-> Map String a
-> Map Text MetaValue
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (String -> Text) -> Map String a -> Map Text a
forall k2 k1 a. Ord k2 => (k1 -> k2) -> Map k1 a -> Map k2 a
M.mapKeys String -> Text
T.pack

class HasMeta a where
  setMeta :: ToMetaValue b => Text -> b -> a -> a
  deleteMeta :: Text -> a -> a

instance HasMeta Meta where
  setMeta :: Text -> b -> Meta -> Meta
setMeta key :: Text
key val :: b
val (Meta ms :: Map Text MetaValue
ms) = Map Text MetaValue -> Meta
Meta (Map Text MetaValue -> Meta) -> Map Text MetaValue -> Meta
forall a b. (a -> b) -> a -> b
$ Text -> MetaValue -> Map Text MetaValue -> Map Text MetaValue
forall k a. Ord k => k -> a -> Map k a -> Map k a
M.insert Text
key (b -> MetaValue
forall a. ToMetaValue a => a -> MetaValue
toMetaValue b
val) Map Text MetaValue
ms
  deleteMeta :: Text -> Meta -> Meta
deleteMeta key :: Text
key (Meta ms :: Map Text MetaValue
ms) = Map Text MetaValue -> Meta
Meta (Map Text MetaValue -> Meta) -> Map Text MetaValue -> Meta
forall a b. (a -> b) -> a -> b
$ Text -> Map Text MetaValue -> Map Text MetaValue
forall k a. Ord k => k -> Map k a -> Map k a
M.delete Text
key Map Text MetaValue
ms

instance HasMeta Pandoc where
  setMeta :: Text -> b -> Pandoc -> Pandoc
setMeta key :: Text
key val :: b
val (Pandoc (Meta ms :: Map Text MetaValue
ms) bs :: [Block]
bs) =
    Meta -> [Block] -> Pandoc
Pandoc (Map Text MetaValue -> Meta
Meta (Map Text MetaValue -> Meta) -> Map Text MetaValue -> Meta
forall a b. (a -> b) -> a -> b
$ Text -> MetaValue -> Map Text MetaValue -> Map Text MetaValue
forall k a. Ord k => k -> a -> Map k a -> Map k a
M.insert Text
key (b -> MetaValue
forall a. ToMetaValue a => a -> MetaValue
toMetaValue b
val) Map Text MetaValue
ms) [Block]
bs
  deleteMeta :: Text -> Pandoc -> Pandoc
deleteMeta key :: Text
key (Pandoc (Meta ms :: Map Text MetaValue
ms) bs :: [Block]
bs) =
    Meta -> [Block] -> Pandoc
Pandoc (Map Text MetaValue -> Meta
Meta (Map Text MetaValue -> Meta) -> Map Text MetaValue -> Meta
forall a b. (a -> b) -> a -> b
$ Text -> Map Text MetaValue -> Map Text MetaValue
forall k a. Ord k => k -> Map k a -> Map k a
M.delete Text
key Map Text MetaValue
ms) [Block]
bs

setTitle :: Inlines -> Pandoc -> Pandoc
setTitle :: Inlines -> Pandoc -> Pandoc
setTitle = Text -> Inlines -> Pandoc -> Pandoc
forall a b. (HasMeta a, ToMetaValue b) => Text -> b -> a -> a
setMeta "title"

setAuthors :: [Inlines] -> Pandoc -> Pandoc
setAuthors :: [Inlines] -> Pandoc -> Pandoc
setAuthors = Text -> [Inlines] -> Pandoc -> Pandoc
forall a b. (HasMeta a, ToMetaValue b) => Text -> b -> a -> a
setMeta "author"

setDate :: Inlines -> Pandoc -> Pandoc
setDate :: Inlines -> Pandoc -> Pandoc
setDate = Text -> Inlines -> Pandoc -> Pandoc
forall a b. (HasMeta a, ToMetaValue b) => Text -> b -> a -> a
setMeta "date"

-- Inline list builders

-- | Convert a 'Text' to 'Inlines', treating interword spaces as 'Space's
-- or 'SoftBreak's.  If you want a 'Str' with literal spaces, use 'str'.
text :: Text -> Inlines
text :: Text -> Inlines
text = [Inline] -> Inlines
forall a. [a] -> Many a
fromList ([Inline] -> Inlines) -> (Text -> [Inline]) -> Text -> Inlines
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Text -> Inline) -> [Text] -> [Inline]
forall a b. (a -> b) -> [a] -> [b]
map Text -> Inline
conv ([Text] -> [Inline]) -> (Text -> [Text]) -> Text -> [Inline]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> [Text]
breakBySpaces
  where breakBySpaces :: Text -> [Text]
breakBySpaces = (Char -> Char -> Bool) -> Text -> [Text]
T.groupBy Char -> Char -> Bool
sameCategory
        sameCategory :: Char -> Char -> Bool
sameCategory x :: Char
x y :: Char
y = Char -> Bool
is_space Char
x Bool -> Bool -> Bool
forall a. Eq a => a -> a -> Bool
== Char -> Bool
is_space Char
y
        conv :: Text -> Inline
conv xs :: Text
xs | (Char -> Bool) -> Text -> Bool
T.all Char -> Bool
is_space Text
xs =
           if (Char -> Bool) -> Text -> Bool
T.any Char -> Bool
is_newline Text
xs
              then Inline
SoftBreak
              else Inline
Space
        conv xs :: Text
xs = Text -> Inline
Str Text
xs
        is_space :: Char -> Bool
is_space ' '    = Bool
True
        is_space '\r'   = Bool
True
        is_space '\n'   = Bool
True
        is_space '\t'   = Bool
True
        is_space _      = Bool
False
        is_newline :: Char -> Bool
is_newline '\r' = Bool
True
        is_newline '\n' = Bool
True
        is_newline _    = Bool
False

str :: Text -> Inlines
str :: Text -> Inlines
str = Inline -> Inlines
forall a. a -> Many a
singleton (Inline -> Inlines) -> (Text -> Inline) -> Text -> Inlines
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> Inline
Str

emph :: Inlines -> Inlines
emph :: Inlines -> Inlines
emph = Inline -> Inlines
forall a. a -> Many a
singleton (Inline -> Inlines) -> (Inlines -> Inline) -> Inlines -> Inlines
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Inline] -> Inline
Emph ([Inline] -> Inline) -> (Inlines -> [Inline]) -> Inlines -> Inline
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Inlines -> [Inline]
forall a. Many a -> [a]
toList

underline :: Inlines -> Inlines
underline :: Inlines -> Inlines
underline = Inline -> Inlines
forall a. a -> Many a
singleton (Inline -> Inlines) -> (Inlines -> Inline) -> Inlines -> Inlines
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Inline] -> Inline
Underline ([Inline] -> Inline) -> (Inlines -> [Inline]) -> Inlines -> Inline
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Inlines -> [Inline]
forall a. Many a -> [a]
toList

strong :: Inlines -> Inlines
strong :: Inlines -> Inlines
strong = Inline -> Inlines
forall a. a -> Many a
singleton (Inline -> Inlines) -> (Inlines -> Inline) -> Inlines -> Inlines
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Inline] -> Inline
Strong ([Inline] -> Inline) -> (Inlines -> [Inline]) -> Inlines -> Inline
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Inlines -> [Inline]
forall a. Many a -> [a]
toList

strikeout :: Inlines -> Inlines
strikeout :: Inlines -> Inlines
strikeout = Inline -> Inlines
forall a. a -> Many a
singleton (Inline -> Inlines) -> (Inlines -> Inline) -> Inlines -> Inlines
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Inline] -> Inline
Strikeout ([Inline] -> Inline) -> (Inlines -> [Inline]) -> Inlines -> Inline
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Inlines -> [Inline]
forall a. Many a -> [a]
toList

superscript :: Inlines -> Inlines
superscript :: Inlines -> Inlines
superscript = Inline -> Inlines
forall a. a -> Many a
singleton (Inline -> Inlines) -> (Inlines -> Inline) -> Inlines -> Inlines
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Inline] -> Inline
Superscript ([Inline] -> Inline) -> (Inlines -> [Inline]) -> Inlines -> Inline
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Inlines -> [Inline]
forall a. Many a -> [a]
toList

subscript :: Inlines -> Inlines
subscript :: Inlines -> Inlines
subscript = Inline -> Inlines
forall a. a -> Many a
singleton (Inline -> Inlines) -> (Inlines -> Inline) -> Inlines -> Inlines
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Inline] -> Inline
Subscript ([Inline] -> Inline) -> (Inlines -> [Inline]) -> Inlines -> Inline
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Inlines -> [Inline]
forall a. Many a -> [a]
toList

smallcaps :: Inlines -> Inlines
smallcaps :: Inlines -> Inlines
smallcaps = Inline -> Inlines
forall a. a -> Many a
singleton (Inline -> Inlines) -> (Inlines -> Inline) -> Inlines -> Inlines
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Inline] -> Inline
SmallCaps ([Inline] -> Inline) -> (Inlines -> [Inline]) -> Inlines -> Inline
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Inlines -> [Inline]
forall a. Many a -> [a]
toList

singleQuoted :: Inlines -> Inlines
singleQuoted :: Inlines -> Inlines
singleQuoted = QuoteType -> Inlines -> Inlines
quoted QuoteType
SingleQuote

doubleQuoted :: Inlines -> Inlines
doubleQuoted :: Inlines -> Inlines
doubleQuoted = QuoteType -> Inlines -> Inlines
quoted QuoteType
DoubleQuote

quoted :: QuoteType -> Inlines -> Inlines
quoted :: QuoteType -> Inlines -> Inlines
quoted qt :: QuoteType
qt = Inline -> Inlines
forall a. a -> Many a
singleton (Inline -> Inlines) -> (Inlines -> Inline) -> Inlines -> Inlines
forall b c a. (b -> c) -> (a -> b) -> a -> c
. QuoteType -> [Inline] -> Inline
Quoted QuoteType
qt ([Inline] -> Inline) -> (Inlines -> [Inline]) -> Inlines -> Inline
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Inlines -> [Inline]
forall a. Many a -> [a]
toList

cite :: [Citation] -> Inlines -> Inlines
cite :: [Citation] -> Inlines -> Inlines
cite cts :: [Citation]
cts = Inline -> Inlines
forall a. a -> Many a
singleton (Inline -> Inlines) -> (Inlines -> Inline) -> Inlines -> Inlines
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Citation] -> [Inline] -> Inline
Cite [Citation]
cts ([Inline] -> Inline) -> (Inlines -> [Inline]) -> Inlines -> Inline
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Inlines -> [Inline]
forall a. Many a -> [a]
toList

-- | Inline code with attributes.
codeWith :: Attr -> Text -> Inlines
codeWith :: Attr -> Text -> Inlines
codeWith attrs :: Attr
attrs = Inline -> Inlines
forall a. a -> Many a
singleton (Inline -> Inlines) -> (Text -> Inline) -> Text -> Inlines
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Attr -> Text -> Inline
Code Attr
attrs

-- | Plain inline code.
code :: Text -> Inlines
code :: Text -> Inlines
code = Attr -> Text -> Inlines
codeWith Attr
nullAttr

space :: Inlines
space :: Inlines
space = Inline -> Inlines
forall a. a -> Many a
singleton Inline
Space

softbreak :: Inlines
softbreak :: Inlines
softbreak = Inline -> Inlines
forall a. a -> Many a
singleton Inline
SoftBreak

linebreak :: Inlines
linebreak :: Inlines
linebreak = Inline -> Inlines
forall a. a -> Many a
singleton Inline
LineBreak

-- | Inline math
math :: Text -> Inlines
math :: Text -> Inlines
math = Inline -> Inlines
forall a. a -> Many a
singleton (Inline -> Inlines) -> (Text -> Inline) -> Text -> Inlines
forall b c a. (b -> c) -> (a -> b) -> a -> c
. MathType -> Text -> Inline
Math MathType
InlineMath

-- | Display math
displayMath :: Text -> Inlines
displayMath :: Text -> Inlines
displayMath = Inline -> Inlines
forall a. a -> Many a
singleton (Inline -> Inlines) -> (Text -> Inline) -> Text -> Inlines
forall b c a. (b -> c) -> (a -> b) -> a -> c
. MathType -> Text -> Inline
Math MathType
DisplayMath

rawInline :: Text -> Text -> Inlines
rawInline :: Text -> Text -> Inlines
rawInline format :: Text
format = Inline -> Inlines
forall a. a -> Many a
singleton (Inline -> Inlines) -> (Text -> Inline) -> Text -> Inlines
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Format -> Text -> Inline
RawInline (Text -> Format
Format Text
format)

link :: Text  -- ^ URL
     -> Text  -- ^ Title
     -> Inlines -- ^ Label
     -> Inlines
link :: Text -> Text -> Inlines -> Inlines
link = Attr -> Text -> Text -> Inlines -> Inlines
linkWith Attr
nullAttr

linkWith :: Attr    -- ^ Attributes
         -> Text  -- ^ URL
         -> Text  -- ^ Title
         -> Inlines -- ^ Label
         -> Inlines
linkWith :: Attr -> Text -> Text -> Inlines -> Inlines
linkWith attr :: Attr
attr url :: Text
url title :: Text
title x :: Inlines
x = Inline -> Inlines
forall a. a -> Many a
singleton (Inline -> Inlines) -> Inline -> Inlines
forall a b. (a -> b) -> a -> b
$ Attr -> [Inline] -> Target -> Inline
Link Attr
attr (Inlines -> [Inline]
forall a. Many a -> [a]
toList Inlines
x) (Text
url, Text
title)

image :: Text  -- ^ URL
      -> Text  -- ^ Title
      -> Inlines -- ^ Alt text
      -> Inlines
image :: Text -> Text -> Inlines -> Inlines
image = Attr -> Text -> Text -> Inlines -> Inlines
imageWith Attr
nullAttr

imageWith :: Attr -- ^ Attributes
          -> Text  -- ^ URL
          -> Text  -- ^ Title
          -> Inlines -- ^ Alt text
          -> Inlines
imageWith :: Attr -> Text -> Text -> Inlines -> Inlines
imageWith attr :: Attr
attr url :: Text
url title :: Text
title x :: Inlines
x = Inline -> Inlines
forall a. a -> Many a
singleton (Inline -> Inlines) -> Inline -> Inlines
forall a b. (a -> b) -> a -> b
$ Attr -> [Inline] -> Target -> Inline
Image Attr
attr (Inlines -> [Inline]
forall a. Many a -> [a]
toList Inlines
x) (Text
url, Text
title)

note :: Blocks -> Inlines
note :: Many Block -> Inlines
note = Inline -> Inlines
forall a. a -> Many a
singleton (Inline -> Inlines)
-> (Many Block -> Inline) -> Many Block -> Inlines
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Block] -> Inline
Note ([Block] -> Inline)
-> (Many Block -> [Block]) -> Many Block -> Inline
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Many Block -> [Block]
forall a. Many a -> [a]
toList

spanWith :: Attr -> Inlines -> Inlines
spanWith :: Attr -> Inlines -> Inlines
spanWith attr :: Attr
attr = Inline -> Inlines
forall a. a -> Many a
singleton (Inline -> Inlines) -> (Inlines -> Inline) -> Inlines -> Inlines
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Attr -> [Inline] -> Inline
Span Attr
attr ([Inline] -> Inline) -> (Inlines -> [Inline]) -> Inlines -> Inline
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Inlines -> [Inline]
forall a. Many a -> [a]
toList

-- Block list builders

para :: Inlines -> Blocks
para :: Inlines -> Many Block
para = Block -> Many Block
forall a. a -> Many a
singleton (Block -> Many Block)
-> (Inlines -> Block) -> Inlines -> Many Block
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Inline] -> Block
Para ([Inline] -> Block) -> (Inlines -> [Inline]) -> Inlines -> Block
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Inlines -> [Inline]
forall a. Many a -> [a]
toList

plain :: Inlines -> Blocks
plain :: Inlines -> Many Block
plain ils :: Inlines
ils = if Inlines -> Bool
forall a. Many a -> Bool
isNull Inlines
ils
               then Many Block
forall a. Monoid a => a
mempty
               else Block -> Many Block
forall a. a -> Many a
singleton (Block -> Many Block)
-> (Inlines -> Block) -> Inlines -> Many Block
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Inline] -> Block
Plain ([Inline] -> Block) -> (Inlines -> [Inline]) -> Inlines -> Block
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Inlines -> [Inline]
forall a. Many a -> [a]
toList (Inlines -> Many Block) -> Inlines -> Many Block
forall a b. (a -> b) -> a -> b
$ Inlines
ils

lineBlock :: [Inlines] -> Blocks
lineBlock :: [Inlines] -> Many Block
lineBlock = Block -> Many Block
forall a. a -> Many a
singleton (Block -> Many Block)
-> ([Inlines] -> Block) -> [Inlines] -> Many Block
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [[Inline]] -> Block
LineBlock ([[Inline]] -> Block)
-> ([Inlines] -> [[Inline]]) -> [Inlines] -> Block
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Inlines -> [Inline]) -> [Inlines] -> [[Inline]]
forall a b. (a -> b) -> [a] -> [b]
map Inlines -> [Inline]
forall a. Many a -> [a]
toList

-- | A code block with attributes.
codeBlockWith :: Attr -> Text -> Blocks
codeBlockWith :: Attr -> Text -> Many Block
codeBlockWith attrs :: Attr
attrs = Block -> Many Block
forall a. a -> Many a
singleton (Block -> Many Block) -> (Text -> Block) -> Text -> Many Block
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Attr -> Text -> Block
CodeBlock Attr
attrs

-- | A plain code block.
codeBlock :: Text -> Blocks
codeBlock :: Text -> Many Block
codeBlock = Attr -> Text -> Many Block
codeBlockWith Attr
nullAttr

rawBlock :: Text -> Text -> Blocks
rawBlock :: Text -> Text -> Many Block
rawBlock format :: Text
format = Block -> Many Block
forall a. a -> Many a
singleton (Block -> Many Block) -> (Text -> Block) -> Text -> Many Block
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Format -> Text -> Block
RawBlock (Text -> Format
Format Text
format)

blockQuote :: Blocks -> Blocks
blockQuote :: Many Block -> Many Block
blockQuote = Block -> Many Block
forall a. a -> Many a
singleton (Block -> Many Block)
-> (Many Block -> Block) -> Many Block -> Many Block
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Block] -> Block
BlockQuote ([Block] -> Block)
-> (Many Block -> [Block]) -> Many Block -> Block
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Many Block -> [Block]
forall a. Many a -> [a]
toList

-- | Ordered list with attributes.
orderedListWith :: ListAttributes -> [Blocks] -> Blocks
orderedListWith :: ListAttributes -> [Many Block] -> Many Block
orderedListWith attrs :: ListAttributes
attrs = Block -> Many Block
forall a. a -> Many a
singleton (Block -> Many Block)
-> ([Many Block] -> Block) -> [Many Block] -> Many Block
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ListAttributes -> [[Block]] -> Block
OrderedList ListAttributes
attrs ([[Block]] -> Block)
-> ([Many Block] -> [[Block]]) -> [Many Block] -> Block
forall b c a. (b -> c) -> (a -> b) -> a -> c
.  (Many Block -> [Block]) -> [Many Block] -> [[Block]]
forall a b. (a -> b) -> [a] -> [b]
map Many Block -> [Block]
forall a. Many a -> [a]
toList

-- | Ordered list with default attributes.
orderedList :: [Blocks] -> Blocks
orderedList :: [Many Block] -> Many Block
orderedList = ListAttributes -> [Many Block] -> Many Block
orderedListWith (1, ListNumberStyle
DefaultStyle, ListNumberDelim
DefaultDelim)

bulletList :: [Blocks] -> Blocks
bulletList :: [Many Block] -> Many Block
bulletList = Block -> Many Block
forall a. a -> Many a
singleton (Block -> Many Block)
-> ([Many Block] -> Block) -> [Many Block] -> Many Block
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [[Block]] -> Block
BulletList ([[Block]] -> Block)
-> ([Many Block] -> [[Block]]) -> [Many Block] -> Block
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Many Block -> [Block]) -> [Many Block] -> [[Block]]
forall a b. (a -> b) -> [a] -> [b]
map Many Block -> [Block]
forall a. Many a -> [a]
toList

definitionList :: [(Inlines, [Blocks])] -> Blocks
definitionList :: [(Inlines, [Many Block])] -> Many Block
definitionList = Block -> Many Block
forall a. a -> Many a
singleton (Block -> Many Block)
-> ([(Inlines, [Many Block])] -> Block)
-> [(Inlines, [Many Block])]
-> Many Block
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [([Inline], [[Block]])] -> Block
DefinitionList ([([Inline], [[Block]])] -> Block)
-> ([(Inlines, [Many Block])] -> [([Inline], [[Block]])])
-> [(Inlines, [Many Block])]
-> Block
forall b c a. (b -> c) -> (a -> b) -> a -> c
.  ((Inlines, [Many Block]) -> ([Inline], [[Block]]))
-> [(Inlines, [Many Block])] -> [([Inline], [[Block]])]
forall a b. (a -> b) -> [a] -> [b]
map (Inlines -> [Inline]
forall a. Many a -> [a]
toList (Inlines -> [Inline])
-> ([Many Block] -> [[Block]])
-> (Inlines, [Many Block])
-> ([Inline], [[Block]])
forall (a :: * -> * -> *) b c b' c'.
Arrow a =>
a b c -> a b' c' -> a (b, b') (c, c')
*** (Many Block -> [Block]) -> [Many Block] -> [[Block]]
forall a b. (a -> b) -> [a] -> [b]
map Many Block -> [Block]
forall a. Many a -> [a]
toList)

header :: Int  -- ^ Level
       -> Inlines
       -> Blocks
header :: Int -> Inlines -> Many Block
header = Attr -> Int -> Inlines -> Many Block
headerWith Attr
nullAttr

headerWith :: Attr -> Int -> Inlines -> Blocks
headerWith :: Attr -> Int -> Inlines -> Many Block
headerWith attr :: Attr
attr level :: Int
level = Block -> Many Block
forall a. a -> Many a
singleton (Block -> Many Block)
-> (Inlines -> Block) -> Inlines -> Many Block
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> Attr -> [Inline] -> Block
Header Int
level Attr
attr ([Inline] -> Block) -> (Inlines -> [Inline]) -> Inlines -> Block
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Inlines -> [Inline]
forall a. Many a -> [a]
toList

horizontalRule :: Blocks
horizontalRule :: Many Block
horizontalRule = Block -> Many Block
forall a. a -> Many a
singleton Block
HorizontalRule

cellWith :: Attr
         -> Alignment
         -> RowSpan
         -> ColSpan
         -> Blocks
         -> Cell
cellWith :: Attr -> Alignment -> RowSpan -> ColSpan -> Many Block -> Cell
cellWith at :: Attr
at a :: Alignment
a r :: RowSpan
r c :: ColSpan
c = Attr -> Alignment -> RowSpan -> ColSpan -> [Block] -> Cell
Cell Attr
at Alignment
a RowSpan
r ColSpan
c ([Block] -> Cell) -> (Many Block -> [Block]) -> Many Block -> Cell
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Many Block -> [Block]
forall a. Many a -> [a]
toList

cell :: Alignment
     -> RowSpan
     -> ColSpan
     -> Blocks
     -> Cell
cell :: Alignment -> RowSpan -> ColSpan -> Many Block -> Cell
cell = Attr -> Alignment -> RowSpan -> ColSpan -> Many Block -> Cell
cellWith Attr
nullAttr

-- | A 1×1 cell with default alignment.
simpleCell :: Blocks -> Cell
simpleCell :: Many Block -> Cell
simpleCell = Alignment -> RowSpan -> ColSpan -> Many Block -> Cell
cell Alignment
AlignDefault 1 1

-- | A 1×1 empty cell.
emptyCell :: Cell
emptyCell :: Cell
emptyCell = Many Block -> Cell
simpleCell Many Block
forall a. Monoid a => a
mempty

-- | Table builder. Performs normalization with 'normalizeTableHead',
-- 'normalizeTableBody', and 'normalizeTableFoot'. The number of table
-- columns is given by the length of @['ColSpec']@.
table :: Caption
      -> [ColSpec]
      -> TableHead
      -> [TableBody]
      -> TableFoot
      -> Blocks
table :: Caption
-> [ColSpec] -> TableHead -> [TableBody] -> TableFoot -> Many Block
table = Attr
-> Caption
-> [ColSpec]
-> TableHead
-> [TableBody]
-> TableFoot
-> Many Block
tableWith Attr
nullAttr

tableWith :: Attr
          -> Caption
          -> [ColSpec]
          -> TableHead
          -> [TableBody]
          -> TableFoot
          -> Blocks
tableWith :: Attr
-> Caption
-> [ColSpec]
-> TableHead
-> [TableBody]
-> TableFoot
-> Many Block
tableWith attr :: Attr
attr capt :: Caption
capt specs :: [ColSpec]
specs th :: TableHead
th tbs :: [TableBody]
tbs tf :: TableFoot
tf
  = Block -> Many Block
forall a. a -> Many a
singleton (Block -> Many Block) -> Block -> Many Block
forall a b. (a -> b) -> a -> b
$ Attr
-> Caption
-> [ColSpec]
-> TableHead
-> [TableBody]
-> TableFoot
-> Block
Table Attr
attr Caption
capt [ColSpec]
specs TableHead
th' [TableBody]
tbs' TableFoot
tf'
  where
    twidth :: Int
twidth = [ColSpec] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length [ColSpec]
specs
    th' :: TableHead
th'  = Int -> TableHead -> TableHead
normalizeTableHead Int
twidth TableHead
th
    tbs' :: [TableBody]
tbs' = (TableBody -> TableBody) -> [TableBody] -> [TableBody]
forall a b. (a -> b) -> [a] -> [b]
map (Int -> TableBody -> TableBody
normalizeTableBody Int
twidth) [TableBody]
tbs
    tf' :: TableFoot
tf'  = Int -> TableFoot -> TableFoot
normalizeTableFoot Int
twidth TableFoot
tf

-- | A simple table without a caption.
simpleTable :: [Blocks]   -- ^ Headers
            -> [[Blocks]] -- ^ Rows
            -> Blocks
simpleTable :: [Many Block] -> [[Many Block]] -> Many Block
simpleTable headers :: [Many Block]
headers rows :: [[Many Block]]
rows =
  Caption
-> [ColSpec] -> TableHead -> [TableBody] -> TableFoot -> Many Block
table Caption
emptyCaption (Int -> ColSpec -> [ColSpec]
forall a. Int -> a -> [a]
replicate Int
numcols ColSpec
defaults) TableHead
th [TableBody
tb] TableFoot
tf
  where defaults :: ColSpec
defaults = (Alignment
AlignDefault, ColWidth
ColWidthDefault)
        numcols :: Int
numcols  = [Int] -> Int
forall (t :: * -> *) a. (Foldable t, Ord a) => t a -> a
maximum (([Many Block] -> Int) -> [[Many Block]] -> [Int]
forall a b. (a -> b) -> [a] -> [b]
map [Many Block] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length ([Many Block]
headers[Many Block] -> [[Many Block]] -> [[Many Block]]
forall a. a -> [a] -> [a]
:[[Many Block]]
rows))
        toRow :: [Many Block] -> Row
toRow = Attr -> [Cell] -> Row
Row Attr
nullAttr ([Cell] -> Row) -> ([Many Block] -> [Cell]) -> [Many Block] -> Row
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Many Block -> Cell) -> [Many Block] -> [Cell]
forall a b. (a -> b) -> [a] -> [b]
map Many Block -> Cell
simpleCell
        toHeaderRow :: t a -> [Row]
toHeaderRow l :: t a
l
          | t a -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null t a
l    = []
          | Bool
otherwise = [[Many Block] -> Row
toRow [Many Block]
headers]
        th :: TableHead
th = Attr -> [Row] -> TableHead
TableHead Attr
nullAttr ([Many Block] -> [Row]
forall (t :: * -> *) a. Foldable t => t a -> [Row]
toHeaderRow [Many Block]
headers)
        tb :: TableBody
tb = Attr -> RowHeadColumns -> [Row] -> [Row] -> TableBody
TableBody Attr
nullAttr 0 [] ([Row] -> TableBody) -> [Row] -> TableBody
forall a b. (a -> b) -> a -> b
$ ([Many Block] -> Row) -> [[Many Block]] -> [Row]
forall a b. (a -> b) -> [a] -> [b]
map [Many Block] -> Row
toRow [[Many Block]]
rows
        tf :: TableFoot
tf = Attr -> [Row] -> TableFoot
TableFoot Attr
nullAttr []

caption :: Maybe ShortCaption -> Blocks -> Caption
caption :: Maybe [Inline] -> Many Block -> Caption
caption x :: Maybe [Inline]
x = Maybe [Inline] -> [Block] -> Caption
Caption Maybe [Inline]
x ([Block] -> Caption)
-> (Many Block -> [Block]) -> Many Block -> Caption
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Many Block -> [Block]
forall a. Many a -> [a]
toList

simpleCaption :: Blocks -> Caption
simpleCaption :: Many Block -> Caption
simpleCaption = Maybe [Inline] -> Many Block -> Caption
caption Maybe [Inline]
forall a. Maybe a
Nothing

emptyCaption :: Caption
emptyCaption :: Caption
emptyCaption = Many Block -> Caption
simpleCaption Many Block
forall a. Monoid a => a
mempty

simpleFigureWith :: Attr -> Inlines -> Text -> Text -> Blocks
simpleFigureWith :: Attr -> Inlines -> Text -> Text -> Many Block
simpleFigureWith attr :: Attr
attr figureCaption :: Inlines
figureCaption url :: Text
url title :: Text
title =
  Inlines -> Many Block
para (Inlines -> Many Block) -> Inlines -> Many Block
forall a b. (a -> b) -> a -> b
$ Attr -> Text -> Text -> Inlines -> Inlines
imageWith Attr
attr Text
url ("fig:" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
title) Inlines
figureCaption

simpleFigure :: Inlines -> Text -> Text -> Blocks
simpleFigure :: Inlines -> Text -> Text -> Many Block
simpleFigure = Attr -> Inlines -> Text -> Text -> Many Block
simpleFigureWith Attr
nullAttr

divWith :: Attr -> Blocks -> Blocks
divWith :: Attr -> Many Block -> Many Block
divWith attr :: Attr
attr = Block -> Many Block
forall a. a -> Many a
singleton (Block -> Many Block)
-> (Many Block -> Block) -> Many Block -> Many Block
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Attr -> [Block] -> Block
Div Attr
attr ([Block] -> Block)
-> (Many Block -> [Block]) -> Many Block -> Block
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Many Block -> [Block]
forall a. Many a -> [a]
toList

-- | Normalize the 'TableHead' with 'clipRows' and 'placeRowSection'
-- so that when placed on a grid with the given width and a height
-- equal to the number of rows in the initial 'TableHead', there will
-- be no empty spaces or overlapping cells, and the cells will not
-- protrude beyond the grid.
normalizeTableHead :: Int -> TableHead -> TableHead
normalizeTableHead :: Int -> TableHead -> TableHead
normalizeTableHead twidth :: Int
twidth (TableHead attr :: Attr
attr rows :: [Row]
rows)
  = Attr -> [Row] -> TableHead
TableHead Attr
attr ([Row] -> TableHead) -> [Row] -> TableHead
forall a b. (a -> b) -> a -> b
$ Int -> [Row] -> [Row]
normalizeHeaderSection Int
twidth [Row]
rows

-- | Normalize the intermediate head and body section of a
-- 'TableBody', as in 'normalizeTableHead', but additionally ensure
-- that row head cells do not go beyond the row head inside the
-- intermediate body.
normalizeTableBody :: Int -> TableBody -> TableBody
normalizeTableBody :: Int -> TableBody -> TableBody
normalizeTableBody twidth :: Int
twidth (TableBody attr :: Attr
attr rhc :: RowHeadColumns
rhc th :: [Row]
th tb :: [Row]
tb)
  = Attr -> RowHeadColumns -> [Row] -> [Row] -> TableBody
TableBody Attr
attr
              RowHeadColumns
rhc'
              (Int -> [Row] -> [Row]
normalizeHeaderSection Int
twidth [Row]
th)
              (Int -> RowHeadColumns -> [Row] -> [Row]
normalizeBodySection Int
twidth RowHeadColumns
rhc' [Row]
tb)
  where
    rhc' :: RowHeadColumns
rhc' = RowHeadColumns -> RowHeadColumns -> RowHeadColumns
forall a. Ord a => a -> a -> a
max 0 (RowHeadColumns -> RowHeadColumns)
-> RowHeadColumns -> RowHeadColumns
forall a b. (a -> b) -> a -> b
$ RowHeadColumns -> RowHeadColumns -> RowHeadColumns
forall a. Ord a => a -> a -> a
min (Int -> RowHeadColumns
RowHeadColumns Int
twidth) RowHeadColumns
rhc

-- | Normalize the 'TableFoot', as in 'normalizeTableHead'.
normalizeTableFoot :: Int -> TableFoot -> TableFoot
normalizeTableFoot :: Int -> TableFoot -> TableFoot
normalizeTableFoot twidth :: Int
twidth (TableFoot attr :: Attr
attr rows :: [Row]
rows)
  = Attr -> [Row] -> TableFoot
TableFoot Attr
attr ([Row] -> TableFoot) -> [Row] -> TableFoot
forall a b. (a -> b) -> a -> b
$ Int -> [Row] -> [Row]
normalizeHeaderSection Int
twidth [Row]
rows

normalizeHeaderSection :: Int -- ^ The desired width of the table
                       -> [Row]
                       -> [Row]
normalizeHeaderSection :: Int -> [Row] -> [Row]
normalizeHeaderSection twidth :: Int
twidth rows :: [Row]
rows
  = [RowSpan] -> [Row] -> [Row]
normalizeRows' (Int -> RowSpan -> [RowSpan]
forall a. Int -> a -> [a]
replicate Int
twidth 1) ([Row] -> [Row]) -> [Row] -> [Row]
forall a b. (a -> b) -> a -> b
$ [Row] -> [Row]
clipRows [Row]
rows
  where
    normalizeRows' :: [RowSpan] -> [Row] -> [Row]
normalizeRows' oldHang :: [RowSpan]
oldHang (Row attr :: Attr
attr cells :: [Cell]
cells:rs :: [Row]
rs)
      = let (newHang :: [RowSpan]
newHang, cells' :: [Cell]
cells', _) = [RowSpan] -> [Cell] -> ([RowSpan], [Cell], [Cell])
placeRowSection [RowSpan]
oldHang ([Cell] -> ([RowSpan], [Cell], [Cell]))
-> [Cell] -> ([RowSpan], [Cell], [Cell])
forall a b. (a -> b) -> a -> b
$ [Cell]
cells [Cell] -> [Cell] -> [Cell]
forall a. Semigroup a => a -> a -> a
<> Cell -> [Cell]
forall a. a -> [a]
repeat Cell
emptyCell
            rs' :: [Row]
rs' = [RowSpan] -> [Row] -> [Row]
normalizeRows' [RowSpan]
newHang [Row]
rs
        in Attr -> [Cell] -> Row
Row Attr
attr [Cell]
cells' Row -> [Row] -> [Row]
forall a. a -> [a] -> [a]
: [Row]
rs'
    normalizeRows' _ [] = []

normalizeBodySection :: Int -- ^ The desired width of the table
                     -> RowHeadColumns -- ^ The width of the row head,
                                       -- between 0 and the table
                                       -- width
                     -> [Row]
                     -> [Row]
normalizeBodySection :: Int -> RowHeadColumns -> [Row] -> [Row]
normalizeBodySection twidth :: Int
twidth (RowHeadColumns rhc :: Int
rhc) rows :: [Row]
rows
  = [RowSpan] -> [RowSpan] -> [Row] -> [Row]
normalizeRows' (Int -> RowSpan -> [RowSpan]
forall a. Int -> a -> [a]
replicate Int
rhc 1) (Int -> RowSpan -> [RowSpan]
forall a. Int -> a -> [a]
replicate Int
rbc 1) ([Row] -> [Row]) -> [Row] -> [Row]
forall a b. (a -> b) -> a -> b
$ [Row] -> [Row]
clipRows [Row]
rows
  where
    rbc :: Int
rbc = Int
twidth Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
rhc

    normalizeRows' :: [RowSpan] -> [RowSpan] -> [Row] -> [Row]
normalizeRows' headHang :: [RowSpan]
headHang bodyHang :: [RowSpan]
bodyHang (Row attr :: Attr
attr cells :: [Cell]
cells:rs :: [Row]
rs)
      = let (headHang' :: [RowSpan]
headHang', rowHead :: [Cell]
rowHead, cells' :: [Cell]
cells') = [RowSpan] -> [Cell] -> ([RowSpan], [Cell], [Cell])
placeRowSection [RowSpan]
headHang ([Cell] -> ([RowSpan], [Cell], [Cell]))
-> [Cell] -> ([RowSpan], [Cell], [Cell])
forall a b. (a -> b) -> a -> b
$ [Cell]
cells [Cell] -> [Cell] -> [Cell]
forall a. Semigroup a => a -> a -> a
<> Cell -> [Cell]
forall a. a -> [a]
repeat Cell
emptyCell
            (bodyHang' :: [RowSpan]
bodyHang', rowBody :: [Cell]
rowBody, _)      = [RowSpan] -> [Cell] -> ([RowSpan], [Cell], [Cell])
placeRowSection [RowSpan]
bodyHang [Cell]
cells'
            rs' :: [Row]
rs' = [RowSpan] -> [RowSpan] -> [Row] -> [Row]
normalizeRows' [RowSpan]
headHang' [RowSpan]
bodyHang' [Row]
rs
        in Attr -> [Cell] -> Row
Row Attr
attr ([Cell]
rowHead [Cell] -> [Cell] -> [Cell]
forall a. Semigroup a => a -> a -> a
<> [Cell]
rowBody) Row -> [Row] -> [Row]
forall a. a -> [a] -> [a]
: [Row]
rs'
    normalizeRows' _ _ [] = []

-- | Normalize the given list of cells so that they fit on a single
-- grid row. The 'RowSpan' values of the cells are assumed to be valid
-- (clamped to lie between 1 and the remaining grid height). The cells
-- in the list are also assumed to be able to fill the entire grid
-- row. These conditions can be met by appending @repeat 'emptyCell'@
-- to the @['Cell']@ list and using 'clipRows' on the entire table
-- section beforehand.
--
-- Normalization follows the principle that cells are placed on a grid
-- row in order, each at the first available grid position from the
-- left, having their 'ColSpan' reduced if they would overlap with a
-- previous cell, stopping once the row is filled. Only the dimensions
-- of cells are changed, and only of those cells that fit on the row.
--
-- Possible overlap is detected using the given @['RowSpan']@, which
-- is the "overhang" of the previous grid row, a list of the heights
-- of cells that descend through the previous row, reckoned
-- /only from the previous row/.
-- Its length should be the width (number of columns) of the current
-- grid row.
--
-- For example, the numbers in the following headerless grid table
-- represent the overhang at each grid position for that table:
--
-- @
--     1   1   1   1
--   +---+---+---+---+
--   | 1 | 2   2 | 3 |
--   +---+       +   +
--   | 1 | 1   1 | 2 |
--   +---+---+---+   +
--   | 1   1 | 1 | 1 |
--   +---+---+---+---+
-- @
--
-- In any table, the row before the first has an overhang of
-- @replicate tableWidth 1@, since there are no cells to descend into
-- the table from there.  The overhang of the first row in the example
-- is @[1, 2, 2, 3]@.
--
-- So if after 'clipRows' the unnormalized second row of that example
-- table were
--
-- > r = [("a", 1, 2),("b", 2, 3)] -- the cells displayed as (label, RowSpan, ColSpan) only
--
-- a correct invocation of 'placeRowSection' to normalize it would be
--
-- >>> placeRowSection [1, 2, 2, 3] $ r ++ repeat emptyCell
-- ([1, 1, 1, 2], [("a", 1, 1)], [("b", 2, 3)] ++ repeat emptyCell) -- wouldn't stop printing, of course
--
-- and if the third row were only @[("c", 1, 2)]@, then the expression
-- would be
--
-- >>> placeRowSection [1, 1, 1, 2] $ [("c", 1, 2)] ++ repeat emptyCell
-- ([1, 1, 1, 1], [("c", 1, 2), emptyCell], repeat emptyCell)
placeRowSection :: [RowSpan] -- ^ The overhang of the previous grid
                             -- row
                -> [Cell]    -- ^ The cells to lay on the grid row
                -> ([RowSpan], [Cell], [Cell]) -- ^ The overhang of
                                               -- the current grid
                                               -- row, the normalized
                                               -- cells that fit on
                                               -- the current row, and
                                               -- the remaining
                                               -- unmodified cells
placeRowSection :: [RowSpan] -> [Cell] -> ([RowSpan], [Cell], [Cell])
placeRowSection oldHang :: [RowSpan]
oldHang cellStream :: [Cell]
cellStream
  -- If the grid has overhang at our position, try to re-lay in
  -- the next position.
  | o :: RowSpan
o:os :: [RowSpan]
os <- [RowSpan]
oldHang
  , RowSpan
o RowSpan -> RowSpan -> Bool
forall a. Ord a => a -> a -> Bool
> 1 = let (newHang :: [RowSpan]
newHang, newCell :: [Cell]
newCell, cellStream' :: [Cell]
cellStream') = [RowSpan] -> [Cell] -> ([RowSpan], [Cell], [Cell])
placeRowSection [RowSpan]
os [Cell]
cellStream
            in (RowSpan
o RowSpan -> RowSpan -> RowSpan
forall a. Num a => a -> a -> a
- 1 RowSpan -> [RowSpan] -> [RowSpan]
forall a. a -> [a] -> [a]
: [RowSpan]
newHang, [Cell]
newCell, [Cell]
cellStream')
  -- Otherwise if there is any available width, place the cell and
  -- continue.
  | c :: Cell
c:cellStream' :: [Cell]
cellStream' <- [Cell]
cellStream
  , (h :: RowSpan
h, w :: ColSpan
w) <- Cell -> (RowSpan, ColSpan)
getDim Cell
c
  , ColSpan
w' <- ColSpan -> ColSpan -> ColSpan
forall a. Ord a => a -> a -> a
max 1 ColSpan
w
  , (n :: Int
n, oldHang' :: [RowSpan]
oldHang') <- (RowSpan -> Bool) -> Int -> [RowSpan] -> (Int, [RowSpan])
forall a. (a -> Bool) -> Int -> [a] -> (Int, [a])
dropAtMostWhile (RowSpan -> RowSpan -> Bool
forall a. Eq a => a -> a -> Bool
== 1) (ColSpan -> Int
getColSpan ColSpan
w') [RowSpan]
oldHang
  , Int
n Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
> 0
  = let w'' :: ColSpan
w'' = ColSpan -> ColSpan -> ColSpan
forall a. Ord a => a -> a -> a
min (Int -> ColSpan
ColSpan Int
n) ColSpan
w'
        c' :: Cell
c' = ColSpan -> Cell -> Cell
setW ColSpan
w'' Cell
c
        (newHang :: [RowSpan]
newHang, newCell :: [Cell]
newCell, remainCell :: [Cell]
remainCell) = [RowSpan] -> [Cell] -> ([RowSpan], [Cell], [Cell])
placeRowSection [RowSpan]
oldHang' [Cell]
cellStream'
    in (Int -> RowSpan -> [RowSpan]
forall a. Int -> a -> [a]
replicate (ColSpan -> Int
getColSpan ColSpan
w'') RowSpan
h [RowSpan] -> [RowSpan] -> [RowSpan]
forall a. Semigroup a => a -> a -> a
<> [RowSpan]
newHang, Cell
c' Cell -> [Cell] -> [Cell]
forall a. a -> [a] -> [a]
: [Cell]
newCell, [Cell]
remainCell)
  -- Otherwise there is no room in the section, or not enough cells
  -- were given.
  | Bool
otherwise = ([], [], [Cell]
cellStream)
  where
    getColSpan :: ColSpan -> Int
getColSpan (ColSpan w :: Int
w) = Int
w
    getDim :: Cell -> (RowSpan, ColSpan)
getDim (Cell _ _ h :: RowSpan
h w :: ColSpan
w _) = (RowSpan
h, ColSpan
w)
    setW :: ColSpan -> Cell -> Cell
setW w :: ColSpan
w (Cell a :: Attr
a ma :: Alignment
ma h :: RowSpan
h _ b :: [Block]
b) = Attr -> Alignment -> RowSpan -> ColSpan -> [Block] -> Cell
Cell Attr
a Alignment
ma RowSpan
h ColSpan
w [Block]
b

    dropAtMostWhile :: (a -> Bool) -> Int -> [a] -> (Int, [a])
    dropAtMostWhile :: (a -> Bool) -> Int -> [a] -> (Int, [a])
dropAtMostWhile p :: a -> Bool
p n :: Int
n = Int -> [a] -> (Int, [a])
go 0
      where
        go :: Int -> [a] -> (Int, [a])
go acc :: Int
acc (l :: a
l:ls :: [a]
ls) | a -> Bool
p a
l Bool -> Bool -> Bool
&& Int
acc Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
< Int
n = Int -> [a] -> (Int, [a])
go (Int
accInt -> Int -> Int
forall a. Num a => a -> a -> a
+1) [a]
ls
        go acc :: Int
acc l :: [a]
l = (Int
acc, [a]
l)

-- | Ensure that the height of each cell in a table section lies
-- between 1 and the distance from its row to the end of the
-- section. So if there were four rows in the input list, the cells in
-- the second row would have their height clamped between 1 and 3.
clipRows :: [Row] -> [Row]
clipRows :: [Row] -> [Row]
clipRows rows :: [Row]
rows
  = let totalHeight :: RowSpan
totalHeight = Int -> RowSpan
RowSpan (Int -> RowSpan) -> Int -> RowSpan
forall a b. (a -> b) -> a -> b
$ [Row] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length [Row]
rows
    in (RowSpan -> Row -> Row) -> [RowSpan] -> [Row] -> [Row]
forall a b c. (a -> b -> c) -> [a] -> [b] -> [c]
zipWith RowSpan -> Row -> Row
clipRowH [RowSpan
totalHeight, RowSpan
totalHeight RowSpan -> RowSpan -> RowSpan
forall a. Num a => a -> a -> a
- 1..1] [Row]
rows
  where
    getH :: Cell -> RowSpan
getH (Cell _ _ h :: RowSpan
h _ _) = RowSpan
h
    setH :: RowSpan -> Cell -> Cell
setH h :: RowSpan
h (Cell a :: Attr
a ma :: Alignment
ma _ w :: ColSpan
w body :: [Block]
body) = Attr -> Alignment -> RowSpan -> ColSpan -> [Block] -> Cell
Cell Attr
a Alignment
ma RowSpan
h ColSpan
w [Block]
body
    clipH :: RowSpan -> RowSpan -> Cell -> Cell
clipH low :: RowSpan
low high :: RowSpan
high c :: Cell
c = let h :: RowSpan
h = Cell -> RowSpan
getH Cell
c in RowSpan -> Cell -> Cell
setH (RowSpan -> RowSpan -> RowSpan
forall a. Ord a => a -> a -> a
min RowSpan
high (RowSpan -> RowSpan) -> RowSpan -> RowSpan
forall a b. (a -> b) -> a -> b
$ RowSpan -> RowSpan -> RowSpan
forall a. Ord a => a -> a -> a
max RowSpan
low RowSpan
h) Cell
c
    clipRowH :: RowSpan -> Row -> Row
clipRowH high :: RowSpan
high (Row attr :: Attr
attr cells :: [Cell]
cells) = Attr -> [Cell] -> Row
Row Attr
attr ([Cell] -> Row) -> [Cell] -> Row
forall a b. (a -> b) -> a -> b
$ (Cell -> Cell) -> [Cell] -> [Cell]
forall a b. (a -> b) -> [a] -> [b]
map (RowSpan -> RowSpan -> Cell -> Cell
clipH 1 RowSpan
high) [Cell]
cells