{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TypeApplications #-}
module Text.Pandoc.Lua.Marshal.Block
(
peekBlock
, peekBlockFuzzy
, pushBlock
, peekBlocks
, peekBlocksFuzzy
, pushBlocks
, blockConstructors
, mkBlocks
) where
import Control.Applicative ((<|>))
import Control.Monad.Catch (throwM)
import Control.Monad ((<$!>))
import Data.Data (showConstr, toConstr)
import Data.Maybe (fromMaybe)
import Data.Proxy (Proxy (Proxy))
import Data.Text (Text)
import HsLua hiding (Div)
import Text.Pandoc.Lua.Marshal.Attr (peekAttr, pushAttr)
import Text.Pandoc.Lua.Marshal.Content
( Content (..), contentTypeDescription, peekContent, pushContent
, peekDefinitionItem )
import Text.Pandoc.Lua.Marshal.Format (peekFormat, pushFormat)
import Text.Pandoc.Lua.Marshal.Inline (peekInlinesFuzzy)
import Text.Pandoc.Lua.Marshal.List (newListMetatable, pushPandocList)
import Text.Pandoc.Lua.Marshal.ListAttributes (peekListAttributes, pushListAttributes)
import Text.Pandoc.Lua.Marshal.TableParts
( peekCaption, pushCaption
, peekColSpec, pushColSpec
, peekTableBody, pushTableBody
, peekTableFoot, pushTableFoot
, peekTableHead, pushTableHead
)
import Text.Pandoc.Definition
pushBlock :: LuaError e => Pusher e Block
pushBlock :: Pusher e Block
pushBlock = UDTypeWithList e (DocumentedFunction e) Block Void
-> Pusher e Block
forall e fn a itemtype.
LuaError e =>
UDTypeWithList e fn a itemtype -> a -> LuaE e ()
pushUD UDTypeWithList e (DocumentedFunction e) Block Void
forall e. LuaError e => DocumentedType e Block
typeBlock
{-# INLINE pushBlock #-}
peekBlock :: LuaError e => Peeker e Block
peekBlock :: Peeker e Block
peekBlock = UDTypeWithList e (DocumentedFunction e) Block Void
-> Peeker e Block
forall e fn a itemtype.
LuaError e =>
UDTypeWithList e fn a itemtype -> Peeker e a
peekUD UDTypeWithList e (DocumentedFunction e) Block Void
forall e. LuaError e => DocumentedType e Block
typeBlock
{-# INLINE peekBlock #-}
peekBlocks :: LuaError e
=> Peeker e [Block]
peekBlocks :: Peeker e [Block]
peekBlocks = Peeker e Block -> Peeker e [Block]
forall a e. LuaError e => Peeker e a -> Peeker e [a]
peekList Peeker e Block
forall e. LuaError e => Peeker e Block
peekBlock
{-# INLINABLE peekBlocks #-}
pushBlocks :: LuaError e
=> Pusher e [Block]
pushBlocks :: Pusher e [Block]
pushBlocks [Block]
xs = do
Pusher e Block -> Pusher e [Block]
forall e a. LuaError e => Pusher e a -> [a] -> LuaE e ()
pushList Pusher e Block
forall e. LuaError e => Pusher e Block
pushBlock [Block]
xs
Name -> LuaE e () -> LuaE e ()
forall e. Name -> LuaE e () -> LuaE e ()
newListMetatable Name
"Blocks" (LuaE e () -> LuaE e ()) -> LuaE e () -> LuaE e ()
forall a b. (a -> b) -> a -> b
$
() -> LuaE e ()
forall (f :: * -> *) a. Applicative f => a -> f a
pure ()
StackIndex -> LuaE e ()
forall e. StackIndex -> LuaE e ()
setmetatable (CInt -> StackIndex
nth CInt
2)
{-# INLINABLE pushBlocks #-}
peekBlockFuzzy :: LuaError e
=> Peeker e Block
peekBlockFuzzy :: Peeker e Block
peekBlockFuzzy = [Peeker e Block] -> Peeker e Block
forall e a. LuaError e => [Peeker e a] -> Peeker e a
choice
[ Peeker e Block
forall e. LuaError e => Peeker e Block
peekBlock
, \StackIndex
idx -> [Inline] -> Block
Plain ([Inline] -> Block) -> Peek e [Inline] -> Peek e Block
forall (m :: * -> *) a b. Monad m => (a -> b) -> m a -> m b
<$!> Peeker e [Inline]
forall e. LuaError e => Peeker e [Inline]
peekInlinesFuzzy StackIndex
idx
]
{-# INLINABLE peekBlockFuzzy #-}
peekBlocksFuzzy :: LuaError e
=> Peeker e [Block]
peekBlocksFuzzy :: Peeker e [Block]
peekBlocksFuzzy = [Peeker e [Block]] -> Peeker e [Block]
forall e a. LuaError e => [Peeker e a] -> Peeker e a
choice
[ Peeker e Block -> Peeker e [Block]
forall a e. LuaError e => Peeker e a -> Peeker e [a]
peekList Peeker e Block
forall e. LuaError e => Peeker e Block
peekBlockFuzzy
, (Block -> [Block]) -> Peek e Block -> Peek e [Block]
forall (m :: * -> *) a b. Monad m => (a -> b) -> m a -> m b
(<$!>) Block -> [Block]
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Peek e Block -> Peek e [Block])
-> Peeker e Block -> Peeker e [Block]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Peeker e Block
forall e. LuaError e => Peeker e Block
peekBlockFuzzy
]
{-# INLINABLE peekBlocksFuzzy #-}
typeBlock :: forall e. LuaError e => DocumentedType e Block
typeBlock :: DocumentedType e Block
typeBlock = Name
-> [(Operation, DocumentedFunction e)]
-> [Member e (DocumentedFunction e) Block]
-> DocumentedType e Block
forall e a.
LuaError e =>
Name
-> [(Operation, DocumentedFunction e)]
-> [Member e (DocumentedFunction e) a]
-> DocumentedType e a
deftype Name
"Block"
[ Operation
-> DocumentedFunction e -> (Operation, DocumentedFunction e)
forall e.
Operation
-> DocumentedFunction e -> (Operation, DocumentedFunction e)
operation Operation
Eq (DocumentedFunction e -> (Operation, DocumentedFunction e))
-> DocumentedFunction e -> (Operation, DocumentedFunction e)
forall a b. (a -> b) -> a -> b
$ (Block -> Block -> LuaE e Bool)
-> HsFnPrecursor e (Block -> Block -> LuaE e Bool)
forall a e. a -> HsFnPrecursor e a
lambda
### liftPure2 (==)
HsFnPrecursor e (Block -> Block -> LuaE e Bool)
-> Parameter e Block -> HsFnPrecursor e (Block -> LuaE e Bool)
forall e a b.
HsFnPrecursor e (a -> b) -> Parameter e a -> HsFnPrecursor e b
<#> Peeker e Block -> Text -> Text -> Text -> Parameter e Block
forall e a. Peeker e a -> Text -> Text -> Text -> Parameter e a
parameter Peeker e Block
forall e. LuaError e => Peeker e Block
peekBlockFuzzy Text
"Block" Text
"a" Text
""
HsFnPrecursor e (Block -> LuaE e Bool)
-> Parameter e Block -> HsFnPrecursor e (LuaE e Bool)
forall e a b.
HsFnPrecursor e (a -> b) -> Parameter e a -> HsFnPrecursor e b
<#> Peeker e Block -> Text -> Text -> Text -> Parameter e Block
forall e a. Peeker e a -> Text -> Text -> Text -> Parameter e a
parameter Peeker e Block
forall e. LuaError e => Peeker e Block
peekBlockFuzzy Text
"Block" Text
"b" Text
""
HsFnPrecursor e (LuaE e Bool)
-> FunctionResults e Bool -> DocumentedFunction e
forall e a.
HsFnPrecursor e (LuaE e a)
-> FunctionResults e a -> DocumentedFunction e
=#> Text -> FunctionResults e Bool
forall e. Text -> FunctionResults e Bool
boolResult Text
"whether the two values are equal"
, Operation
-> DocumentedFunction e -> (Operation, DocumentedFunction e)
forall e.
Operation
-> DocumentedFunction e -> (Operation, DocumentedFunction e)
operation Operation
Tostring (DocumentedFunction e -> (Operation, DocumentedFunction e))
-> DocumentedFunction e -> (Operation, DocumentedFunction e)
forall a b. (a -> b) -> a -> b
$ (Block -> LuaE e String)
-> HsFnPrecursor e (Block -> LuaE e String)
forall a e. a -> HsFnPrecursor e a
lambda
### liftPure show
HsFnPrecursor e (Block -> LuaE e String)
-> Parameter e Block -> HsFnPrecursor e (LuaE e String)
forall e a b.
HsFnPrecursor e (a -> b) -> Parameter e a -> HsFnPrecursor e b
<#> DocumentedType e Block -> Text -> Text -> Parameter e Block
forall e a itemtype.
LuaError e =>
DocumentedTypeWithList e a itemtype
-> Text -> Text -> Parameter e a
udparam DocumentedType e Block
forall e. LuaError e => DocumentedType e Block
typeBlock Text
"self" Text
""
HsFnPrecursor e (LuaE e String)
-> FunctionResults e String -> DocumentedFunction e
forall e a.
HsFnPrecursor e (LuaE e a)
-> FunctionResults e a -> DocumentedFunction e
=#> Pusher e String -> Text -> Text -> FunctionResults e String
forall e a. Pusher e a -> Text -> Text -> FunctionResults e a
functionResult Pusher e String
forall e. String -> LuaE e ()
pushString Text
"string" Text
"Haskell representation"
]
[ Name
-> Text
-> (Pusher e Attr, Block -> Possible Attr)
-> (Peeker e Attr, Block -> Attr -> Possible Block)
-> Member e (DocumentedFunction e) Block
forall e b a fn.
LuaError e =>
Name
-> Text
-> (Pusher e b, a -> Possible b)
-> (Peeker e b, a -> b -> Possible a)
-> Member e fn a
possibleProperty Name
"attr" Text
"element attributes"
(Pusher e Attr
forall e. LuaError e => Pusher e Attr
pushAttr, \case
CodeBlock Attr
attr Text
_ -> Attr -> Possible Attr
forall a. a -> Possible a
Actual Attr
attr
Div Attr
attr [Block]
_ -> Attr -> Possible Attr
forall a. a -> Possible a
Actual Attr
attr
Header Int
_ Attr
attr [Inline]
_ -> Attr -> Possible Attr
forall a. a -> Possible a
Actual Attr
attr
Table Attr
attr Caption
_ [ColSpec]
_ TableHead
_ [TableBody]
_ TableFoot
_ -> Attr -> Possible Attr
forall a. a -> Possible a
Actual Attr
attr
Block
_ -> Possible Attr
forall a. Possible a
Absent)
(Peeker e Attr
forall e. LuaError e => Peeker e Attr
peekAttr, \case
CodeBlock Attr
_ Text
code -> Block -> Possible Block
forall a. a -> Possible a
Actual (Block -> Possible Block)
-> (Attr -> Block) -> Attr -> Possible Block
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Attr -> Text -> Block) -> Text -> Attr -> Block
forall a b c. (a -> b -> c) -> b -> a -> c
flip Attr -> Text -> Block
CodeBlock Text
code
Div Attr
_ [Block]
blks -> Block -> Possible Block
forall a. a -> Possible a
Actual (Block -> Possible Block)
-> (Attr -> Block) -> Attr -> Possible Block
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Attr -> [Block] -> Block) -> [Block] -> Attr -> Block
forall a b c. (a -> b -> c) -> b -> a -> c
flip Attr -> [Block] -> Block
Div [Block]
blks
Header Int
lvl Attr
_ [Inline]
blks -> Block -> Possible Block
forall a. a -> Possible a
Actual (Block -> Possible Block)
-> (Attr -> Block) -> Attr -> Possible Block
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (\Attr
attr -> Int -> Attr -> [Inline] -> Block
Header Int
lvl Attr
attr [Inline]
blks)
Table Attr
_ Caption
c [ColSpec]
cs TableHead
h [TableBody]
bs TableFoot
f -> Block -> Possible Block
forall a. a -> Possible a
Actual (Block -> Possible Block)
-> (Attr -> Block) -> Attr -> Possible Block
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (\Attr
attr -> Attr
-> Caption
-> [ColSpec]
-> TableHead
-> [TableBody]
-> TableFoot
-> Block
Table Attr
attr Caption
c [ColSpec]
cs TableHead
h [TableBody]
bs TableFoot
f)
Block
_ -> Possible Block -> Attr -> Possible Block
forall a b. a -> b -> a
const Possible Block
forall a. Possible a
Absent)
, Name
-> Text
-> (Pusher e [TableBody], Block -> Possible [TableBody])
-> (Peeker e [TableBody], Block -> [TableBody] -> Possible Block)
-> Member e (DocumentedFunction e) Block
forall e b a fn.
LuaError e =>
Name
-> Text
-> (Pusher e b, a -> Possible b)
-> (Peeker e b, a -> b -> Possible a)
-> Member e fn a
possibleProperty Name
"bodies" Text
"table bodies"
(Pusher e TableBody -> Pusher e [TableBody]
forall e a. LuaError e => Pusher e a -> [a] -> LuaE e ()
pushPandocList Pusher e TableBody
forall e. LuaError e => Pusher e TableBody
pushTableBody, \case
Table Attr
_ Caption
_ [ColSpec]
_ TableHead
_ [TableBody]
bs TableFoot
_ -> [TableBody] -> Possible [TableBody]
forall a. a -> Possible a
Actual [TableBody]
bs
Block
_ -> Possible [TableBody]
forall a. Possible a
Absent)
(Peeker e TableBody -> Peeker e [TableBody]
forall a e. LuaError e => Peeker e a -> Peeker e [a]
peekList Peeker e TableBody
forall e. LuaError e => Peeker e TableBody
peekTableBody, \case
Table Attr
attr Caption
c [ColSpec]
cs TableHead
h [TableBody]
_ TableFoot
f -> Block -> Possible Block
forall a. a -> Possible a
Actual (Block -> Possible Block)
-> ([TableBody] -> Block) -> [TableBody] -> Possible Block
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (\[TableBody]
bs -> Attr
-> Caption
-> [ColSpec]
-> TableHead
-> [TableBody]
-> TableFoot
-> Block
Table Attr
attr Caption
c [ColSpec]
cs TableHead
h [TableBody]
bs TableFoot
f)
Block
_ -> Possible Block -> [TableBody] -> Possible Block
forall a b. a -> b -> a
const Possible Block
forall a. Possible a
Absent)
, Name
-> Text
-> (Pusher e Caption, Block -> Possible Caption)
-> (Peeker e Caption, Block -> Caption -> Possible Block)
-> Member e (DocumentedFunction e) Block
forall e b a fn.
LuaError e =>
Name
-> Text
-> (Pusher e b, a -> Possible b)
-> (Peeker e b, a -> b -> Possible a)
-> Member e fn a
possibleProperty Name
"caption" Text
"element caption"
(Pusher e Caption
forall e. LuaError e => Caption -> LuaE e ()
pushCaption, \case {Table Attr
_ Caption
capt [ColSpec]
_ TableHead
_ [TableBody]
_ TableFoot
_ -> Caption -> Possible Caption
forall a. a -> Possible a
Actual Caption
capt; Block
_ -> Possible Caption
forall a. Possible a
Absent})
(Peeker e Caption
forall e. LuaError e => Peeker e Caption
peekCaption, \case
Table Attr
attr Caption
_ [ColSpec]
cs TableHead
h [TableBody]
bs TableFoot
f -> Block -> Possible Block
forall a. a -> Possible a
Actual (Block -> Possible Block)
-> (Caption -> Block) -> Caption -> Possible Block
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (\Caption
c -> Attr
-> Caption
-> [ColSpec]
-> TableHead
-> [TableBody]
-> TableFoot
-> Block
Table Attr
attr Caption
c [ColSpec]
cs TableHead
h [TableBody]
bs TableFoot
f)
Block
_ -> Possible Block -> Caption -> Possible Block
forall a b. a -> b -> a
const Possible Block
forall a. Possible a
Absent)
, Name
-> Text
-> (Pusher e [ColSpec], Block -> Possible [ColSpec])
-> (Peeker e [ColSpec], Block -> [ColSpec] -> Possible Block)
-> Member e (DocumentedFunction e) Block
forall e b a fn.
LuaError e =>
Name
-> Text
-> (Pusher e b, a -> Possible b)
-> (Peeker e b, a -> b -> Possible a)
-> Member e fn a
possibleProperty Name
"colspecs" Text
"column alignments and widths"
(Pusher e ColSpec -> Pusher e [ColSpec]
forall e a. LuaError e => Pusher e a -> [a] -> LuaE e ()
pushPandocList Pusher e ColSpec
forall e. LuaError e => Pusher e ColSpec
pushColSpec, \case
Table Attr
_ Caption
_ [ColSpec]
cs TableHead
_ [TableBody]
_ TableFoot
_ -> [ColSpec] -> Possible [ColSpec]
forall a. a -> Possible a
Actual [ColSpec]
cs
Block
_ -> Possible [ColSpec]
forall a. Possible a
Absent)
(Peeker e ColSpec -> Peeker e [ColSpec]
forall a e. LuaError e => Peeker e a -> Peeker e [a]
peekList Peeker e ColSpec
forall e. LuaError e => Peeker e ColSpec
peekColSpec, \case
Table Attr
attr Caption
c [ColSpec]
_ TableHead
h [TableBody]
bs TableFoot
f -> Block -> Possible Block
forall a. a -> Possible a
Actual (Block -> Possible Block)
-> ([ColSpec] -> Block) -> [ColSpec] -> Possible Block
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (\[ColSpec]
cs -> Attr
-> Caption
-> [ColSpec]
-> TableHead
-> [TableBody]
-> TableFoot
-> Block
Table Attr
attr Caption
c [ColSpec]
cs TableHead
h [TableBody]
bs TableFoot
f)
Block
_ -> Possible Block -> [ColSpec] -> Possible Block
forall a b. a -> b -> a
const Possible Block
forall a. Possible a
Absent)
, Name
-> Text
-> (Pusher e Content, Block -> Possible Content)
-> (Peeker e Content, Block -> Content -> Possible Block)
-> Member e (DocumentedFunction e) Block
forall e b a fn.
LuaError e =>
Name
-> Text
-> (Pusher e b, a -> Possible b)
-> (Peeker e b, a -> b -> Possible a)
-> Member e fn a
possibleProperty Name
"content" Text
"element content"
(Pusher e Content
forall e. LuaError e => Pusher e Content
pushContent, Block -> Possible Content
getBlockContent)
(Peeker e Content
forall e. LuaError e => Peeker e Content
peekContent, Proxy e -> Block -> Content -> Possible Block
forall e.
LuaError e =>
Proxy e -> Block -> Content -> Possible Block
setBlockContent (Proxy e
forall k (t :: k). Proxy t
Proxy @e))
, Name
-> Text
-> (Pusher e TableFoot, Block -> Possible TableFoot)
-> (Peeker e TableFoot, Block -> TableFoot -> Possible Block)
-> Member e (DocumentedFunction e) Block
forall e b a fn.
LuaError e =>
Name
-> Text
-> (Pusher e b, a -> Possible b)
-> (Peeker e b, a -> b -> Possible a)
-> Member e fn a
possibleProperty Name
"foot" Text
"table foot"
(Pusher e TableFoot
forall e. LuaError e => Pusher e TableFoot
pushTableFoot, \case {Table Attr
_ Caption
_ [ColSpec]
_ TableHead
_ [TableBody]
_ TableFoot
f -> TableFoot -> Possible TableFoot
forall a. a -> Possible a
Actual TableFoot
f; Block
_ -> Possible TableFoot
forall a. Possible a
Absent})
(Peeker e TableFoot
forall e. LuaError e => Peeker e TableFoot
peekTableFoot, \case
Table Attr
attr Caption
c [ColSpec]
cs TableHead
h [TableBody]
bs TableFoot
_ -> Block -> Possible Block
forall a. a -> Possible a
Actual (Block -> Possible Block)
-> (TableFoot -> Block) -> TableFoot -> Possible Block
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Attr
-> Caption
-> [ColSpec]
-> TableHead
-> [TableBody]
-> TableFoot
-> Block
Table Attr
attr Caption
c [ColSpec]
cs TableHead
h [TableBody]
bs
Block
_ -> Possible Block -> TableFoot -> Possible Block
forall a b. a -> b -> a
const Possible Block
forall a. Possible a
Absent)
, Name
-> Text
-> (Pusher e Format, Block -> Possible Format)
-> (Peeker e Format, Block -> Format -> Possible Block)
-> Member e (DocumentedFunction e) Block
forall e b a fn.
LuaError e =>
Name
-> Text
-> (Pusher e b, a -> Possible b)
-> (Peeker e b, a -> b -> Possible a)
-> Member e fn a
possibleProperty Name
"format" Text
"format of raw content"
(Pusher e Format
forall e. Pusher e Format
pushFormat, \case {RawBlock Format
f Text
_ -> Format -> Possible Format
forall a. a -> Possible a
Actual Format
f; Block
_ -> Possible Format
forall a. Possible a
Absent})
(Peeker e Format
forall e. Peeker e Format
peekFormat, \case
RawBlock Format
_ Text
txt -> Block -> Possible Block
forall a. a -> Possible a
Actual (Block -> Possible Block)
-> (Format -> Block) -> Format -> Possible Block
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Format -> Text -> Block
`RawBlock` Text
txt)
Block
_ -> Possible Block -> Format -> Possible Block
forall a b. a -> b -> a
const Possible Block
forall a. Possible a
Absent)
, Name
-> Text
-> (Pusher e TableHead, Block -> Possible TableHead)
-> (Peeker e TableHead, Block -> TableHead -> Possible Block)
-> Member e (DocumentedFunction e) Block
forall e b a fn.
LuaError e =>
Name
-> Text
-> (Pusher e b, a -> Possible b)
-> (Peeker e b, a -> b -> Possible a)
-> Member e fn a
possibleProperty Name
"head" Text
"table head"
(Pusher e TableHead
forall e. LuaError e => Pusher e TableHead
pushTableHead, \case {Table Attr
_ Caption
_ [ColSpec]
_ TableHead
h [TableBody]
_ TableFoot
_ -> TableHead -> Possible TableHead
forall a. a -> Possible a
Actual TableHead
h; Block
_ -> Possible TableHead
forall a. Possible a
Absent})
(Peeker e TableHead
forall e. LuaError e => Peeker e TableHead
peekTableHead, \case
Table Attr
attr Caption
c [ColSpec]
cs TableHead
_ [TableBody]
bs TableFoot
f -> Block -> Possible Block
forall a. a -> Possible a
Actual (Block -> Possible Block)
-> (TableHead -> Block) -> TableHead -> Possible Block
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (\TableHead
h -> Attr
-> Caption
-> [ColSpec]
-> TableHead
-> [TableBody]
-> TableFoot
-> Block
Table Attr
attr Caption
c [ColSpec]
cs TableHead
h [TableBody]
bs TableFoot
f)
Block
_ -> Possible Block -> TableHead -> Possible Block
forall a b. a -> b -> a
const Possible Block
forall a. Possible a
Absent)
, Name
-> Text
-> (Pusher e Int, Block -> Possible Int)
-> (Peeker e Int, Block -> Int -> Possible Block)
-> Member e (DocumentedFunction e) Block
forall e b a fn.
LuaError e =>
Name
-> Text
-> (Pusher e b, a -> Possible b)
-> (Peeker e b, a -> b -> Possible a)
-> Member e fn a
possibleProperty Name
"level" Text
"heading level"
(Pusher e Int
forall a e. (Integral a, Show a) => a -> LuaE e ()
pushIntegral, \case {Header Int
lvl Attr
_ [Inline]
_ -> Int -> Possible Int
forall a. a -> Possible a
Actual Int
lvl; Block
_ -> Possible Int
forall a. Possible a
Absent})
(Peeker e Int
forall a e. (Integral a, Read a) => Peeker e a
peekIntegral, \case
Header Int
_ Attr
attr [Inline]
inlns -> Block -> Possible Block
forall a. a -> Possible a
Actual (Block -> Possible Block)
-> (Int -> Block) -> Int -> Possible Block
forall b c a. (b -> c) -> (a -> b) -> a -> c
. \Int
lvl -> Int -> Attr -> [Inline] -> Block
Header Int
lvl Attr
attr [Inline]
inlns
Block
_ -> Possible Block -> Int -> Possible Block
forall a b. a -> b -> a
const Possible Block
forall a. Possible a
Absent)
, Name
-> Text
-> (Pusher e ListAttributes, Block -> Possible ListAttributes)
-> (Peeker e ListAttributes,
Block -> ListAttributes -> Possible Block)
-> Member e (DocumentedFunction e) Block
forall e b a fn.
LuaError e =>
Name
-> Text
-> (Pusher e b, a -> Possible b)
-> (Peeker e b, a -> b -> Possible a)
-> Member e fn a
possibleProperty Name
"listAttributes" Text
"ordered list attributes"
(Pusher e ListAttributes
forall e. LuaError e => Pusher e ListAttributes
pushListAttributes, \case
OrderedList ListAttributes
listAttr [[Block]]
_ -> ListAttributes -> Possible ListAttributes
forall a. a -> Possible a
Actual ListAttributes
listAttr
Block
_ -> Possible ListAttributes
forall a. Possible a
Absent)
(Peeker e ListAttributes
forall e. LuaError e => Peeker e ListAttributes
peekListAttributes, \case
OrderedList ListAttributes
_ [[Block]]
content -> Block -> Possible Block
forall a. a -> Possible a
Actual (Block -> Possible Block)
-> (ListAttributes -> Block) -> ListAttributes -> Possible Block
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (ListAttributes -> [[Block]] -> Block
`OrderedList` [[Block]]
content)
Block
_ -> Possible Block -> ListAttributes -> Possible Block
forall a b. a -> b -> a
const Possible Block
forall a. Possible a
Absent)
, Name
-> Text
-> (Pusher e Text, Block -> Possible Text)
-> (Peeker e Text, Block -> Text -> Possible Block)
-> Member e (DocumentedFunction e) Block
forall e b a fn.
LuaError e =>
Name
-> Text
-> (Pusher e b, a -> Possible b)
-> (Peeker e b, a -> b -> Possible a)
-> Member e fn a
possibleProperty Name
"text" Text
"text contents"
(Pusher e Text
forall e. Pusher e Text
pushText, Block -> Possible Text
getBlockText)
(Peeker e Text
forall e. Peeker e Text
peekText, Block -> Text -> Possible Block
setBlockText)
, Name
-> Text
-> (Pusher e String, Block -> String)
-> Member e (DocumentedFunction e) Block
forall e b a fn.
Name -> Text -> (Pusher e b, a -> b) -> Member e fn a
readonly Name
"tag" Text
"type of Block"
(Pusher e String
forall e. String -> LuaE e ()
pushString, Constr -> String
showConstr (Constr -> String) -> (Block -> Constr) -> Block -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Block -> Constr
forall a. Data a => a -> Constr
toConstr )
, Name
-> Text -> [AliasIndex] -> Member e (DocumentedFunction e) Block
forall e fn a. Name -> Text -> [AliasIndex] -> Member e fn a
alias Name
"t" Text
"tag" [AliasIndex
"tag"]
, Name
-> Text -> [AliasIndex] -> Member e (DocumentedFunction e) Block
forall e fn a. Name -> Text -> [AliasIndex] -> Member e fn a
alias Name
"c" Text
"content" [AliasIndex
"content"]
, Name
-> Text -> [AliasIndex] -> Member e (DocumentedFunction e) Block
forall e fn a. Name -> Text -> [AliasIndex] -> Member e fn a
alias Name
"identifier" Text
"element identifier" [AliasIndex
"attr", AliasIndex
"identifier"]
, Name
-> Text -> [AliasIndex] -> Member e (DocumentedFunction e) Block
forall e fn a. Name -> Text -> [AliasIndex] -> Member e fn a
alias Name
"classes" Text
"element classes" [AliasIndex
"attr", AliasIndex
"classes"]
, Name
-> Text -> [AliasIndex] -> Member e (DocumentedFunction e) Block
forall e fn a. Name -> Text -> [AliasIndex] -> Member e fn a
alias Name
"attributes" Text
"other element attributes" [AliasIndex
"attr", AliasIndex
"attributes"]
, Name
-> Text -> [AliasIndex] -> Member e (DocumentedFunction e) Block
forall e fn a. Name -> Text -> [AliasIndex] -> Member e fn a
alias Name
"start" Text
"ordered list start number" [AliasIndex
"listAttributes", AliasIndex
"start"]
, Name
-> Text -> [AliasIndex] -> Member e (DocumentedFunction e) Block
forall e fn a. Name -> Text -> [AliasIndex] -> Member e fn a
alias Name
"style" Text
"ordered list style" [AliasIndex
"listAttributes", AliasIndex
"style"]
, Name
-> Text -> [AliasIndex] -> Member e (DocumentedFunction e) Block
forall e fn a. Name -> Text -> [AliasIndex] -> Member e fn a
alias Name
"delimiter" Text
"numbering delimiter" [AliasIndex
"listAttributes", AliasIndex
"delimiter"]
, DocumentedFunction e -> Member e (DocumentedFunction e) Block
forall e a.
DocumentedFunction e -> Member e (DocumentedFunction e) a
method (DocumentedFunction e -> Member e (DocumentedFunction e) Block)
-> DocumentedFunction e -> Member e (DocumentedFunction e) Block
forall a b. (a -> b) -> a -> b
$ Name
-> (Block -> LuaE e Block)
-> HsFnPrecursor e (Block -> LuaE e Block)
forall a e. Name -> a -> HsFnPrecursor e a
defun Name
"clone"
### return
HsFnPrecursor e (Block -> LuaE e Block)
-> Parameter e Block -> HsFnPrecursor e (LuaE e Block)
forall e a b.
HsFnPrecursor e (a -> b) -> Parameter e a -> HsFnPrecursor e b
<#> Peeker e Block -> Text -> Text -> Text -> Parameter e Block
forall e a. Peeker e a -> Text -> Text -> Text -> Parameter e a
parameter Peeker e Block
forall e. LuaError e => Peeker e Block
peekBlock Text
"Block" Text
"block" Text
"self"
HsFnPrecursor e (LuaE e Block)
-> FunctionResults e Block -> DocumentedFunction e
forall e a.
HsFnPrecursor e (LuaE e a)
-> FunctionResults e a -> DocumentedFunction e
=#> Pusher e Block -> Text -> Text -> FunctionResults e Block
forall e a. Pusher e a -> Text -> Text -> FunctionResults e a
functionResult Pusher e Block
forall e. LuaError e => Pusher e Block
pushBlock Text
"Block" Text
"cloned Block"
, DocumentedFunction e -> Member e (DocumentedFunction e) Block
forall e a.
DocumentedFunction e -> Member e (DocumentedFunction e) a
method (DocumentedFunction e -> Member e (DocumentedFunction e) Block)
-> DocumentedFunction e -> Member e (DocumentedFunction e) Block
forall a b. (a -> b) -> a -> b
$ Name
-> (Block -> LuaE e String)
-> HsFnPrecursor e (Block -> LuaE e String)
forall a e. Name -> a -> HsFnPrecursor e a
defun Name
"show"
### liftPure show
HsFnPrecursor e (Block -> LuaE e String)
-> Parameter e Block -> HsFnPrecursor e (LuaE e String)
forall e a b.
HsFnPrecursor e (a -> b) -> Parameter e a -> HsFnPrecursor e b
<#> Peeker e Block -> Text -> Text -> Text -> Parameter e Block
forall e a. Peeker e a -> Text -> Text -> Text -> Parameter e a
parameter Peeker e Block
forall e. LuaError e => Peeker e Block
peekBlock Text
"Block" Text
"self" Text
""
HsFnPrecursor e (LuaE e String)
-> FunctionResults e String -> DocumentedFunction e
forall e a.
HsFnPrecursor e (LuaE e a)
-> FunctionResults e a -> DocumentedFunction e
=#> Pusher e String -> Text -> Text -> FunctionResults e String
forall e a. Pusher e a -> Text -> Text -> FunctionResults e a
functionResult Pusher e String
forall e. String -> LuaE e ()
pushString Text
"string" Text
"Haskell string representation"
]
where
boolResult :: Text -> FunctionResults e Bool
boolResult = Pusher e Bool -> Text -> Text -> FunctionResults e Bool
forall e a. Pusher e a -> Text -> Text -> FunctionResults e a
functionResult Pusher e Bool
forall e. Pusher e Bool
pushBool Text
"boolean"
getBlockContent :: Block -> Possible Content
getBlockContent :: Block -> Possible Content
getBlockContent = \case
Para [Inline]
inlns -> Content -> Possible Content
forall a. a -> Possible a
Actual (Content -> Possible Content) -> Content -> Possible Content
forall a b. (a -> b) -> a -> b
$ [Inline] -> Content
ContentInlines [Inline]
inlns
Plain [Inline]
inlns -> Content -> Possible Content
forall a. a -> Possible a
Actual (Content -> Possible Content) -> Content -> Possible Content
forall a b. (a -> b) -> a -> b
$ [Inline] -> Content
ContentInlines [Inline]
inlns
Header Int
_ Attr
_ [Inline]
inlns -> Content -> Possible Content
forall a. a -> Possible a
Actual (Content -> Possible Content) -> Content -> Possible Content
forall a b. (a -> b) -> a -> b
$ [Inline] -> Content
ContentInlines [Inline]
inlns
BlockQuote [Block]
blks -> Content -> Possible Content
forall a. a -> Possible a
Actual (Content -> Possible Content) -> Content -> Possible Content
forall a b. (a -> b) -> a -> b
$ [Block] -> Content
ContentBlocks [Block]
blks
Div Attr
_ [Block]
blks -> Content -> Possible Content
forall a. a -> Possible a
Actual (Content -> Possible Content) -> Content -> Possible Content
forall a b. (a -> b) -> a -> b
$ [Block] -> Content
ContentBlocks [Block]
blks
LineBlock [[Inline]]
lns -> Content -> Possible Content
forall a. a -> Possible a
Actual (Content -> Possible Content) -> Content -> Possible Content
forall a b. (a -> b) -> a -> b
$ [[Inline]] -> Content
ContentLines [[Inline]]
lns
BulletList [[Block]]
itms -> Content -> Possible Content
forall a. a -> Possible a
Actual (Content -> Possible Content) -> Content -> Possible Content
forall a b. (a -> b) -> a -> b
$ [[Block]] -> Content
ContentListItems [[Block]]
itms
OrderedList ListAttributes
_ [[Block]]
itms -> Content -> Possible Content
forall a. a -> Possible a
Actual (Content -> Possible Content) -> Content -> Possible Content
forall a b. (a -> b) -> a -> b
$ [[Block]] -> Content
ContentListItems [[Block]]
itms
DefinitionList [([Inline], [[Block]])]
itms -> Content -> Possible Content
forall a. a -> Possible a
Actual (Content -> Possible Content) -> Content -> Possible Content
forall a b. (a -> b) -> a -> b
$ [([Inline], [[Block]])] -> Content
ContentDefItems [([Inline], [[Block]])]
itms
Block
_ -> Possible Content
forall a. Possible a
Absent
setBlockContent :: forall e. LuaError e
=> Proxy e -> Block -> Content -> Possible Block
setBlockContent :: Proxy e -> Block -> Content -> Possible Block
setBlockContent Proxy e
_ = \case
Para [Inline]
_ -> Block -> Possible Block
forall a. a -> Possible a
Actual (Block -> Possible Block)
-> (Content -> Block) -> Content -> Possible Block
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Inline] -> Block
Para ([Inline] -> Block) -> (Content -> [Inline]) -> Content -> Block
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Content -> [Inline]
inlineContent
Plain [Inline]
_ -> Block -> Possible Block
forall a. a -> Possible a
Actual (Block -> Possible Block)
-> (Content -> Block) -> Content -> Possible Block
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Inline] -> Block
Plain ([Inline] -> Block) -> (Content -> [Inline]) -> Content -> Block
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Content -> [Inline]
inlineContent
Header Int
attr Attr
lvl [Inline]
_ -> Block -> Possible Block
forall a. a -> Possible a
Actual (Block -> Possible Block)
-> (Content -> Block) -> Content -> Possible Block
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> Attr -> [Inline] -> Block
Header Int
attr Attr
lvl ([Inline] -> Block) -> (Content -> [Inline]) -> Content -> Block
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Content -> [Inline]
inlineContent
BlockQuote [Block]
_ -> Block -> Possible Block
forall a. a -> Possible a
Actual (Block -> Possible Block)
-> (Content -> Block) -> Content -> Possible Block
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Block] -> Block
BlockQuote ([Block] -> Block) -> (Content -> [Block]) -> Content -> Block
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Content -> [Block]
blockContent
Div Attr
attr [Block]
_ -> Block -> Possible Block
forall a. a -> Possible a
Actual (Block -> Possible Block)
-> (Content -> Block) -> Content -> Possible Block
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Attr -> [Block] -> Block
Div Attr
attr ([Block] -> Block) -> (Content -> [Block]) -> Content -> Block
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Content -> [Block]
blockContent
LineBlock [[Inline]]
_ -> Block -> Possible Block
forall a. a -> Possible a
Actual (Block -> Possible Block)
-> (Content -> Block) -> Content -> Possible Block
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [[Inline]] -> Block
LineBlock ([[Inline]] -> Block)
-> (Content -> [[Inline]]) -> Content -> Block
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Content -> [[Inline]]
lineContent
BulletList [[Block]]
_ -> Block -> Possible Block
forall a. a -> Possible a
Actual (Block -> Possible Block)
-> (Content -> Block) -> Content -> Possible Block
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [[Block]] -> Block
BulletList ([[Block]] -> Block) -> (Content -> [[Block]]) -> Content -> Block
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Content -> [[Block]]
listItemContent
OrderedList ListAttributes
la [[Block]]
_ -> Block -> Possible Block
forall a. a -> Possible a
Actual (Block -> Possible Block)
-> (Content -> Block) -> Content -> Possible Block
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ListAttributes -> [[Block]] -> Block
OrderedList ListAttributes
la ([[Block]] -> Block) -> (Content -> [[Block]]) -> Content -> Block
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Content -> [[Block]]
listItemContent
DefinitionList [([Inline], [[Block]])]
_ -> Block -> Possible Block
forall a. a -> Possible a
Actual (Block -> Possible Block)
-> (Content -> Block) -> Content -> Possible Block
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [([Inline], [[Block]])] -> Block
DefinitionList ([([Inline], [[Block]])] -> Block)
-> (Content -> [([Inline], [[Block]])]) -> Content -> Block
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Content -> [([Inline], [[Block]])]
defItemContent
Block
_ -> Possible Block -> Content -> Possible Block
forall a b. a -> b -> a
const Possible Block
forall a. Possible a
Absent
where
inlineContent :: Content -> [Inline]
inlineContent = \case
ContentInlines [Inline]
inlns -> [Inline]
inlns
Content
c -> e -> [Inline]
forall (m :: * -> *) e a. (MonadThrow m, Exception e) => e -> m a
throwM (e -> [Inline]) -> (String -> e) -> String -> [Inline]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. LuaError e => String -> e
forall e. LuaError e => String -> e
luaException @e (String -> [Inline]) -> String -> [Inline]
forall a b. (a -> b) -> a -> b
$
String
"expected Inlines, got " String -> String -> String
forall a. Semigroup a => a -> a -> a
<> Content -> String
contentTypeDescription Content
c
blockContent :: Content -> [Block]
blockContent = \case
ContentBlocks [Block]
blks -> [Block]
blks
ContentInlines [Inline]
inlns -> [[Inline] -> Block
Plain [Inline]
inlns]
Content
c -> e -> [Block]
forall (m :: * -> *) e a. (MonadThrow m, Exception e) => e -> m a
throwM (e -> [Block]) -> (String -> e) -> String -> [Block]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. LuaError e => String -> e
forall e. LuaError e => String -> e
luaException @e (String -> [Block]) -> String -> [Block]
forall a b. (a -> b) -> a -> b
$
String
"expected Blocks, got " String -> String -> String
forall a. Semigroup a => a -> a -> a
<> Content -> String
contentTypeDescription Content
c
lineContent :: Content -> [[Inline]]
lineContent = \case
ContentLines [[Inline]]
lns -> [[Inline]]
lns
Content
c -> e -> [[Inline]]
forall (m :: * -> *) e a. (MonadThrow m, Exception e) => e -> m a
throwM (e -> [[Inline]]) -> (String -> e) -> String -> [[Inline]]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. LuaError e => String -> e
forall e. LuaError e => String -> e
luaException @e (String -> [[Inline]]) -> String -> [[Inline]]
forall a b. (a -> b) -> a -> b
$
String
"expected list of lines (Inlines), got " String -> String -> String
forall a. Semigroup a => a -> a -> a
<> Content -> String
contentTypeDescription Content
c
defItemContent :: Content -> [([Inline], [[Block]])]
defItemContent = \case
ContentDefItems [([Inline], [[Block]])]
itms -> [([Inline], [[Block]])]
itms
Content
c -> e -> [([Inline], [[Block]])]
forall (m :: * -> *) e a. (MonadThrow m, Exception e) => e -> m a
throwM (e -> [([Inline], [[Block]])])
-> (String -> e) -> String -> [([Inline], [[Block]])]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. LuaError e => String -> e
forall e. LuaError e => String -> e
luaException @e (String -> [([Inline], [[Block]])])
-> String -> [([Inline], [[Block]])]
forall a b. (a -> b) -> a -> b
$
String
"expected definition items, got " String -> String -> String
forall a. Semigroup a => a -> a -> a
<> Content -> String
contentTypeDescription Content
c
listItemContent :: Content -> [[Block]]
listItemContent = \case
ContentBlocks [Block]
blks -> [[Block]
blks]
ContentLines [[Inline]]
lns -> ([Inline] -> [Block]) -> [[Inline]] -> [[Block]]
forall a b. (a -> b) -> [a] -> [b]
map ((Block -> [Block] -> [Block]
forall a. a -> [a] -> [a]
:[]) (Block -> [Block]) -> ([Inline] -> Block) -> [Inline] -> [Block]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Inline] -> Block
Plain) [[Inline]]
lns
ContentListItems [[Block]]
itms -> [[Block]]
itms
Content
c -> e -> [[Block]]
forall (m :: * -> *) e a. (MonadThrow m, Exception e) => e -> m a
throwM (e -> [[Block]]) -> (String -> e) -> String -> [[Block]]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. LuaError e => String -> e
forall e. LuaError e => String -> e
luaException @e (String -> [[Block]]) -> String -> [[Block]]
forall a b. (a -> b) -> a -> b
$
String
"expected list of items, got " String -> String -> String
forall a. Semigroup a => a -> a -> a
<> Content -> String
contentTypeDescription Content
c
getBlockText :: Block -> Possible Text
getBlockText :: Block -> Possible Text
getBlockText = \case
CodeBlock Attr
_ Text
lst -> Text -> Possible Text
forall a. a -> Possible a
Actual Text
lst
RawBlock Format
_ Text
raw -> Text -> Possible Text
forall a. a -> Possible a
Actual Text
raw
Block
_ -> Possible Text
forall a. Possible a
Absent
setBlockText :: Block -> Text -> Possible Block
setBlockText :: Block -> Text -> Possible Block
setBlockText = \case
CodeBlock Attr
attr Text
_ -> Block -> Possible Block
forall a. a -> Possible a
Actual (Block -> Possible Block)
-> (Text -> Block) -> Text -> Possible Block
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Attr -> Text -> Block
CodeBlock Attr
attr
RawBlock Format
f Text
_ -> Block -> Possible Block
forall a. a -> Possible a
Actual (Block -> Possible Block)
-> (Text -> Block) -> Text -> Possible Block
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Format -> Text -> Block
RawBlock Format
f
Block
_ -> Possible Block -> Text -> Possible Block
forall a b. a -> b -> a
const Possible Block
forall a. Possible a
Absent
blockConstructors :: LuaError e => [DocumentedFunction e]
blockConstructors :: [DocumentedFunction e]
blockConstructors =
[ Name
-> ([Block] -> LuaE e Block)
-> HsFnPrecursor e ([Block] -> LuaE e Block)
forall a e. Name -> a -> HsFnPrecursor e a
defun Name
"BlockQuote"
### liftPure BlockQuote
HsFnPrecursor e ([Block] -> LuaE e Block)
-> Parameter e [Block] -> HsFnPrecursor e (LuaE e Block)
forall e a b.
HsFnPrecursor e (a -> b) -> Parameter e a -> HsFnPrecursor e b
<#> Parameter e [Block]
blocksParam
HsFnPrecursor e (LuaE e Block)
-> FunctionResults e Block -> DocumentedFunction e
forall e a.
HsFnPrecursor e (LuaE e a)
-> FunctionResults e a -> DocumentedFunction e
=#> Text -> FunctionResults e Block
blockResult Text
"BlockQuote element"
, Name
-> ([[Block]] -> LuaE e Block)
-> HsFnPrecursor e ([[Block]] -> LuaE e Block)
forall a e. Name -> a -> HsFnPrecursor e a
defun Name
"BulletList"
### liftPure BulletList
HsFnPrecursor e ([[Block]] -> LuaE e Block)
-> Parameter e [[Block]] -> HsFnPrecursor e (LuaE e Block)
forall e a b.
HsFnPrecursor e (a -> b) -> Parameter e a -> HsFnPrecursor e b
<#> Text -> Parameter e [[Block]]
blockItemsParam Text
"list items"
HsFnPrecursor e (LuaE e Block)
-> FunctionResults e Block -> DocumentedFunction e
forall e a.
HsFnPrecursor e (LuaE e a)
-> FunctionResults e a -> DocumentedFunction e
=#> Text -> FunctionResults e Block
blockResult Text
"BulletList element"
, Name
-> (Text -> Maybe Attr -> LuaE e Block)
-> HsFnPrecursor e (Text -> Maybe Attr -> LuaE e Block)
forall a e. Name -> a -> HsFnPrecursor e a
defun Name
"CodeBlock"
### liftPure2 (\code mattr -> CodeBlock (fromMaybe nullAttr mattr) code)
HsFnPrecursor e (Text -> Maybe Attr -> LuaE e Block)
-> Parameter e Text -> HsFnPrecursor e (Maybe Attr -> LuaE e Block)
forall e a b.
HsFnPrecursor e (a -> b) -> Parameter e a -> HsFnPrecursor e b
<#> Text -> Text -> Parameter e Text
forall e. Text -> Text -> Parameter e Text
textParam Text
"text" Text
"code block content"
HsFnPrecursor e (Maybe Attr -> LuaE e Block)
-> Parameter e (Maybe Attr) -> HsFnPrecursor e (LuaE e Block)
forall e a b.
HsFnPrecursor e (a -> b) -> Parameter e a -> HsFnPrecursor e b
<#> Parameter e (Maybe Attr)
optAttrParam
HsFnPrecursor e (LuaE e Block)
-> FunctionResults e Block -> DocumentedFunction e
forall e a.
HsFnPrecursor e (LuaE e a)
-> FunctionResults e a -> DocumentedFunction e
=#> Text -> FunctionResults e Block
blockResult Text
"CodeBlock element"
, Name
-> ([([Inline], [[Block]])] -> LuaE e Block)
-> HsFnPrecursor e ([([Inline], [[Block]])] -> LuaE e Block)
forall a e. Name -> a -> HsFnPrecursor e a
defun Name
"DefinitionList"
### liftPure DefinitionList
HsFnPrecursor e ([([Inline], [[Block]])] -> LuaE e Block)
-> Parameter e [([Inline], [[Block]])]
-> HsFnPrecursor e (LuaE e Block)
forall e a b.
HsFnPrecursor e (a -> b) -> Parameter e a -> HsFnPrecursor e b
<#> Peeker e [([Inline], [[Block]])]
-> Text -> Text -> Text -> Parameter e [([Inline], [[Block]])]
forall e a. Peeker e a -> Text -> Text -> Text -> Parameter e a
parameter ([Peeker e [([Inline], [[Block]])]]
-> Peeker e [([Inline], [[Block]])]
forall e a. LuaError e => [Peeker e a] -> Peeker e a
choice
[ Peeker e ([Inline], [[Block]]) -> Peeker e [([Inline], [[Block]])]
forall a e. LuaError e => Peeker e a -> Peeker e [a]
peekList Peeker e ([Inline], [[Block]])
forall e. LuaError e => Peeker e ([Inline], [[Block]])
peekDefinitionItem
, \StackIndex
idx -> (([Inline], [[Block]])
-> [([Inline], [[Block]])] -> [([Inline], [[Block]])]
forall a. a -> [a] -> [a]
:[]) (([Inline], [[Block]]) -> [([Inline], [[Block]])])
-> Peek e ([Inline], [[Block]]) -> Peek e [([Inline], [[Block]])]
forall (m :: * -> *) a b. Monad m => (a -> b) -> m a -> m b
<$!> Peeker e ([Inline], [[Block]])
forall e. LuaError e => Peeker e ([Inline], [[Block]])
peekDefinitionItem StackIndex
idx
])
Text
"{{Inlines, {Blocks,...}},...}"
Text
"content" Text
"definition items"
HsFnPrecursor e (LuaE e Block)
-> FunctionResults e Block -> DocumentedFunction e
forall e a.
HsFnPrecursor e (LuaE e a)
-> FunctionResults e a -> DocumentedFunction e
=#> Text -> FunctionResults e Block
blockResult Text
"DefinitionList element"
, Name
-> ([Block] -> Maybe Attr -> LuaE e Block)
-> HsFnPrecursor e ([Block] -> Maybe Attr -> LuaE e Block)
forall a e. Name -> a -> HsFnPrecursor e a
defun Name
"Div"
### liftPure2 (\content mattr -> Div (fromMaybe nullAttr mattr) content)
HsFnPrecursor e ([Block] -> Maybe Attr -> LuaE e Block)
-> Parameter e [Block]
-> HsFnPrecursor e (Maybe Attr -> LuaE e Block)
forall e a b.
HsFnPrecursor e (a -> b) -> Parameter e a -> HsFnPrecursor e b
<#> Parameter e [Block]
blocksParam
HsFnPrecursor e (Maybe Attr -> LuaE e Block)
-> Parameter e (Maybe Attr) -> HsFnPrecursor e (LuaE e Block)
forall e a b.
HsFnPrecursor e (a -> b) -> Parameter e a -> HsFnPrecursor e b
<#> Parameter e (Maybe Attr)
optAttrParam
HsFnPrecursor e (LuaE e Block)
-> FunctionResults e Block -> DocumentedFunction e
forall e a.
HsFnPrecursor e (LuaE e a)
-> FunctionResults e a -> DocumentedFunction e
=#> Text -> FunctionResults e Block
blockResult Text
"Div element"
, Name
-> (Int -> [Inline] -> Maybe Attr -> LuaE e Block)
-> HsFnPrecursor e (Int -> [Inline] -> Maybe Attr -> LuaE e Block)
forall a e. Name -> a -> HsFnPrecursor e a
defun Name
"Header"
### liftPure3 (\lvl content mattr ->
Header lvl (fromMaybe nullAttr mattr) content)
HsFnPrecursor e (Int -> [Inline] -> Maybe Attr -> LuaE e Block)
-> Parameter e Int
-> HsFnPrecursor e ([Inline] -> Maybe Attr -> LuaE e Block)
forall e a b.
HsFnPrecursor e (a -> b) -> Parameter e a -> HsFnPrecursor e b
<#> Peeker e Int -> Text -> Text -> Text -> Parameter e Int
forall e a. Peeker e a -> Text -> Text -> Text -> Parameter e a
parameter Peeker e Int
forall a e. (Integral a, Read a) => Peeker e a
peekIntegral Text
"integer" Text
"level" Text
"heading level"
HsFnPrecursor e ([Inline] -> Maybe Attr -> LuaE e Block)
-> Parameter e [Inline]
-> HsFnPrecursor e (Maybe Attr -> LuaE e Block)
forall e a b.
HsFnPrecursor e (a -> b) -> Parameter e a -> HsFnPrecursor e b
<#> Peeker e [Inline] -> Text -> Text -> Text -> Parameter e [Inline]
forall e a. Peeker e a -> Text -> Text -> Text -> Parameter e a
parameter Peeker e [Inline]
forall e. LuaError e => Peeker e [Inline]
peekInlinesFuzzy Text
"Inlines" Text
"content" Text
"inline content"
HsFnPrecursor e (Maybe Attr -> LuaE e Block)
-> Parameter e (Maybe Attr) -> HsFnPrecursor e (LuaE e Block)
forall e a b.
HsFnPrecursor e (a -> b) -> Parameter e a -> HsFnPrecursor e b
<#> Parameter e (Maybe Attr)
optAttrParam
HsFnPrecursor e (LuaE e Block)
-> FunctionResults e Block -> DocumentedFunction e
forall e a.
HsFnPrecursor e (LuaE e a)
-> FunctionResults e a -> DocumentedFunction e
=#> Text -> FunctionResults e Block
blockResult Text
"Header element"
, Name -> LuaE e Block -> HsFnPrecursor e (LuaE e Block)
forall a e. Name -> a -> HsFnPrecursor e a
defun Name
"HorizontalRule"
### return HorizontalRule
HsFnPrecursor e (LuaE e Block)
-> FunctionResults e Block -> DocumentedFunction e
forall e a.
HsFnPrecursor e (LuaE e a)
-> FunctionResults e a -> DocumentedFunction e
=#> Text -> FunctionResults e Block
blockResult Text
"HorizontalRule element"
, Name
-> ([[Inline]] -> LuaE e Block)
-> HsFnPrecursor e ([[Inline]] -> LuaE e Block)
forall a e. Name -> a -> HsFnPrecursor e a
defun Name
"LineBlock"
### liftPure LineBlock
HsFnPrecursor e ([[Inline]] -> LuaE e Block)
-> Parameter e [[Inline]] -> HsFnPrecursor e (LuaE e Block)
forall e a b.
HsFnPrecursor e (a -> b) -> Parameter e a -> HsFnPrecursor e b
<#> Peeker e [[Inline]]
-> Text -> Text -> Text -> Parameter e [[Inline]]
forall e a. Peeker e a -> Text -> Text -> Text -> Parameter e a
parameter (Peeker e [Inline] -> Peeker e [[Inline]]
forall a e. LuaError e => Peeker e a -> Peeker e [a]
peekList Peeker e [Inline]
forall e. LuaError e => Peeker e [Inline]
peekInlinesFuzzy) Text
"{Inlines,...}" Text
"content" Text
"lines"
HsFnPrecursor e (LuaE e Block)
-> FunctionResults e Block -> DocumentedFunction e
forall e a.
HsFnPrecursor e (LuaE e a)
-> FunctionResults e a -> DocumentedFunction e
=#> Text -> FunctionResults e Block
blockResult Text
"LineBlock element"
, Name -> LuaE e Block -> HsFnPrecursor e (LuaE e Block)
forall a e. Name -> a -> HsFnPrecursor e a
defun Name
"Null"
### return Null
HsFnPrecursor e (LuaE e Block)
-> FunctionResults e Block -> DocumentedFunction e
forall e a.
HsFnPrecursor e (LuaE e a)
-> FunctionResults e a -> DocumentedFunction e
=#> Text -> FunctionResults e Block
blockResult Text
"Null element"
, Name
-> ([[Block]] -> Maybe ListAttributes -> LuaE e Block)
-> HsFnPrecursor
e ([[Block]] -> Maybe ListAttributes -> LuaE e Block)
forall a e. Name -> a -> HsFnPrecursor e a
defun Name
"OrderedList"
### liftPure2 (\items mListAttrib ->
let defListAttrib = (1, DefaultStyle, DefaultDelim)
in OrderedList (fromMaybe defListAttrib mListAttrib) items)
HsFnPrecursor e ([[Block]] -> Maybe ListAttributes -> LuaE e Block)
-> Parameter e [[Block]]
-> HsFnPrecursor e (Maybe ListAttributes -> LuaE e Block)
forall e a b.
HsFnPrecursor e (a -> b) -> Parameter e a -> HsFnPrecursor e b
<#> Text -> Parameter e [[Block]]
blockItemsParam Text
"ordered list items"
HsFnPrecursor e (Maybe ListAttributes -> LuaE e Block)
-> Parameter e (Maybe ListAttributes)
-> HsFnPrecursor e (LuaE e Block)
forall e a b.
HsFnPrecursor e (a -> b) -> Parameter e a -> HsFnPrecursor e b
<#> Peeker e ListAttributes
-> Text -> Text -> Text -> Parameter e (Maybe ListAttributes)
forall e a.
Peeker e a -> Text -> Text -> Text -> Parameter e (Maybe a)
optionalParameter Peeker e ListAttributes
forall e. LuaError e => Peeker e ListAttributes
peekListAttributes Text
"ListAttributes" Text
"listAttributes"
Text
"specifier for the list's numbering"
HsFnPrecursor e (LuaE e Block)
-> FunctionResults e Block -> DocumentedFunction e
forall e a.
HsFnPrecursor e (LuaE e a)
-> FunctionResults e a -> DocumentedFunction e
=#> Text -> FunctionResults e Block
blockResult Text
"OrderedList element"
, Name
-> ([Inline] -> LuaE e Block)
-> HsFnPrecursor e ([Inline] -> LuaE e Block)
forall a e. Name -> a -> HsFnPrecursor e a
defun Name
"Para"
### liftPure Para
HsFnPrecursor e ([Inline] -> LuaE e Block)
-> Parameter e [Inline] -> HsFnPrecursor e (LuaE e Block)
forall e a b.
HsFnPrecursor e (a -> b) -> Parameter e a -> HsFnPrecursor e b
<#> Peeker e [Inline] -> Text -> Text -> Text -> Parameter e [Inline]
forall e a. Peeker e a -> Text -> Text -> Text -> Parameter e a
parameter Peeker e [Inline]
forall e. LuaError e => Peeker e [Inline]
peekInlinesFuzzy Text
"Inlines" Text
"content" Text
"paragraph content"
HsFnPrecursor e (LuaE e Block)
-> FunctionResults e Block -> DocumentedFunction e
forall e a.
HsFnPrecursor e (LuaE e a)
-> FunctionResults e a -> DocumentedFunction e
=#> Text -> FunctionResults e Block
blockResult Text
"Para element"
, Name
-> ([Inline] -> LuaE e Block)
-> HsFnPrecursor e ([Inline] -> LuaE e Block)
forall a e. Name -> a -> HsFnPrecursor e a
defun Name
"Plain"
### liftPure Plain
HsFnPrecursor e ([Inline] -> LuaE e Block)
-> Parameter e [Inline] -> HsFnPrecursor e (LuaE e Block)
forall e a b.
HsFnPrecursor e (a -> b) -> Parameter e a -> HsFnPrecursor e b
<#> Peeker e [Inline] -> Text -> Text -> Text -> Parameter e [Inline]
forall e a. Peeker e a -> Text -> Text -> Text -> Parameter e a
parameter Peeker e [Inline]
forall e. LuaError e => Peeker e [Inline]
peekInlinesFuzzy Text
"Inlines" Text
"content" Text
"paragraph content"
HsFnPrecursor e (LuaE e Block)
-> FunctionResults e Block -> DocumentedFunction e
forall e a.
HsFnPrecursor e (LuaE e a)
-> FunctionResults e a -> DocumentedFunction e
=#> Text -> FunctionResults e Block
blockResult Text
"Plain element"
, Name
-> (Format -> Text -> LuaE e Block)
-> HsFnPrecursor e (Format -> Text -> LuaE e Block)
forall a e. Name -> a -> HsFnPrecursor e a
defun Name
"RawBlock"
### liftPure2 RawBlock
HsFnPrecursor e (Format -> Text -> LuaE e Block)
-> Parameter e Format -> HsFnPrecursor e (Text -> LuaE e Block)
forall e a b.
HsFnPrecursor e (a -> b) -> Parameter e a -> HsFnPrecursor e b
<#> Peeker e Format -> Text -> Text -> Text -> Parameter e Format
forall e a. Peeker e a -> Text -> Text -> Text -> Parameter e a
parameter Peeker e Format
forall e. Peeker e Format
peekFormat Text
"Format" Text
"format" Text
"format of content"
HsFnPrecursor e (Text -> LuaE e Block)
-> Parameter e Text -> HsFnPrecursor e (LuaE e Block)
forall e a b.
HsFnPrecursor e (a -> b) -> Parameter e a -> HsFnPrecursor e b
<#> Peeker e Text -> Text -> Text -> Text -> Parameter e Text
forall e a. Peeker e a -> Text -> Text -> Text -> Parameter e a
parameter Peeker e Text
forall e. Peeker e Text
peekText Text
"string" Text
"text" Text
"raw content"
HsFnPrecursor e (LuaE e Block)
-> FunctionResults e Block -> DocumentedFunction e
forall e a.
HsFnPrecursor e (LuaE e a)
-> FunctionResults e a -> DocumentedFunction e
=#> Text -> FunctionResults e Block
blockResult Text
"RawBlock element"
, Name
-> (Caption
-> [ColSpec]
-> TableHead
-> [TableBody]
-> TableFoot
-> Maybe Attr
-> LuaE e Block)
-> HsFnPrecursor
e
(Caption
-> [ColSpec]
-> TableHead
-> [TableBody]
-> TableFoot
-> Maybe Attr
-> LuaE e Block)
forall a e. Name -> a -> HsFnPrecursor e a
defun Name
"Table"
### (\capt colspecs thead tbodies tfoot mattr ->
let attr = fromMaybe nullAttr mattr
in return $! attr `seq` capt `seq` colspecs `seq` thead `seq` tbodies
`seq` tfoot `seq` Table attr capt colspecs thead tbodies tfoot)
HsFnPrecursor
e
(Caption
-> [ColSpec]
-> TableHead
-> [TableBody]
-> TableFoot
-> Maybe Attr
-> LuaE e Block)
-> Parameter e Caption
-> HsFnPrecursor
e
([ColSpec]
-> TableHead
-> [TableBody]
-> TableFoot
-> Maybe Attr
-> LuaE e Block)
forall e a b.
HsFnPrecursor e (a -> b) -> Parameter e a -> HsFnPrecursor e b
<#> Peeker e Caption -> Text -> Text -> Text -> Parameter e Caption
forall e a. Peeker e a -> Text -> Text -> Text -> Parameter e a
parameter Peeker e Caption
forall e. LuaError e => Peeker e Caption
peekCaption Text
"Caption" Text
"caption" Text
"table caption"
HsFnPrecursor
e
([ColSpec]
-> TableHead
-> [TableBody]
-> TableFoot
-> Maybe Attr
-> LuaE e Block)
-> Parameter e [ColSpec]
-> HsFnPrecursor
e
(TableHead
-> [TableBody] -> TableFoot -> Maybe Attr -> LuaE e Block)
forall e a b.
HsFnPrecursor e (a -> b) -> Parameter e a -> HsFnPrecursor e b
<#> Peeker e [ColSpec] -> Text -> Text -> Text -> Parameter e [ColSpec]
forall e a. Peeker e a -> Text -> Text -> Text -> Parameter e a
parameter (Peeker e ColSpec -> Peeker e [ColSpec]
forall a e. LuaError e => Peeker e a -> Peeker e [a]
peekList Peeker e ColSpec
forall e. LuaError e => Peeker e ColSpec
peekColSpec) Text
"{ColSpec,...}" Text
"colspecs"
Text
"column alignments and widths"
HsFnPrecursor
e
(TableHead
-> [TableBody] -> TableFoot -> Maybe Attr -> LuaE e Block)
-> Parameter e TableHead
-> HsFnPrecursor
e ([TableBody] -> TableFoot -> Maybe Attr -> LuaE e Block)
forall e a b.
HsFnPrecursor e (a -> b) -> Parameter e a -> HsFnPrecursor e b
<#> Peeker e TableHead -> Text -> Text -> Text -> Parameter e TableHead
forall e a. Peeker e a -> Text -> Text -> Text -> Parameter e a
parameter Peeker e TableHead
forall e. LuaError e => Peeker e TableHead
peekTableHead Text
"TableHead" Text
"head" Text
"table head"
HsFnPrecursor
e ([TableBody] -> TableFoot -> Maybe Attr -> LuaE e Block)
-> Parameter e [TableBody]
-> HsFnPrecursor e (TableFoot -> Maybe Attr -> LuaE e Block)
forall e a b.
HsFnPrecursor e (a -> b) -> Parameter e a -> HsFnPrecursor e b
<#> Peeker e [TableBody]
-> Text -> Text -> Text -> Parameter e [TableBody]
forall e a. Peeker e a -> Text -> Text -> Text -> Parameter e a
parameter (Peeker e TableBody -> Peeker e [TableBody]
forall a e. LuaError e => Peeker e a -> Peeker e [a]
peekList Peeker e TableBody
forall e. LuaError e => Peeker e TableBody
peekTableBody) Text
"{TableBody,...}" Text
"bodies"
Text
"table bodies"
HsFnPrecursor e (TableFoot -> Maybe Attr -> LuaE e Block)
-> Parameter e TableFoot
-> HsFnPrecursor e (Maybe Attr -> LuaE e Block)
forall e a b.
HsFnPrecursor e (a -> b) -> Parameter e a -> HsFnPrecursor e b
<#> Peeker e TableFoot -> Text -> Text -> Text -> Parameter e TableFoot
forall e a. Peeker e a -> Text -> Text -> Text -> Parameter e a
parameter Peeker e TableFoot
forall e. LuaError e => Peeker e TableFoot
peekTableFoot Text
"TableFoot" Text
"foot" Text
"table foot"
HsFnPrecursor e (Maybe Attr -> LuaE e Block)
-> Parameter e (Maybe Attr) -> HsFnPrecursor e (LuaE e Block)
forall e a b.
HsFnPrecursor e (a -> b) -> Parameter e a -> HsFnPrecursor e b
<#> Parameter e (Maybe Attr)
optAttrParam
HsFnPrecursor e (LuaE e Block)
-> FunctionResults e Block -> DocumentedFunction e
forall e a.
HsFnPrecursor e (LuaE e a)
-> FunctionResults e a -> DocumentedFunction e
=#> Text -> FunctionResults e Block
blockResult Text
"Table element"
]
where
blockResult :: Text -> FunctionResults e Block
blockResult = Pusher e Block -> Text -> Text -> FunctionResults e Block
forall e a. Pusher e a -> Text -> Text -> FunctionResults e a
functionResult Pusher e Block
forall e. LuaError e => Pusher e Block
pushBlock Text
"Block"
blocksParam :: Parameter e [Block]
blocksParam = Peeker e [Block] -> Text -> Text -> Text -> Parameter e [Block]
forall e a. Peeker e a -> Text -> Text -> Text -> Parameter e a
parameter Peeker e [Block]
forall e. LuaError e => Peeker e [Block]
peekBlocksFuzzy Text
"Blocks" Text
"content" Text
"block content"
blockItemsParam :: Text -> Parameter e [[Block]]
blockItemsParam = Peeker e [[Block]] -> Text -> Text -> Text -> Parameter e [[Block]]
forall e a. Peeker e a -> Text -> Text -> Text -> Parameter e a
parameter Peeker e [[Block]]
forall e. LuaError e => StackIndex -> Peek e [[Block]]
peekItemsFuzzy Text
"List of Blocks" Text
"content"
peekItemsFuzzy :: StackIndex -> Peek e [[Block]]
peekItemsFuzzy StackIndex
idx = Peeker e [Block] -> StackIndex -> Peek e [[Block]]
forall a e. LuaError e => Peeker e a -> Peeker e [a]
peekList Peeker e [Block]
forall e. LuaError e => Peeker e [Block]
peekBlocksFuzzy StackIndex
idx
Peek e [[Block]] -> Peek e [[Block]] -> Peek e [[Block]]
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> (([Block] -> [[Block]] -> [[Block]]
forall a. a -> [a] -> [a]
:[]) ([Block] -> [[Block]]) -> Peek e [Block] -> Peek e [[Block]]
forall (m :: * -> *) a b. Monad m => (a -> b) -> m a -> m b
<$!> Peeker e [Block]
forall e. LuaError e => Peeker e [Block]
peekBlocksFuzzy StackIndex
idx)
textParam :: Text -> Text -> Parameter e Text
textParam = Peeker e Text -> Text -> Text -> Text -> Parameter e Text
forall e a. Peeker e a -> Text -> Text -> Text -> Parameter e a
parameter Peeker e Text
forall e. Peeker e Text
peekText Text
"string"
optAttrParam :: Parameter e (Maybe Attr)
optAttrParam = Peeker e Attr -> Text -> Text -> Text -> Parameter e (Maybe Attr)
forall e a.
Peeker e a -> Text -> Text -> Text -> Parameter e (Maybe a)
optionalParameter Peeker e Attr
forall e. LuaError e => Peeker e Attr
peekAttr Text
"attr" Text
"Attr"
Text
"additional attributes"
mkBlocks :: LuaError e => DocumentedFunction e
mkBlocks :: DocumentedFunction e
mkBlocks = Name
-> ([Block] -> LuaE e [Block])
-> HsFnPrecursor e ([Block] -> LuaE e [Block])
forall a e. Name -> a -> HsFnPrecursor e a
defun Name
"Blocks"
### liftPure id
HsFnPrecursor e ([Block] -> LuaE e [Block])
-> Parameter e [Block] -> HsFnPrecursor e (LuaE e [Block])
forall e a b.
HsFnPrecursor e (a -> b) -> Parameter e a -> HsFnPrecursor e b
<#> Peeker e [Block] -> Text -> Text -> Text -> Parameter e [Block]
forall e a. Peeker e a -> Text -> Text -> Text -> Parameter e a
parameter Peeker e [Block]
forall e. LuaError e => Peeker e [Block]
peekBlocksFuzzy Text
"Blocks" Text
"blocks" Text
"block elements"
HsFnPrecursor e (LuaE e [Block])
-> FunctionResults e [Block] -> DocumentedFunction e
forall e a.
HsFnPrecursor e (LuaE e a)
-> FunctionResults e a -> DocumentedFunction e
=#> Pusher e [Block] -> Text -> Text -> FunctionResults e [Block]
forall e a. Pusher e a -> Text -> Text -> FunctionResults e a
functionResult Pusher e [Block]
forall e. LuaError e => Pusher e [Block]
pushBlocks Text
"Blocks" Text
"list of block elements"