{-# LANGUAGE FlexibleInstances, MultiParamTypeClasses, DeriveDataTypeable,
    GeneralizedNewtypeDeriving, CPP, StandaloneDeriving, DeriveGeneric,
    DeriveTraversable, OverloadedStrings #-}
{-
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
                           , 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
                           , table
                           , simpleTable
                           , divWith
                           )
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

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 Seq Inline
xs) <> :: Inlines -> Inlines -> Inlines
<> (Many 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
      (ViewR Inline
EmptyR, ViewL Inline
_) -> Seq Inline -> Inlines
forall a. Seq a -> Many a
Many Seq Inline
ys
      (ViewR Inline
_, ViewL Inline
EmptyL) -> Seq Inline -> Inlines
forall a. Seq a -> Many a
Many Seq Inline
xs
      (Seq Inline
xs' :> Inline
x, Inline
y :< 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
                          (Inline
Space, Inline
Space)     -> Seq Inline
xs' Seq Inline -> Inline -> Seq Inline
forall a. Seq a -> a -> Seq a
|> Inline
Space
                          (Inline
Space, Inline
SoftBreak) -> Seq Inline
xs' Seq Inline -> Inline -> Seq Inline
forall a. Seq a -> a -> Seq a
|> Inline
SoftBreak
                          (Inline
SoftBreak, Inline
Space) -> Seq Inline
xs' Seq Inline -> Inline -> Seq Inline
forall a. Seq a -> a -> Seq a
|> Inline
SoftBreak
                          (Str Text
t1, Str 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 [Inline]
i1, Emph [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)
                          (Strong [Inline]
i1, Strong [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 [Inline]
i1, Subscript [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 [Inline]
i1, Superscript [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 [Inline]
i1, Strikeout [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)
                          (Inline
Space, Inline
LineBreak) -> Seq Inline
xs' Seq Inline -> Inline -> Seq Inline
forall a. Seq a -> a -> Seq a
|> Inline
LineBreak
                          (Inline
LineBreak, Inline
Space) -> Seq Inline
xs' Seq Inline -> Inline -> Seq Inline
forall a. Seq a -> a -> Seq a
|> Inline
LineBreak
                          (Inline
SoftBreak, Inline
LineBreak) -> Seq Inline
xs' Seq Inline -> Inline -> Seq Inline
forall a. Seq a -> a -> Seq a
|> Inline
LineBreak
                          (Inline
LineBreak, Inline
SoftBreak) -> Seq Inline
xs' Seq Inline -> Inline -> Seq Inline
forall a. Seq a -> a -> Seq a
|> Inline
LineBreak
                          (Inline
SoftBreak, Inline
SoftBreak) -> Seq Inline
xs' Seq Inline -> Inline -> Seq Inline
forall a. Seq a -> a -> Seq a
|> Inline
SoftBreak
                          (Inline, Inline)
_                  -> 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 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 Inline
Space = Bool
True
        isSp Inline
SoftBreak = Bool
True
        isSp Inline
_ = Bool
False

-- Document builders

doc :: Blocks -> Pandoc
doc :: Blocks -> Pandoc
doc = Meta -> [Block] -> Pandoc
Pandoc Meta
nullMeta ([Block] -> Pandoc) -> (Blocks -> [Block]) -> Blocks -> Pandoc
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Blocks -> [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 :: Blocks -> MetaValue
toMetaValue = [Block] -> MetaValue
MetaBlocks ([Block] -> MetaValue)
-> (Blocks -> [Block]) -> Blocks -> MetaValue
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Blocks -> [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 Text
key b
val (Meta 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 Text
key (Meta 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 Text
key b
val (Pandoc (Meta Map Text MetaValue
ms) [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 Text
key (Pandoc (Meta Map Text MetaValue
ms) [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 Text
"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 Text
"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 Text
"date"

-- Inline list builders

-- | Convert a 'String' 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 Char
x 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 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 Text
xs = Text -> Inline
Str Text
xs
        is_space :: Char -> Bool
is_space Char
' '    = Bool
True
        is_space Char
'\r'   = Bool
True
        is_space Char
'\n'   = Bool
True
        is_space Char
'\t'   = Bool
True
        is_space Char
_      = Bool
False
        is_newline :: Char -> Bool
is_newline Char
'\r' = Bool
True
        is_newline Char
'\n' = Bool
True
        is_newline Char
_    = 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

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 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 [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 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 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 Text
url Text
title 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 Text
url Text
title 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 :: Blocks -> Inlines
note = Inline -> Inlines
forall a. a -> Many a
singleton (Inline -> Inlines) -> (Blocks -> Inline) -> Blocks -> Inlines
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Block] -> Inline
Note ([Block] -> Inline) -> (Blocks -> [Block]) -> Blocks -> Inline
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Blocks -> [Block]
forall a. Many a -> [a]
toList

spanWith :: Attr -> Inlines -> Inlines
spanWith :: Attr -> Inlines -> Inlines
spanWith 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 -> Blocks
para = Block -> Blocks
forall a. a -> Many a
singleton (Block -> Blocks) -> (Inlines -> Block) -> Inlines -> Blocks
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 -> Blocks
plain Inlines
ils = if Inlines -> Bool
forall a. Many a -> Bool
isNull Inlines
ils
               then Blocks
forall a. Monoid a => a
mempty
               else Block -> Blocks
forall a. a -> Many a
singleton (Block -> Blocks) -> (Inlines -> Block) -> Inlines -> Blocks
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 -> Blocks) -> Inlines -> Blocks
forall a b. (a -> b) -> a -> b
$ Inlines
ils

lineBlock :: [Inlines] -> Blocks
lineBlock :: [Inlines] -> Blocks
lineBlock = Block -> Blocks
forall a. a -> Many a
singleton (Block -> Blocks) -> ([Inlines] -> Block) -> [Inlines] -> Blocks
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 -> Blocks
codeBlockWith Attr
attrs = Block -> Blocks
forall a. a -> Many a
singleton (Block -> Blocks) -> (Text -> Block) -> Text -> Blocks
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 -> Blocks
codeBlock = Attr -> Text -> Blocks
codeBlockWith Attr
nullAttr

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

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

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

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

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

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

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

headerWith :: Attr -> Int -> Inlines -> Blocks
headerWith :: Attr -> Int -> Inlines -> Blocks
headerWith Attr
attr Int
level = Block -> Blocks
forall a. a -> Many a
singleton (Block -> Blocks) -> (Inlines -> Block) -> Inlines -> Blocks
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 :: Blocks
horizontalRule = Block -> Blocks
forall a. a -> Many a
singleton Block
HorizontalRule

-- | Table builder. Rows and headers will be padded or truncated to the size of
-- @cellspecs@
table :: Inlines               -- ^ Caption
      -> [(Alignment, Double)] -- ^ Column alignments and fractional widths
      -> [Blocks]              -- ^ Headers
      -> [[Blocks]]            -- ^ Rows
      -> Blocks
table :: Inlines
-> [(Alignment, Double)] -> [Blocks] -> [[Blocks]] -> Blocks
table Inlines
caption [(Alignment, Double)]
cellspecs [Blocks]
headers [[Blocks]]
rows = Block -> Blocks
forall a. a -> Many a
singleton (Block -> Blocks) -> Block -> Blocks
forall a b. (a -> b) -> a -> b
$
  [Inline]
-> [Alignment] -> [Double] -> [[Block]] -> [[[Block]]] -> Block
Table (Inlines -> [Inline]
forall a. Many a -> [a]
toList Inlines
caption) [Alignment]
aligns [Double]
widths ([Blocks] -> [[Block]]
sanitise [Blocks]
headers) (([Blocks] -> [[Block]]) -> [[Blocks]] -> [[[Block]]]
forall a b. (a -> b) -> [a] -> [b]
map [Blocks] -> [[Block]]
sanitise [[Blocks]]
rows)
   where ([Alignment]
aligns, [Double]
widths) = [(Alignment, Double)] -> ([Alignment], [Double])
forall a b. [(a, b)] -> ([a], [b])
unzip [(Alignment, Double)]
cellspecs
         sanitise :: [Blocks] -> [[Block]]
sanitise = (Blocks -> [Block]) -> [Blocks] -> [[Block]]
forall a b. (a -> b) -> [a] -> [b]
map Blocks -> [Block]
forall a. Many a -> [a]
toList ([Blocks] -> [[Block]])
-> ([Blocks] -> [Blocks]) -> [Blocks] -> [[Block]]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Blocks -> Int -> [Blocks] -> [Blocks]
forall a. a -> Int -> [a] -> [a]
pad Blocks
forall a. Monoid a => a
mempty Int
numcols
         numcols :: Int
numcols = [(Alignment, Double)] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length [(Alignment, Double)]
cellspecs
         pad :: a -> Int -> [a] -> [a]
pad a
element Int
upTo [a]
list = Int -> [a] -> [a]
forall a. Int -> [a] -> [a]
take Int
upTo ([a]
list [a] -> [a] -> [a]
forall a. [a] -> [a] -> [a]
++ a -> [a]
forall a. a -> [a]
repeat a
element)

-- | A simple table without a caption.
simpleTable :: [Blocks]   -- ^ Headers
            -> [[Blocks]] -- ^ Rows
            -> Blocks
simpleTable :: [Blocks] -> [[Blocks]] -> Blocks
simpleTable [Blocks]
headers [[Blocks]]
rows =
  Inlines
-> [(Alignment, Double)] -> [Blocks] -> [[Blocks]] -> Blocks
table Inlines
forall a. Monoid a => a
mempty (Int -> (Alignment, Double) -> [(Alignment, Double)]
forall a. Int -> a -> [a]
replicate Int
numcols (Alignment, Double)
defaults) [Blocks]
headers [[Blocks]]
rows
  where defaults :: (Alignment, Double)
defaults = (Alignment
AlignDefault, Double
0)
        numcols :: Int
numcols  = case [Blocks]
headers[Blocks] -> [[Blocks]] -> [[Blocks]]
forall a. a -> [a] -> [a]
:[[Blocks]]
rows of
                        [] -> Int
0
                        [[Blocks]]
xs -> [Int] -> Int
forall (t :: * -> *) a. (Foldable t, Ord a) => t a -> a
maximum (([Blocks] -> Int) -> [[Blocks]] -> [Int]
forall a b. (a -> b) -> [a] -> [b]
map [Blocks] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length [[Blocks]]
xs)

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