{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TypeApplications #-}
{-# LANGUAGE TupleSections #-}
module Text.Pandoc.Lua.Marshal.Inline
(
peekInline
, peekInlineFuzzy
, pushInline
, peekInlines
, peekInlinesFuzzy
, pushInlines
, inlineConstructors
, mkInlines
, walkInlineSplicing
, walkInlinesStraight
) where
import Control.Applicative ((<|>), optional)
import Control.Monad.Catch (throwM)
import Control.Monad ((<$!>))
import Data.Data (showConstr, toConstr)
import Data.Maybe (fromMaybe)
import Data.Text (Text)
import HsLua
import Text.Pandoc.Definition (Inline (..), nullAttr)
import Text.Pandoc.Lua.Marshal.Attr (peekAttr, pushAttr)
import {-# SOURCE #-} Text.Pandoc.Lua.Marshal.Block (peekBlocksFuzzy)
import Text.Pandoc.Lua.Marshal.Citation (peekCitation, pushCitation)
import Text.Pandoc.Lua.Marshal.Content
( Content (..), contentTypeDescription, peekContent, pushContent )
import Text.Pandoc.Lua.Marshal.Filter (Filter, peekFilter)
import Text.Pandoc.Lua.Marshal.Format (peekFormat, pushFormat)
import Text.Pandoc.Lua.Marshal.List (pushPandocList, newListMetatable)
import Text.Pandoc.Lua.Marshal.MathType (peekMathType, pushMathType)
import Text.Pandoc.Lua.Marshal.QuoteType (peekQuoteType, pushQuoteType)
import Text.Pandoc.Lua.Marshal.Shared (walkBlocksAndInlines)
import Text.Pandoc.Lua.Walk (SpliceList, Walkable, walkSplicing, walkStraight)
import qualified Text.Pandoc.Builder as B
pushInline :: LuaError e => Pusher e Inline
pushInline :: Pusher e Inline
pushInline = UDTypeWithList e (DocumentedFunction e) Inline Void
-> Pusher e Inline
forall e fn a itemtype.
LuaError e =>
UDTypeWithList e fn a itemtype -> a -> LuaE e ()
pushUD UDTypeWithList e (DocumentedFunction e) Inline Void
forall e. LuaError e => DocumentedType e Inline
typeInline
{-# INLINE pushInline #-}
peekInline :: LuaError e => Peeker e Inline
peekInline :: Peeker e Inline
peekInline = UDTypeWithList e (DocumentedFunction e) Inline Void
-> Peeker e Inline
forall e fn a itemtype.
LuaError e =>
UDTypeWithList e fn a itemtype -> Peeker e a
peekUD UDTypeWithList e (DocumentedFunction e) Inline Void
forall e. LuaError e => DocumentedType e Inline
typeInline
{-# INLINE peekInline #-}
peekInlines :: LuaError e
=> Peeker e [Inline]
peekInlines :: Peeker e [Inline]
peekInlines = 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
peekInline
{-# INLINABLE peekInlines #-}
pushInlines :: LuaError e
=> Pusher e [Inline]
pushInlines :: Pusher e [Inline]
pushInlines xs :: [Inline]
xs = do
Pusher e Inline -> Pusher e [Inline]
forall e a. LuaError e => Pusher e a -> [a] -> LuaE e ()
pushList Pusher e Inline
forall e. LuaError e => Pusher e Inline
pushInline [Inline]
xs
Name -> LuaE e () -> LuaE e ()
forall e. Name -> LuaE e () -> LuaE e ()
newListMetatable "Inlines" (LuaE e () -> LuaE e ()) -> LuaE e () -> LuaE e ()
forall a b. (a -> b) -> a -> b
$ do
Name -> LuaE e ()
forall e. Name -> LuaE e ()
pushName "walk"
DocumentedFunction e -> LuaE e ()
forall e. LuaError e => DocumentedFunction e -> LuaE e ()
pushDocumentedFunction (DocumentedFunction e -> LuaE e ())
-> DocumentedFunction e -> LuaE e ()
forall a b. (a -> b) -> a -> b
$ ([Inline] -> Filter -> LuaE e [Inline])
-> HsFnPrecursor e ([Inline] -> Filter -> LuaE e [Inline])
forall a e. a -> HsFnPrecursor e a
lambda
### flip walkBlocksAndInlines
HsFnPrecursor e ([Inline] -> Filter -> LuaE e [Inline])
-> Parameter e [Inline]
-> HsFnPrecursor e (Filter -> LuaE e [Inline])
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 "Blocks" "self" ""
HsFnPrecursor e (Filter -> LuaE e [Inline])
-> Parameter e Filter -> HsFnPrecursor e (LuaE e [Inline])
forall e a b.
HsFnPrecursor e (a -> b) -> Parameter e a -> HsFnPrecursor e b
<#> Peeker e Filter -> Text -> Text -> Text -> Parameter e Filter
forall e a. Peeker e a -> Text -> Text -> Text -> Parameter e a
parameter Peeker e Filter
forall e. LuaError e => Peeker e Filter
peekFilter "Filter" "lua_filter" "table of filter functions"
HsFnPrecursor e (LuaE e [Inline])
-> FunctionResults e [Inline] -> DocumentedFunction e
forall e a.
HsFnPrecursor e (LuaE e a)
-> FunctionResults e a -> DocumentedFunction e
=#> Pusher e [Inline] -> Text -> Text -> FunctionResults e [Inline]
forall e a. Pusher e a -> Text -> Text -> FunctionResults e a
functionResult Pusher e [Inline]
forall e. LuaError e => Pusher e [Inline]
pushInlines "Blocks" "modified list"
StackIndex -> LuaE e ()
forall e. LuaError e => StackIndex -> LuaE e ()
rawset (CInt -> StackIndex
nth 3)
StackIndex -> LuaE e ()
forall e. StackIndex -> LuaE e ()
setmetatable (CInt -> StackIndex
nth 2)
{-# INLINABLE pushInlines #-}
peekInlineFuzzy :: LuaError e => Peeker e Inline
peekInlineFuzzy :: Peeker e Inline
peekInlineFuzzy idx :: StackIndex
idx = Name -> Peek e Inline -> Peek e Inline
forall e a. Name -> Peek e a -> Peek e a
retrieving "Inline" (Peek e Inline -> Peek e Inline) -> Peek e Inline -> Peek e Inline
forall a b. (a -> b) -> a -> b
$ LuaE e Type -> Peek e Type
forall e a. LuaE e a -> Peek e a
liftLua (StackIndex -> LuaE e Type
forall e. StackIndex -> LuaE e Type
ltype StackIndex
idx) Peek e Type -> (Type -> Peek e Inline) -> Peek e Inline
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \case
TypeString -> Text -> Inline
Str (Text -> Inline) -> Peek e Text -> Peek e Inline
forall (m :: * -> *) a b. Monad m => (a -> b) -> m a -> m b
<$!> Peeker e Text
forall e. Peeker e Text
peekText StackIndex
idx
_ -> Peeker e Inline
forall e. LuaError e => Peeker e Inline
peekInline StackIndex
idx
{-# INLINABLE peekInlineFuzzy #-}
peekInlinesFuzzy :: LuaError e
=> Peeker e [Inline]
peekInlinesFuzzy :: Peeker e [Inline]
peekInlinesFuzzy idx :: StackIndex
idx = LuaE e Type -> Peek e Type
forall e a. LuaE e a -> Peek e a
liftLua (StackIndex -> LuaE e Type
forall e. StackIndex -> LuaE e Type
ltype StackIndex
idx) Peek e Type -> (Type -> Peek e [Inline]) -> Peek e [Inline]
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \case
TypeString -> Many Inline -> [Inline]
forall a. Many a -> [a]
B.toList (Many Inline -> [Inline])
-> (Text -> Many Inline) -> Text -> [Inline]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> Many Inline
B.text (Text -> [Inline]) -> Peek e Text -> Peek e [Inline]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Peeker e Text
forall e. Peeker e Text
peekText StackIndex
idx
_ -> 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
peekInlineFuzzy StackIndex
idx
Peek e [Inline] -> Peek e [Inline] -> Peek e [Inline]
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> (Inline -> [Inline]
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Inline -> [Inline]) -> Peek e Inline -> Peek e [Inline]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Peeker e Inline
forall e. LuaError e => Peeker e Inline
peekInlineFuzzy StackIndex
idx)
Peek e [Inline] -> Peek e [Inline] -> Peek e [Inline]
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> (ByteString -> Peek e [Inline]
forall a e. ByteString -> Peek e a
failPeek (ByteString -> Peek e [Inline])
-> Peek e ByteString -> Peek e [Inline]
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<<
Name -> StackIndex -> Peek e ByteString
forall e. Name -> StackIndex -> Peek e ByteString
typeMismatchMessage "Inline, list of Inlines, or string" StackIndex
idx)
{-# INLINABLE peekInlinesFuzzy #-}
typeInline :: forall e. LuaError e => DocumentedType e Inline
typeInline :: DocumentedType e Inline
typeInline = Name
-> [(Operation, DocumentedFunction e)]
-> [Member e (DocumentedFunction e) Inline]
-> DocumentedType e Inline
forall e a.
LuaError e =>
Name
-> [(Operation, DocumentedFunction e)]
-> [Member e (DocumentedFunction e) a]
-> DocumentedType e a
deftype "Inline"
[ 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
$ (Inline -> LuaE e String)
-> HsFnPrecursor e (Inline -> LuaE e String)
forall a e. a -> HsFnPrecursor e a
lambda
### liftPure (show @Inline)
HsFnPrecursor e (Inline -> LuaE e String)
-> Parameter e Inline -> HsFnPrecursor e (LuaE e String)
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
peekInline "inline" "Inline" "Object"
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 "string" "stringified Inline"
, 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
$ Name
-> (Maybe Inline -> Maybe Inline -> LuaE e Bool)
-> HsFnPrecursor e (Maybe Inline -> Maybe Inline -> LuaE e Bool)
forall a e. Name -> a -> HsFnPrecursor e a
defun "__eq"
### liftPure2 (\a b -> fromMaybe False ((==) <$> a <*> b))
HsFnPrecursor e (Maybe Inline -> Maybe Inline -> LuaE e Bool)
-> Parameter e (Maybe Inline)
-> HsFnPrecursor e (Maybe Inline -> LuaE e Bool)
forall e a b.
HsFnPrecursor e (a -> b) -> Parameter e a -> HsFnPrecursor e b
<#> Peeker e (Maybe Inline)
-> Text -> Text -> Text -> Parameter e (Maybe Inline)
forall e a. Peeker e a -> Text -> Text -> Text -> Parameter e a
parameter (Peek e Inline -> Peek e (Maybe Inline)
forall (f :: * -> *) a. Alternative f => f a -> f (Maybe a)
optional (Peek e Inline -> Peek e (Maybe Inline))
-> Peeker e Inline -> Peeker e (Maybe Inline)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Peeker e Inline
forall e. LuaError e => Peeker e Inline
peekInline) "a" "Inline" ""
HsFnPrecursor e (Maybe Inline -> LuaE e Bool)
-> Parameter e (Maybe Inline) -> HsFnPrecursor e (LuaE e Bool)
forall e a b.
HsFnPrecursor e (a -> b) -> Parameter e a -> HsFnPrecursor e b
<#> Peeker e (Maybe Inline)
-> Text -> Text -> Text -> Parameter e (Maybe Inline)
forall e a. Peeker e a -> Text -> Text -> Text -> Parameter e a
parameter (Peek e Inline -> Peek e (Maybe Inline)
forall (f :: * -> *) a. Alternative f => f a -> f (Maybe a)
optional (Peek e Inline -> Peek e (Maybe Inline))
-> Peeker e Inline -> Peeker e (Maybe Inline)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Peeker e Inline
forall e. LuaError e => Peeker e Inline
peekInline) "b" "Inline" ""
HsFnPrecursor e (LuaE e Bool)
-> FunctionResults e Bool -> DocumentedFunction e
forall e a.
HsFnPrecursor e (LuaE e a)
-> FunctionResults e a -> DocumentedFunction e
=#> 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 "boolean" "whether the two are equal"
]
[ Name
-> Text
-> (Pusher e Attr, Inline -> Possible Attr)
-> (Peeker e Attr, Inline -> Attr -> Possible Inline)
-> Member e (DocumentedFunction e) Inline
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 "attr" "element attributes"
(Pusher e Attr
forall e. LuaError e => Pusher e Attr
pushAttr, \case
Code attr :: Attr
attr _ -> Attr -> Possible Attr
forall a. a -> Possible a
Actual Attr
attr
Image attr :: Attr
attr _ _ -> Attr -> Possible Attr
forall a. a -> Possible a
Actual Attr
attr
Link attr :: Attr
attr _ _ -> Attr -> Possible Attr
forall a. a -> Possible a
Actual Attr
attr
Span attr :: Attr
attr _ -> Attr -> Possible Attr
forall a. a -> Possible a
Actual Attr
attr
_ -> Possible Attr
forall a. Possible a
Absent)
(Peeker e Attr
forall e. LuaError e => Peeker e Attr
peekAttr, \case
Code _ cs :: Text
cs -> Inline -> Possible Inline
forall a. a -> Possible a
Actual (Inline -> Possible Inline)
-> (Attr -> Inline) -> Attr -> Possible Inline
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Attr -> Text -> Inline
`Code` Text
cs)
Image _ cpt :: [Inline]
cpt tgt :: Target
tgt -> Inline -> Possible Inline
forall a. a -> Possible a
Actual (Inline -> Possible Inline)
-> (Attr -> Inline) -> Attr -> Possible Inline
forall b c a. (b -> c) -> (a -> b) -> a -> c
. \attr :: Attr
attr -> Attr -> [Inline] -> Target -> Inline
Image Attr
attr [Inline]
cpt Target
tgt
Link _ cpt :: [Inline]
cpt tgt :: Target
tgt -> Inline -> Possible Inline
forall a. a -> Possible a
Actual (Inline -> Possible Inline)
-> (Attr -> Inline) -> Attr -> Possible Inline
forall b c a. (b -> c) -> (a -> b) -> a -> c
. \attr :: Attr
attr -> Attr -> [Inline] -> Target -> Inline
Link Attr
attr [Inline]
cpt Target
tgt
Span _ inlns :: [Inline]
inlns -> Inline -> Possible Inline
forall a. a -> Possible a
Actual (Inline -> Possible Inline)
-> (Attr -> Inline) -> Attr -> Possible Inline
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Attr -> [Inline] -> Inline
`Span` [Inline]
inlns)
_ -> Possible Inline -> Attr -> Possible Inline
forall a b. a -> b -> a
const Possible Inline
forall a. Possible a
Absent)
, Name
-> Text
-> (Pusher e [Inline], Inline -> Possible [Inline])
-> (Peeker e [Inline], Inline -> [Inline] -> Possible Inline)
-> Member e (DocumentedFunction e) Inline
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 "caption" "image caption"
(Pusher e [Inline]
forall e. LuaError e => Pusher e [Inline]
pushInlines, \case
Image _ capt :: [Inline]
capt _ -> [Inline] -> Possible [Inline]
forall a. a -> Possible a
Actual [Inline]
capt
_ -> Possible [Inline]
forall a. Possible a
Absent)
(Peeker e [Inline]
forall e. LuaError e => Peeker e [Inline]
peekInlinesFuzzy, \case
Image attr :: Attr
attr _ target :: Target
target -> Inline -> Possible Inline
forall a. a -> Possible a
Actual (Inline -> Possible Inline)
-> ([Inline] -> Inline) -> [Inline] -> Possible Inline
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (\capt :: [Inline]
capt -> Attr -> [Inline] -> Target -> Inline
Image Attr
attr [Inline]
capt Target
target)
_ -> Possible Inline -> [Inline] -> Possible Inline
forall a b. a -> b -> a
const Possible Inline
forall a. Possible a
Absent)
, Name
-> Text
-> (Pusher e [Citation], Inline -> Possible [Citation])
-> (Peeker e [Citation], Inline -> [Citation] -> Possible Inline)
-> Member e (DocumentedFunction e) Inline
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 "citations" "list of citations"
(Pusher e Citation -> Pusher e [Citation]
forall e a. LuaError e => Pusher e a -> [a] -> LuaE e ()
pushPandocList Pusher e Citation
forall e. LuaError e => Pusher e Citation
pushCitation, \case
Cite cs :: [Citation]
cs _ -> [Citation] -> Possible [Citation]
forall a. a -> Possible a
Actual [Citation]
cs
_ -> Possible [Citation]
forall a. Possible a
Absent)
(Peeker e Citation -> Peeker e [Citation]
forall a e. LuaError e => Peeker e a -> Peeker e [a]
peekList Peeker e Citation
forall e. LuaError e => Peeker e Citation
peekCitation, \case
Cite _ inlns :: [Inline]
inlns -> Inline -> Possible Inline
forall a. a -> Possible a
Actual (Inline -> Possible Inline)
-> ([Citation] -> Inline) -> [Citation] -> Possible Inline
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ([Citation] -> [Inline] -> Inline
`Cite` [Inline]
inlns)
_ -> Possible Inline -> [Citation] -> Possible Inline
forall a b. a -> b -> a
const Possible Inline
forall a. Possible a
Absent)
, Name
-> Text
-> (Pusher e Content, Inline -> Possible Content)
-> (Peeker e Content, Inline -> Content -> Possible Inline)
-> Member e (DocumentedFunction e) Inline
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 "content" "element contents"
(Pusher e Content
forall e. LuaError e => Pusher e Content
pushContent, \case
Cite _ inlns :: [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
Emph inlns :: [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
Link _ inlns :: [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
Quoted _ inlns :: [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
SmallCaps inlns :: [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
Span _ inlns :: [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
Strikeout inlns :: [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
Strong inlns :: [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
Subscript inlns :: [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
Superscript inlns :: [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
Underline inlns :: [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
Note blks :: [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
_ -> Possible Content
forall a. Possible a
Absent)
(Peeker e Content
forall e. LuaError e => Peeker e Content
peekContent,
let inlineContent :: Content -> [Inline]
inlineContent = \case
ContentInlines inlns :: [Inline]
inlns -> [Inline]
inlns
c :: 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
$
"expected Inlines, got " String -> String -> String
forall a. Semigroup a => a -> a -> a
<> Content -> String
contentTypeDescription Content
c
blockContent :: Content -> [Block]
blockContent = \case
ContentBlocks blks :: [Block]
blks -> [Block]
blks
ContentInlines [] -> []
c :: 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
$
"expected Blocks, got " String -> String -> String
forall a. Semigroup a => a -> a -> a
<> Content -> String
contentTypeDescription Content
c
in \case
Cite cs :: [Citation]
cs _ -> Inline -> Possible Inline
forall a. a -> Possible a
Actual (Inline -> Possible Inline)
-> (Content -> Inline) -> Content -> Possible Inline
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Citation] -> [Inline] -> Inline
Cite [Citation]
cs ([Inline] -> Inline) -> (Content -> [Inline]) -> Content -> Inline
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Content -> [Inline]
inlineContent
Emph _ -> Inline -> Possible Inline
forall a. a -> Possible a
Actual (Inline -> Possible Inline)
-> (Content -> Inline) -> Content -> Possible Inline
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Inline] -> Inline
Emph ([Inline] -> Inline) -> (Content -> [Inline]) -> Content -> Inline
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Content -> [Inline]
inlineContent
Link a :: Attr
a _ tgt :: Target
tgt -> Inline -> Possible Inline
forall a. a -> Possible a
Actual (Inline -> Possible Inline)
-> (Content -> Inline) -> Content -> Possible Inline
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (\inlns :: [Inline]
inlns -> Attr -> [Inline] -> Target -> Inline
Link Attr
a [Inline]
inlns Target
tgt) ([Inline] -> Inline) -> (Content -> [Inline]) -> Content -> Inline
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Content -> [Inline]
inlineContent
Quoted qt :: QuoteType
qt _ -> Inline -> Possible Inline
forall a. a -> Possible a
Actual (Inline -> Possible Inline)
-> (Content -> Inline) -> Content -> Possible Inline
forall b c a. (b -> c) -> (a -> b) -> a -> c
. QuoteType -> [Inline] -> Inline
Quoted QuoteType
qt ([Inline] -> Inline) -> (Content -> [Inline]) -> Content -> Inline
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Content -> [Inline]
inlineContent
SmallCaps _ -> Inline -> Possible Inline
forall a. a -> Possible a
Actual (Inline -> Possible Inline)
-> (Content -> Inline) -> Content -> Possible Inline
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Inline] -> Inline
SmallCaps ([Inline] -> Inline) -> (Content -> [Inline]) -> Content -> Inline
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Content -> [Inline]
inlineContent
Span attr :: Attr
attr _ -> Inline -> Possible Inline
forall a. a -> Possible a
Actual (Inline -> Possible Inline)
-> (Content -> Inline) -> Content -> Possible Inline
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Attr -> [Inline] -> Inline
Span Attr
attr ([Inline] -> Inline) -> (Content -> [Inline]) -> Content -> Inline
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Content -> [Inline]
inlineContent
Strikeout _ -> Inline -> Possible Inline
forall a. a -> Possible a
Actual (Inline -> Possible Inline)
-> (Content -> Inline) -> Content -> Possible Inline
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Inline] -> Inline
Strikeout ([Inline] -> Inline) -> (Content -> [Inline]) -> Content -> Inline
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Content -> [Inline]
inlineContent
Strong _ -> Inline -> Possible Inline
forall a. a -> Possible a
Actual (Inline -> Possible Inline)
-> (Content -> Inline) -> Content -> Possible Inline
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Inline] -> Inline
Strong ([Inline] -> Inline) -> (Content -> [Inline]) -> Content -> Inline
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Content -> [Inline]
inlineContent
Subscript _ -> Inline -> Possible Inline
forall a. a -> Possible a
Actual (Inline -> Possible Inline)
-> (Content -> Inline) -> Content -> Possible Inline
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Inline] -> Inline
Subscript ([Inline] -> Inline) -> (Content -> [Inline]) -> Content -> Inline
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Content -> [Inline]
inlineContent
Superscript _ -> Inline -> Possible Inline
forall a. a -> Possible a
Actual (Inline -> Possible Inline)
-> (Content -> Inline) -> Content -> Possible Inline
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Inline] -> Inline
Superscript ([Inline] -> Inline) -> (Content -> [Inline]) -> Content -> Inline
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Content -> [Inline]
inlineContent
Underline _ -> Inline -> Possible Inline
forall a. a -> Possible a
Actual (Inline -> Possible Inline)
-> (Content -> Inline) -> Content -> Possible Inline
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Inline] -> Inline
Underline ([Inline] -> Inline) -> (Content -> [Inline]) -> Content -> Inline
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Content -> [Inline]
inlineContent
Note _ -> Inline -> Possible Inline
forall a. a -> Possible a
Actual (Inline -> Possible Inline)
-> (Content -> Inline) -> Content -> Possible Inline
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Block] -> Inline
Note ([Block] -> Inline) -> (Content -> [Block]) -> Content -> Inline
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Content -> [Block]
blockContent
_ -> Possible Inline -> Content -> Possible Inline
forall a b. a -> b -> a
const Possible Inline
forall a. Possible a
Absent
)
, Name
-> Text
-> (Pusher e Format, Inline -> Possible Format)
-> (Peeker e Format, Inline -> Format -> Possible Inline)
-> Member e (DocumentedFunction e) Inline
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 "format" "format of raw text"
(Pusher e Format
forall e. Pusher e Format
pushFormat, \case
RawInline fmt :: Format
fmt _ -> Format -> Possible Format
forall a. a -> Possible a
Actual Format
fmt
_ -> Possible Format
forall a. Possible a
Absent)
(Peeker e Format
forall e. Peeker e Format
peekFormat, \case
RawInline _ txt :: Text
txt -> Inline -> Possible Inline
forall a. a -> Possible a
Actual (Inline -> Possible Inline)
-> (Format -> Inline) -> Format -> Possible Inline
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Format -> Text -> Inline
`RawInline` Text
txt)
_ -> Possible Inline -> Format -> Possible Inline
forall a b. a -> b -> a
const Possible Inline
forall a. Possible a
Absent)
, Name
-> Text
-> (Pusher e MathType, Inline -> Possible MathType)
-> (Peeker e MathType, Inline -> MathType -> Possible Inline)
-> Member e (DocumentedFunction e) Inline
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 "mathtype" "math rendering method"
(Pusher e MathType
forall e. Pusher e MathType
pushMathType, \case
Math mt :: MathType
mt _ -> MathType -> Possible MathType
forall a. a -> Possible a
Actual MathType
mt
_ -> Possible MathType
forall a. Possible a
Absent)
(Peeker e MathType
forall e. Peeker e MathType
peekMathType, \case
Math _ txt :: Text
txt -> Inline -> Possible Inline
forall a. a -> Possible a
Actual (Inline -> Possible Inline)
-> (MathType -> Inline) -> MathType -> Possible Inline
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (MathType -> Text -> Inline
`Math` Text
txt)
_ -> Possible Inline -> MathType -> Possible Inline
forall a b. a -> b -> a
const Possible Inline
forall a. Possible a
Absent)
, Name
-> Text
-> (Pusher e QuoteType, Inline -> Possible QuoteType)
-> (Peeker e QuoteType, Inline -> QuoteType -> Possible Inline)
-> Member e (DocumentedFunction e) Inline
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 "quotetype" "type of quotes (single or double)"
(Pusher e QuoteType
forall e. Pusher e QuoteType
pushQuoteType, \case
Quoted qt :: QuoteType
qt _ -> QuoteType -> Possible QuoteType
forall a. a -> Possible a
Actual QuoteType
qt
_ -> Possible QuoteType
forall a. Possible a
Absent)
(Peeker e QuoteType
forall e. Peeker e QuoteType
peekQuoteType, \case
Quoted _ inlns :: [Inline]
inlns -> Inline -> Possible Inline
forall a. a -> Possible a
Actual (Inline -> Possible Inline)
-> (QuoteType -> Inline) -> QuoteType -> Possible Inline
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (QuoteType -> [Inline] -> Inline
`Quoted` [Inline]
inlns)
_ -> Possible Inline -> QuoteType -> Possible Inline
forall a b. a -> b -> a
const Possible Inline
forall a. Possible a
Absent)
, Name
-> Text
-> (Pusher e Text, Inline -> Possible Text)
-> (Peeker e Text, Inline -> Text -> Possible Inline)
-> Member e (DocumentedFunction e) Inline
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 "src" "image source"
(Pusher e Text
forall e. Pusher e Text
pushText, \case
Image _ _ (src :: Text
src, _) -> Text -> Possible Text
forall a. a -> Possible a
Actual Text
src
_ -> Possible Text
forall a. Possible a
Absent)
(Peeker e Text
forall e. Peeker e Text
peekText, \case
Image attr :: Attr
attr capt :: [Inline]
capt (_, title :: Text
title) -> Inline -> Possible Inline
forall a. a -> Possible a
Actual (Inline -> Possible Inline)
-> (Text -> Inline) -> Text -> Possible Inline
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Attr -> [Inline] -> Target -> Inline
Image Attr
attr [Inline]
capt (Target -> Inline) -> (Text -> Target) -> Text -> Inline
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (,Text
title)
_ -> Possible Inline -> Text -> Possible Inline
forall a b. a -> b -> a
const Possible Inline
forall a. Possible a
Absent)
, Name
-> Text
-> (Pusher e Text, Inline -> Possible Text)
-> (Peeker e Text, Inline -> Text -> Possible Inline)
-> Member e (DocumentedFunction e) Inline
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 "target" "link target URL"
(Pusher e Text
forall e. Pusher e Text
pushText, \case
Link _ _ (tgt :: Text
tgt, _) -> Text -> Possible Text
forall a. a -> Possible a
Actual Text
tgt
_ -> Possible Text
forall a. Possible a
Absent)
(Peeker e Text
forall e. Peeker e Text
peekText, \case
Link attr :: Attr
attr capt :: [Inline]
capt (_, title :: Text
title) -> Inline -> Possible Inline
forall a. a -> Possible a
Actual (Inline -> Possible Inline)
-> (Text -> Inline) -> Text -> Possible Inline
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Attr -> [Inline] -> Target -> Inline
Link Attr
attr [Inline]
capt (Target -> Inline) -> (Text -> Target) -> Text -> Inline
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (,Text
title)
_ -> Possible Inline -> Text -> Possible Inline
forall a b. a -> b -> a
const Possible Inline
forall a. Possible a
Absent)
, Name
-> Text
-> (Pusher e Text, Inline -> Possible Text)
-> (Peeker e Text, Inline -> Text -> Possible Inline)
-> Member e (DocumentedFunction e) Inline
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 "title" "title text"
(Pusher e Text
forall e. Pusher e Text
pushText, \case
Image _ _ (_, tit :: Text
tit) -> Text -> Possible Text
forall a. a -> Possible a
Actual Text
tit
Link _ _ (_, tit :: Text
tit) -> Text -> Possible Text
forall a. a -> Possible a
Actual Text
tit
_ -> Possible Text
forall a. Possible a
Absent)
(Peeker e Text
forall e. Peeker e Text
peekText, \case
Image attr :: Attr
attr capt :: [Inline]
capt (src :: Text
src, _) -> Inline -> Possible Inline
forall a. a -> Possible a
Actual (Inline -> Possible Inline)
-> (Text -> Inline) -> Text -> Possible Inline
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Attr -> [Inline] -> Target -> Inline
Image Attr
attr [Inline]
capt (Target -> Inline) -> (Text -> Target) -> Text -> Inline
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Text
src,)
Link attr :: Attr
attr capt :: [Inline]
capt (src :: Text
src, _) -> Inline -> Possible Inline
forall a. a -> Possible a
Actual (Inline -> Possible Inline)
-> (Text -> Inline) -> Text -> Possible Inline
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Attr -> [Inline] -> Target -> Inline
Link Attr
attr [Inline]
capt (Target -> Inline) -> (Text -> Target) -> Text -> Inline
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Text
src,)
_ -> Possible Inline -> Text -> Possible Inline
forall a b. a -> b -> a
const Possible Inline
forall a. Possible a
Absent)
, Name
-> Text
-> (Pusher e Text, Inline -> Possible Text)
-> (Peeker e Text, Inline -> Text -> Possible Inline)
-> Member e (DocumentedFunction e) Inline
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 "text" "text contents"
(Pusher e Text
forall e. Pusher e Text
pushText, Inline -> Possible Text
getInlineText)
(Peeker e Text
forall e. Peeker e Text
peekText, Inline -> Text -> Possible Inline
setInlineText)
, Name
-> Text
-> (Pusher e String, Inline -> String)
-> Member e (DocumentedFunction e) Inline
forall e b a fn.
Name -> Text -> (Pusher e b, a -> b) -> Member e fn a
readonly "tag" "type of Inline"
(Pusher e String
forall e. String -> LuaE e ()
pushString, Constr -> String
showConstr (Constr -> String) -> (Inline -> Constr) -> Inline -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Inline -> Constr
forall a. Data a => a -> Constr
toConstr )
, AliasIndex
-> Text -> [AliasIndex] -> Member e (DocumentedFunction e) Inline
forall e fn a. AliasIndex -> Text -> [AliasIndex] -> Member e fn a
alias "t" "tag" ["tag"]
, AliasIndex
-> Text -> [AliasIndex] -> Member e (DocumentedFunction e) Inline
forall e fn a. AliasIndex -> Text -> [AliasIndex] -> Member e fn a
alias "c" "content" ["content"]
, AliasIndex
-> Text -> [AliasIndex] -> Member e (DocumentedFunction e) Inline
forall e fn a. AliasIndex -> Text -> [AliasIndex] -> Member e fn a
alias "identifier" "element identifier" ["attr", "identifier"]
, AliasIndex
-> Text -> [AliasIndex] -> Member e (DocumentedFunction e) Inline
forall e fn a. AliasIndex -> Text -> [AliasIndex] -> Member e fn a
alias "classes" "element classes" ["attr", "classes"]
, AliasIndex
-> Text -> [AliasIndex] -> Member e (DocumentedFunction e) Inline
forall e fn a. AliasIndex -> Text -> [AliasIndex] -> Member e fn a
alias "attributes" "other element attributes" ["attr", "attributes"]
, DocumentedFunction e -> Member e (DocumentedFunction e) Inline
forall e a.
DocumentedFunction e -> Member e (DocumentedFunction e) a
method (DocumentedFunction e -> Member e (DocumentedFunction e) Inline)
-> DocumentedFunction e -> Member e (DocumentedFunction e) Inline
forall a b. (a -> b) -> a -> b
$ Name
-> (Inline -> LuaE e Inline)
-> HsFnPrecursor e (Inline -> LuaE e Inline)
forall a e. Name -> a -> HsFnPrecursor e a
defun "clone"
### return
HsFnPrecursor e (Inline -> LuaE e Inline)
-> Parameter e Inline -> HsFnPrecursor e (LuaE e Inline)
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
peekInline "inline" "Inline" "self"
HsFnPrecursor e (LuaE e Inline)
-> FunctionResults e Inline -> DocumentedFunction e
forall e a.
HsFnPrecursor e (LuaE e a)
-> FunctionResults e a -> DocumentedFunction e
=#> Pusher e Inline -> Text -> Text -> FunctionResults e Inline
forall e a. Pusher e a -> Text -> Text -> FunctionResults e a
functionResult Pusher e Inline
forall e. LuaError e => Pusher e Inline
pushInline "Inline" "cloned Inline"
, DocumentedFunction e -> Member e (DocumentedFunction e) Inline
forall e a.
DocumentedFunction e -> Member e (DocumentedFunction e) a
method (DocumentedFunction e -> Member e (DocumentedFunction e) Inline)
-> DocumentedFunction e -> Member e (DocumentedFunction e) Inline
forall a b. (a -> b) -> a -> b
$ Name
-> (Inline -> Filter -> LuaE e Inline)
-> HsFnPrecursor e (Inline -> Filter -> LuaE e Inline)
forall a e. Name -> a -> HsFnPrecursor e a
defun "walk"
### flip walkBlocksAndInlines
HsFnPrecursor e (Inline -> Filter -> LuaE e Inline)
-> Parameter e Inline -> HsFnPrecursor e (Filter -> LuaE e Inline)
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
peekInline "Inline" "self" ""
HsFnPrecursor e (Filter -> LuaE e Inline)
-> Parameter e Filter -> HsFnPrecursor e (LuaE e Inline)
forall e a b.
HsFnPrecursor e (a -> b) -> Parameter e a -> HsFnPrecursor e b
<#> Peeker e Filter -> Text -> Text -> Text -> Parameter e Filter
forall e a. Peeker e a -> Text -> Text -> Text -> Parameter e a
parameter Peeker e Filter
forall e. LuaError e => Peeker e Filter
peekFilter "Filter" "lua_filter" "table of filter functions"
HsFnPrecursor e (LuaE e Inline)
-> FunctionResults e Inline -> DocumentedFunction e
forall e a.
HsFnPrecursor e (LuaE e a)
-> FunctionResults e a -> DocumentedFunction e
=#> Pusher e Inline -> Text -> Text -> FunctionResults e Inline
forall e a. Pusher e a -> Text -> Text -> FunctionResults e a
functionResult Pusher e Inline
forall e. LuaError e => Pusher e Inline
pushInline "Inline" "modified element"
]
getInlineText :: Inline -> Possible Text
getInlineText :: Inline -> Possible Text
getInlineText = \case
Code _ lst :: Text
lst -> Text -> Possible Text
forall a. a -> Possible a
Actual Text
lst
Math _ str :: Text
str -> Text -> Possible Text
forall a. a -> Possible a
Actual Text
str
RawInline _ raw :: Text
raw -> Text -> Possible Text
forall a. a -> Possible a
Actual Text
raw
Str s :: Text
s -> Text -> Possible Text
forall a. a -> Possible a
Actual Text
s
_ -> Possible Text
forall a. Possible a
Absent
setInlineText :: Inline -> Text -> Possible Inline
setInlineText :: Inline -> Text -> Possible Inline
setInlineText = \case
Code attr :: Attr
attr _ -> Inline -> Possible Inline
forall a. a -> Possible a
Actual (Inline -> Possible Inline)
-> (Text -> Inline) -> Text -> Possible Inline
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Attr -> Text -> Inline
Code Attr
attr
Math mt :: MathType
mt _ -> Inline -> Possible Inline
forall a. a -> Possible a
Actual (Inline -> Possible Inline)
-> (Text -> Inline) -> Text -> Possible Inline
forall b c a. (b -> c) -> (a -> b) -> a -> c
. MathType -> Text -> Inline
Math MathType
mt
RawInline f :: Format
f _ -> Inline -> Possible Inline
forall a. a -> Possible a
Actual (Inline -> Possible Inline)
-> (Text -> Inline) -> Text -> Possible Inline
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Format -> Text -> Inline
RawInline Format
f
Str _ -> Inline -> Possible Inline
forall a. a -> Possible a
Actual (Inline -> Possible Inline)
-> (Text -> Inline) -> Text -> Possible Inline
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> Inline
Str
_ -> Possible Inline -> Text -> Possible Inline
forall a b. a -> b -> a
const Possible Inline
forall a. Possible a
Absent
inlineConstructors :: LuaError e => [DocumentedFunction e]
inlineConstructors :: [DocumentedFunction e]
inlineConstructors =
[ Name
-> ([Inline] -> [Citation] -> LuaE e Inline)
-> HsFnPrecursor e ([Inline] -> [Citation] -> LuaE e Inline)
forall a e. Name -> a -> HsFnPrecursor e a
defun "Cite"
### liftPure2 (flip Cite)
HsFnPrecursor e ([Inline] -> [Citation] -> LuaE e Inline)
-> Parameter e [Inline]
-> HsFnPrecursor e ([Citation] -> LuaE e Inline)
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 "content" "Inline" "placeholder content"
HsFnPrecursor e ([Citation] -> LuaE e Inline)
-> Parameter e [Citation] -> HsFnPrecursor e (LuaE e Inline)
forall e a b.
HsFnPrecursor e (a -> b) -> Parameter e a -> HsFnPrecursor e b
<#> Peeker e [Citation]
-> Text -> Text -> Text -> Parameter e [Citation]
forall e a. Peeker e a -> Text -> Text -> Text -> Parameter e a
parameter (Peeker e Citation -> Peeker e [Citation]
forall a e. LuaError e => Peeker e a -> Peeker e [a]
peekList Peeker e Citation
forall e. LuaError e => Peeker e Citation
peekCitation) "citations" "list of Citations" ""
HsFnPrecursor e (LuaE e Inline)
-> FunctionResults e Inline -> DocumentedFunction e
forall e a.
HsFnPrecursor e (LuaE e a)
-> FunctionResults e a -> DocumentedFunction e
=#> Pusher e Inline -> Text -> Text -> FunctionResults e Inline
forall e a. Pusher e a -> Text -> Text -> FunctionResults e a
functionResult Pusher e Inline
forall e. LuaError e => Pusher e Inline
pushInline "Inline" "cite element"
, Name
-> (Text -> Maybe Attr -> LuaE e Inline)
-> HsFnPrecursor e (Text -> Maybe Attr -> LuaE e Inline)
forall a e. Name -> a -> HsFnPrecursor e a
defun "Code"
### liftPure2 (\text mattr -> Code (fromMaybe nullAttr mattr) text)
HsFnPrecursor e (Text -> Maybe Attr -> LuaE e Inline)
-> Parameter e Text
-> HsFnPrecursor e (Maybe Attr -> LuaE e Inline)
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 "code" "code string"
HsFnPrecursor e (Maybe Attr -> LuaE e Inline)
-> Parameter e (Maybe Attr) -> HsFnPrecursor e (LuaE e Inline)
forall e a b.
HsFnPrecursor e (a -> b) -> Parameter e a -> HsFnPrecursor e b
<#> Parameter e Attr -> Parameter e (Maybe Attr)
forall e a. Parameter e a -> Parameter e (Maybe a)
opt (Peeker e Attr -> Text -> Text -> Text -> Parameter e Attr
forall e a. Peeker e a -> Text -> Text -> Text -> Parameter e a
parameter Peeker e Attr
forall e. LuaError e => Peeker e Attr
peekAttr "Attr" "attr" "additional attributes")
HsFnPrecursor e (LuaE e Inline)
-> FunctionResults e Inline -> DocumentedFunction e
forall e a.
HsFnPrecursor e (LuaE e a)
-> FunctionResults e a -> DocumentedFunction e
=#> Pusher e Inline -> Text -> Text -> FunctionResults e Inline
forall e a. Pusher e a -> Text -> Text -> FunctionResults e a
functionResult Pusher e Inline
forall e. LuaError e => Pusher e Inline
pushInline "Inline" "code element"
, Name -> ([Inline] -> Inline) -> DocumentedFunction e
forall e.
LuaError e =>
Name -> ([Inline] -> Inline) -> DocumentedFunction e
mkInlinesConstr "Emph" [Inline] -> Inline
Emph
, Name
-> ([Inline] -> Text -> Maybe Text -> Maybe Attr -> LuaE e Inline)
-> HsFnPrecursor
e ([Inline] -> Text -> Maybe Text -> Maybe Attr -> LuaE e Inline)
forall a e. Name -> a -> HsFnPrecursor e a
defun "Image"
### liftPure4 (\caption src mtitle mattr ->
let attr = fromMaybe nullAttr mattr
title = fromMaybe mempty mtitle
in Image attr caption (src, title))
HsFnPrecursor
e ([Inline] -> Text -> Maybe Text -> Maybe Attr -> LuaE e Inline)
-> Parameter e [Inline]
-> HsFnPrecursor
e (Text -> Maybe Text -> Maybe Attr -> LuaE e Inline)
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 "Inlines" "caption" "image caption / alt"
HsFnPrecursor e (Text -> Maybe Text -> Maybe Attr -> LuaE e Inline)
-> Parameter e Text
-> HsFnPrecursor e (Maybe Text -> Maybe Attr -> LuaE e Inline)
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 "src" "path/URL of the image file"
HsFnPrecursor e (Maybe Text -> Maybe Attr -> LuaE e Inline)
-> Parameter e (Maybe Text)
-> HsFnPrecursor e (Maybe Attr -> LuaE e Inline)
forall e a b.
HsFnPrecursor e (a -> b) -> Parameter e a -> HsFnPrecursor e b
<#> Parameter e Text -> Parameter e (Maybe Text)
forall e a. Parameter e a -> Parameter e (Maybe a)
opt (Text -> Text -> Parameter e Text
forall e. Text -> Text -> Parameter e Text
textParam "title" "brief image description")
HsFnPrecursor e (Maybe Attr -> LuaE e Inline)
-> Parameter e (Maybe Attr) -> HsFnPrecursor e (LuaE e Inline)
forall e a b.
HsFnPrecursor e (a -> b) -> Parameter e a -> HsFnPrecursor e b
<#> Parameter e Attr -> Parameter e (Maybe Attr)
forall e a. Parameter e a -> Parameter e (Maybe a)
opt (Peeker e Attr -> Text -> Text -> Text -> Parameter e Attr
forall e a. Peeker e a -> Text -> Text -> Text -> Parameter e a
parameter Peeker e Attr
forall e. LuaError e => Peeker e Attr
peekAttr "Attr" "attr" "image attributes")
HsFnPrecursor e (LuaE e Inline)
-> FunctionResults e Inline -> DocumentedFunction e
forall e a.
HsFnPrecursor e (LuaE e a)
-> FunctionResults e a -> DocumentedFunction e
=#> Pusher e Inline -> Text -> Text -> FunctionResults e Inline
forall e a. Pusher e a -> Text -> Text -> FunctionResults e a
functionResult Pusher e Inline
forall e. LuaError e => Pusher e Inline
pushInline "Inline" "image element"
, Name -> LuaE e Inline -> HsFnPrecursor e (LuaE e Inline)
forall a e. Name -> a -> HsFnPrecursor e a
defun "LineBreak"
### return LineBreak
HsFnPrecursor e (LuaE e Inline)
-> FunctionResults e Inline -> DocumentedFunction e
forall e a.
HsFnPrecursor e (LuaE e a)
-> FunctionResults e a -> DocumentedFunction e
=#> Pusher e Inline -> Text -> Text -> FunctionResults e Inline
forall e a. Pusher e a -> Text -> Text -> FunctionResults e a
functionResult Pusher e Inline
forall e. LuaError e => Pusher e Inline
pushInline "Inline" "line break"
, Name
-> ([Inline] -> Text -> Maybe Text -> Maybe Attr -> LuaE e Inline)
-> HsFnPrecursor
e ([Inline] -> Text -> Maybe Text -> Maybe Attr -> LuaE e Inline)
forall a e. Name -> a -> HsFnPrecursor e a
defun "Link"
### liftPure4 (\content target mtitle mattr ->
let attr = fromMaybe nullAttr mattr
title = fromMaybe mempty mtitle
in Link attr content (target, title))
HsFnPrecursor
e ([Inline] -> Text -> Maybe Text -> Maybe Attr -> LuaE e Inline)
-> Parameter e [Inline]
-> HsFnPrecursor
e (Text -> Maybe Text -> Maybe Attr -> LuaE e Inline)
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 "Inlines" "content" "text for this link"
HsFnPrecursor e (Text -> Maybe Text -> Maybe Attr -> LuaE e Inline)
-> Parameter e Text
-> HsFnPrecursor e (Maybe Text -> Maybe Attr -> LuaE e Inline)
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 "target" "the link target"
HsFnPrecursor e (Maybe Text -> Maybe Attr -> LuaE e Inline)
-> Parameter e (Maybe Text)
-> HsFnPrecursor e (Maybe Attr -> LuaE e Inline)
forall e a b.
HsFnPrecursor e (a -> b) -> Parameter e a -> HsFnPrecursor e b
<#> Parameter e Text -> Parameter e (Maybe Text)
forall e a. Parameter e a -> Parameter e (Maybe a)
opt (Text -> Text -> Parameter e Text
forall e. Text -> Text -> Parameter e Text
textParam "title" "brief link description")
HsFnPrecursor e (Maybe Attr -> LuaE e Inline)
-> Parameter e (Maybe Attr) -> HsFnPrecursor e (LuaE e Inline)
forall e a b.
HsFnPrecursor e (a -> b) -> Parameter e a -> HsFnPrecursor e b
<#> Parameter e Attr -> Parameter e (Maybe Attr)
forall e a. Parameter e a -> Parameter e (Maybe a)
opt (Peeker e Attr -> Text -> Text -> Text -> Parameter e Attr
forall e a. Peeker e a -> Text -> Text -> Text -> Parameter e a
parameter Peeker e Attr
forall e. LuaError e => Peeker e Attr
peekAttr "Attr" "attr" "link attributes")
HsFnPrecursor e (LuaE e Inline)
-> FunctionResults e Inline -> DocumentedFunction e
forall e a.
HsFnPrecursor e (LuaE e a)
-> FunctionResults e a -> DocumentedFunction e
=#> Pusher e Inline -> Text -> Text -> FunctionResults e Inline
forall e a. Pusher e a -> Text -> Text -> FunctionResults e a
functionResult Pusher e Inline
forall e. LuaError e => Pusher e Inline
pushInline "Inline" "link element"
, Name
-> (MathType -> Text -> LuaE e Inline)
-> HsFnPrecursor e (MathType -> Text -> LuaE e Inline)
forall a e. Name -> a -> HsFnPrecursor e a
defun "Math"
### liftPure2 Math
HsFnPrecursor e (MathType -> Text -> LuaE e Inline)
-> Parameter e MathType -> HsFnPrecursor e (Text -> LuaE e Inline)
forall e a b.
HsFnPrecursor e (a -> b) -> Parameter e a -> HsFnPrecursor e b
<#> Peeker e MathType -> Text -> Text -> Text -> Parameter e MathType
forall e a. Peeker e a -> Text -> Text -> Text -> Parameter e a
parameter Peeker e MathType
forall e. Peeker e MathType
peekMathType "quotetype" "Math" "rendering method"
HsFnPrecursor e (Text -> LuaE e Inline)
-> Parameter e Text -> HsFnPrecursor e (LuaE e Inline)
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" "math content"
HsFnPrecursor e (LuaE e Inline)
-> FunctionResults e Inline -> DocumentedFunction e
forall e a.
HsFnPrecursor e (LuaE e a)
-> FunctionResults e a -> DocumentedFunction e
=#> Pusher e Inline -> Text -> Text -> FunctionResults e Inline
forall e a. Pusher e a -> Text -> Text -> FunctionResults e a
functionResult Pusher e Inline
forall e. LuaError e => Pusher e Inline
pushInline "Inline" "math element"
, Name
-> ([Block] -> LuaE e Inline)
-> HsFnPrecursor e ([Block] -> LuaE e Inline)
forall a e. Name -> a -> HsFnPrecursor e a
defun "Note"
### liftPure Note
HsFnPrecursor e ([Block] -> LuaE e Inline)
-> Parameter e [Block] -> HsFnPrecursor e (LuaE e Inline)
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 "content" "Blocks" "note content"
HsFnPrecursor e (LuaE e Inline)
-> FunctionResults e Inline -> DocumentedFunction e
forall e a.
HsFnPrecursor e (LuaE e a)
-> FunctionResults e a -> DocumentedFunction e
=#> Pusher e Inline -> Text -> Text -> FunctionResults e Inline
forall e a. Pusher e a -> Text -> Text -> FunctionResults e a
functionResult Pusher e Inline
forall e. LuaError e => Pusher e Inline
pushInline "Inline" "note"
, Name
-> (QuoteType -> [Inline] -> LuaE e Inline)
-> HsFnPrecursor e (QuoteType -> [Inline] -> LuaE e Inline)
forall a e. Name -> a -> HsFnPrecursor e a
defun "Quoted"
### liftPure2 Quoted
HsFnPrecursor e (QuoteType -> [Inline] -> LuaE e Inline)
-> Parameter e QuoteType
-> HsFnPrecursor e ([Inline] -> LuaE e Inline)
forall e a b.
HsFnPrecursor e (a -> b) -> Parameter e a -> HsFnPrecursor e b
<#> Peeker e QuoteType -> Text -> Text -> Text -> Parameter e QuoteType
forall e a. Peeker e a -> Text -> Text -> Text -> Parameter e a
parameter Peeker e QuoteType
forall e. Peeker e QuoteType
peekQuoteType "quotetype" "QuoteType" "type of quotes"
HsFnPrecursor e ([Inline] -> LuaE e Inline)
-> Parameter e [Inline] -> HsFnPrecursor e (LuaE e Inline)
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 "content" "Inlines" "inlines in quotes"
HsFnPrecursor e (LuaE e Inline)
-> FunctionResults e Inline -> DocumentedFunction e
forall e a.
HsFnPrecursor e (LuaE e a)
-> FunctionResults e a -> DocumentedFunction e
=#> Pusher e Inline -> Text -> Text -> FunctionResults e Inline
forall e a. Pusher e a -> Text -> Text -> FunctionResults e a
functionResult Pusher e Inline
forall e. LuaError e => Pusher e Inline
pushInline "Inline" "quoted element"
, Name
-> (Format -> Text -> LuaE e Inline)
-> HsFnPrecursor e (Format -> Text -> LuaE e Inline)
forall a e. Name -> a -> HsFnPrecursor e a
defun "RawInline"
### liftPure2 RawInline
HsFnPrecursor e (Format -> Text -> LuaE e Inline)
-> Parameter e Format -> HsFnPrecursor e (Text -> LuaE e Inline)
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 "format" "Format" "format of content"
HsFnPrecursor e (Text -> LuaE e Inline)
-> Parameter e Text -> HsFnPrecursor e (LuaE e Inline)
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" "string content"
HsFnPrecursor e (LuaE e Inline)
-> FunctionResults e Inline -> DocumentedFunction e
forall e a.
HsFnPrecursor e (LuaE e a)
-> FunctionResults e a -> DocumentedFunction e
=#> Pusher e Inline -> Text -> Text -> FunctionResults e Inline
forall e a. Pusher e a -> Text -> Text -> FunctionResults e a
functionResult Pusher e Inline
forall e. LuaError e => Pusher e Inline
pushInline "Inline" "raw inline element"
, Name -> ([Inline] -> Inline) -> DocumentedFunction e
forall e.
LuaError e =>
Name -> ([Inline] -> Inline) -> DocumentedFunction e
mkInlinesConstr "SmallCaps" [Inline] -> Inline
SmallCaps
, Name -> LuaE e Inline -> HsFnPrecursor e (LuaE e Inline)
forall a e. Name -> a -> HsFnPrecursor e a
defun "SoftBreak"
### return SoftBreak
HsFnPrecursor e (LuaE e Inline)
-> FunctionResults e Inline -> DocumentedFunction e
forall e a.
HsFnPrecursor e (LuaE e a)
-> FunctionResults e a -> DocumentedFunction e
=#> Pusher e Inline -> Text -> Text -> FunctionResults e Inline
forall e a. Pusher e a -> Text -> Text -> FunctionResults e a
functionResult Pusher e Inline
forall e. LuaError e => Pusher e Inline
pushInline "Inline" "soft break"
, Name -> LuaE e Inline -> HsFnPrecursor e (LuaE e Inline)
forall a e. Name -> a -> HsFnPrecursor e a
defun "Space"
### return Space
HsFnPrecursor e (LuaE e Inline)
-> FunctionResults e Inline -> DocumentedFunction e
forall e a.
HsFnPrecursor e (LuaE e a)
-> FunctionResults e a -> DocumentedFunction e
=#> Pusher e Inline -> Text -> Text -> FunctionResults e Inline
forall e a. Pusher e a -> Text -> Text -> FunctionResults e a
functionResult Pusher e Inline
forall e. LuaError e => Pusher e Inline
pushInline "Inline" "new space"
, Name
-> ([Inline] -> Maybe Attr -> LuaE e Inline)
-> HsFnPrecursor e ([Inline] -> Maybe Attr -> LuaE e Inline)
forall a e. Name -> a -> HsFnPrecursor e a
defun "Span"
### liftPure2 (\inlns mattr -> Span (fromMaybe nullAttr mattr) inlns)
HsFnPrecursor e ([Inline] -> Maybe Attr -> LuaE e Inline)
-> Parameter e [Inline]
-> HsFnPrecursor e (Maybe Attr -> LuaE e Inline)
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 "content" "Inlines" "inline content"
HsFnPrecursor e (Maybe Attr -> LuaE e Inline)
-> Parameter e (Maybe Attr) -> HsFnPrecursor e (LuaE e Inline)
forall e a b.
HsFnPrecursor e (a -> b) -> Parameter e a -> HsFnPrecursor e b
<#> Parameter e Attr -> Parameter e (Maybe Attr)
forall e a. Parameter e a -> Parameter e (Maybe a)
opt (Peeker e Attr -> Text -> Text -> Text -> Parameter e Attr
forall e a. Peeker e a -> Text -> Text -> Text -> Parameter e a
parameter Peeker e Attr
forall e. LuaError e => Peeker e Attr
peekAttr "Attr" "attr" "additional attributes")
HsFnPrecursor e (LuaE e Inline)
-> FunctionResults e Inline -> DocumentedFunction e
forall e a.
HsFnPrecursor e (LuaE e a)
-> FunctionResults e a -> DocumentedFunction e
=#> Pusher e Inline -> Text -> Text -> FunctionResults e Inline
forall e a. Pusher e a -> Text -> Text -> FunctionResults e a
functionResult Pusher e Inline
forall e. LuaError e => Pusher e Inline
pushInline "Inline" "span element"
, Name
-> (Text -> LuaE e Inline)
-> HsFnPrecursor e (Text -> LuaE e Inline)
forall a e. Name -> a -> HsFnPrecursor e a
defun "Str"
### liftPure Str
HsFnPrecursor e (Text -> LuaE e Inline)
-> Parameter e Text -> HsFnPrecursor e (LuaE e Inline)
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" ""
HsFnPrecursor e (LuaE e Inline)
-> FunctionResults e Inline -> DocumentedFunction e
forall e a.
HsFnPrecursor e (LuaE e a)
-> FunctionResults e a -> DocumentedFunction e
=#> Pusher e Inline -> Text -> Text -> FunctionResults e Inline
forall e a. Pusher e a -> Text -> Text -> FunctionResults e a
functionResult Pusher e Inline
forall e. LuaError e => Pusher e Inline
pushInline "Inline" "new Str object"
, Name -> ([Inline] -> Inline) -> DocumentedFunction e
forall e.
LuaError e =>
Name -> ([Inline] -> Inline) -> DocumentedFunction e
mkInlinesConstr "Strong" [Inline] -> Inline
Strong
, Name -> ([Inline] -> Inline) -> DocumentedFunction e
forall e.
LuaError e =>
Name -> ([Inline] -> Inline) -> DocumentedFunction e
mkInlinesConstr "Strikeout" [Inline] -> Inline
Strikeout
, Name -> ([Inline] -> Inline) -> DocumentedFunction e
forall e.
LuaError e =>
Name -> ([Inline] -> Inline) -> DocumentedFunction e
mkInlinesConstr "Subscript" [Inline] -> Inline
Subscript
, Name -> ([Inline] -> Inline) -> DocumentedFunction e
forall e.
LuaError e =>
Name -> ([Inline] -> Inline) -> DocumentedFunction e
mkInlinesConstr "Superscript" [Inline] -> Inline
Superscript
, Name -> ([Inline] -> Inline) -> DocumentedFunction e
forall e.
LuaError e =>
Name -> ([Inline] -> Inline) -> DocumentedFunction e
mkInlinesConstr "Underline" [Inline] -> Inline
Underline
]
where
mkInlinesConstr :: Name -> ([Inline] -> Inline) -> DocumentedFunction e
mkInlinesConstr name :: Name
name constr :: [Inline] -> Inline
constr = Name
-> ([Inline] -> LuaE e Inline)
-> HsFnPrecursor e ([Inline] -> LuaE e Inline)
forall a e. Name -> a -> HsFnPrecursor e a
defun Name
name
### liftPure (\x -> x `seq` constr x)
HsFnPrecursor e ([Inline] -> LuaE e Inline)
-> Parameter e [Inline] -> HsFnPrecursor e (LuaE e Inline)
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 "Inlines" "content" ""
HsFnPrecursor e (LuaE e Inline)
-> FunctionResults e Inline -> DocumentedFunction e
forall e a.
HsFnPrecursor e (LuaE e a)
-> FunctionResults e a -> DocumentedFunction e
=#> Pusher e Inline -> Text -> Text -> FunctionResults e Inline
forall e a. Pusher e a -> Text -> Text -> FunctionResults e a
functionResult Pusher e Inline
forall e. LuaError e => Pusher e Inline
pushInline "Inline" "new object"
mkInlines :: LuaError e => DocumentedFunction e
mkInlines :: DocumentedFunction e
mkInlines = Name
-> ([Inline] -> LuaE e [Inline])
-> HsFnPrecursor e ([Inline] -> LuaE e [Inline])
forall a e. Name -> a -> HsFnPrecursor e a
defun "Inlines"
### liftPure id
HsFnPrecursor e ([Inline] -> LuaE e [Inline])
-> Parameter e [Inline] -> HsFnPrecursor e (LuaE e [Inline])
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 "Inlines" "inlines" "inline elements"
HsFnPrecursor e (LuaE e [Inline])
-> FunctionResults e [Inline] -> DocumentedFunction e
forall e a.
HsFnPrecursor e (LuaE e a)
-> FunctionResults e a -> DocumentedFunction e
=#> Pusher e [Inline] -> Text -> Text -> FunctionResults e [Inline]
forall e a. Pusher e a -> Text -> Text -> FunctionResults e a
functionResult Pusher e [Inline]
forall e. LuaError e => Pusher e [Inline]
pushInlines "Inlines" "list of inline elements"
walkInlineSplicing :: (LuaError e, Walkable (SpliceList Inline) a)
=> Filter -> a -> LuaE e a
walkInlineSplicing :: Filter -> a -> LuaE e a
walkInlineSplicing = Pusher e Inline -> Peeker e [Inline] -> Filter -> a -> LuaE e a
forall e a b.
(LuaError e, Data a, Walkable (SpliceList a) b) =>
Pusher e a -> Peeker e [a] -> Filter -> b -> LuaE e b
walkSplicing Pusher e Inline
forall e. LuaError e => Pusher e Inline
pushInline Peeker e [Inline]
forall e. LuaError e => Peeker e [Inline]
peekInlinesFuzzy
walkInlinesStraight :: (LuaError e, Walkable [Inline] a)
=> Filter -> a -> LuaE e a
walkInlinesStraight :: Filter -> a -> LuaE e a
walkInlinesStraight = Name
-> Pusher e [Inline]
-> Peeker e [Inline]
-> Filter
-> a
-> LuaE e a
forall e a b.
(LuaError e, Walkable a b) =>
Name -> Pusher e a -> Peeker e a -> Filter -> b -> LuaE e b
walkStraight "Inlines" Pusher e [Inline]
forall e. LuaError e => Pusher e [Inline]
pushInlines Peeker e [Inline]
forall e. LuaError e => Peeker e [Inline]
peekInlinesFuzzy