{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TypeApplications #-}
{-# LANGUAGE TupleSections #-}
module Text.Pandoc.Lua.Marshal.Inline
( typeInline
, 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.Aeson (encode)
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 Data.Text as T
import qualified Text.Pandoc.Builder as B
pushInline :: LuaError e => Pusher e Inline
pushInline :: forall e. LuaError e => Pusher e Inline
pushInline = DocumentedTypeWithList e Inline Void -> Inline -> LuaE e ()
forall e a itemtype.
LuaError e =>
DocumentedTypeWithList e a itemtype -> a -> LuaE e ()
pushUD DocumentedTypeWithList e Inline Void
forall e. LuaError e => DocumentedType e Inline
typeInline
{-# INLINE pushInline #-}
peekInline :: LuaError e => Peeker e Inline
peekInline :: forall e. LuaError e => Peeker e Inline
peekInline = DocumentedTypeWithList e Inline Void -> Peeker e Inline
forall e a itemtype.
LuaError e =>
DocumentedTypeWithList e a itemtype -> Peeker e a
peekUD DocumentedTypeWithList e Inline Void
forall e. LuaError e => DocumentedType e Inline
typeInline
{-# INLINE peekInline #-}
peekInlines :: LuaError e
=> Peeker e [Inline]
peekInlines :: forall e. LuaError e => 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 :: forall e. LuaError e => Pusher e [Inline]
pushInlines [Inline]
xs = do
Pusher e Inline -> [Inline] -> LuaE e ()
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 Name
"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 Name
"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]
-> TypeSpec -> Text -> Text -> Parameter e [Inline]
forall e a. Peeker e a -> TypeSpec -> Text -> Text -> Parameter e a
parameter Peeker e [Inline]
forall e. LuaError e => Peeker e [Inline]
peekInlinesFuzzy TypeSpec
"Blocks" Text
"self" Text
""
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 -> TypeSpec -> Text -> Text -> Parameter e Filter
forall e a. Peeker e a -> TypeSpec -> Text -> Text -> Parameter e a
parameter Peeker e Filter
forall e. LuaError e => Peeker e Filter
peekFilter TypeSpec
"Filter" Text
"lua_filter" Text
"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
=#> ([Inline] -> LuaE e ())
-> TypeSpec -> Text -> FunctionResults e [Inline]
forall e a. Pusher e a -> TypeSpec -> Text -> FunctionResults e a
functionResult [Inline] -> LuaE e ()
forall e. LuaError e => Pusher e [Inline]
pushInlines TypeSpec
"Blocks" Text
"modified list"
StackIndex -> LuaE e ()
forall e. LuaError e => StackIndex -> LuaE e ()
rawset (CInt -> StackIndex
nth CInt
3)
Name -> LuaE e ()
forall e. Name -> LuaE e ()
pushName Name
"clone"
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] -> LuaE e [Inline])
-> HsFnPrecursor e ([Inline] -> LuaE e [Inline])
forall a e. a -> HsFnPrecursor e a
lambda
### 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]
-> TypeSpec -> Text -> Text -> Parameter e [Inline]
forall e a. Peeker e a -> TypeSpec -> Text -> Text -> Parameter e a
parameter Peeker e [Inline]
forall e. LuaError e => Peeker e [Inline]
peekInlinesFuzzy TypeSpec
"Inlines" Text
"self" Text
""
HsFnPrecursor e (LuaE e [Inline])
-> FunctionResults e [Inline] -> DocumentedFunction e
forall e a.
HsFnPrecursor e (LuaE e a)
-> FunctionResults e a -> DocumentedFunction e
=#> ([Inline] -> LuaE e ())
-> TypeSpec -> Text -> FunctionResults e [Inline]
forall e a. Pusher e a -> TypeSpec -> Text -> FunctionResults e a
functionResult [Inline] -> LuaE e ()
forall e. LuaError e => Pusher e [Inline]
pushInlines TypeSpec
"Inlines" Text
"deep copy"
StackIndex -> LuaE e ()
forall e. LuaError e => StackIndex -> LuaE e ()
rawset (CInt -> StackIndex
nth CInt
3)
Name -> LuaE e ()
forall e. Name -> LuaE e ()
pushName Name
"__tostring"
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] -> LuaE e String)
-> HsFnPrecursor e ([Inline] -> LuaE e String)
forall a e. a -> HsFnPrecursor e a
lambda
### liftPure show
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]
-> TypeSpec -> Text -> Text -> Parameter e [Inline]
forall e a. Peeker e a -> TypeSpec -> Text -> Text -> Parameter e a
parameter Peeker e [Inline]
forall e. LuaError e => Peeker e [Inline]
peekInlinesFuzzy TypeSpec
"Inlines" 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 -> TypeSpec -> Text -> FunctionResults e String
forall e a. Pusher e a -> TypeSpec -> Text -> FunctionResults e a
functionResult Pusher e String
forall e. String -> LuaE e ()
pushString TypeSpec
"string" Text
"native Haskell representation"
StackIndex -> LuaE e ()
forall e. LuaError e => StackIndex -> LuaE e ()
rawset (CInt -> StackIndex
nth CInt
3)
Name -> LuaE e ()
forall e. Name -> LuaE e ()
pushName Name
"__tojson"
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] -> LuaE e ByteString)
-> HsFnPrecursor e ([Inline] -> LuaE e ByteString)
forall a e. a -> HsFnPrecursor e a
lambda
### liftPure encode
HsFnPrecursor e ([Inline] -> LuaE e ByteString)
-> Parameter e [Inline] -> HsFnPrecursor e (LuaE e ByteString)
forall e a b.
HsFnPrecursor e (a -> b) -> Parameter e a -> HsFnPrecursor e b
<#> Peeker e [Inline]
-> TypeSpec -> Text -> Text -> Parameter e [Inline]
forall e a. Peeker e a -> TypeSpec -> Text -> Text -> Parameter e a
parameter Peeker e [Inline]
forall e. LuaError e => Peeker e [Inline]
peekInlinesFuzzy TypeSpec
"Inlines" Text
"self" Text
""
HsFnPrecursor e (LuaE e ByteString)
-> FunctionResults e ByteString -> DocumentedFunction e
forall e a.
HsFnPrecursor e (LuaE e a)
-> FunctionResults e a -> DocumentedFunction e
=#> Pusher e ByteString
-> TypeSpec -> Text -> FunctionResults e ByteString
forall e a. Pusher e a -> TypeSpec -> Text -> FunctionResults e a
functionResult Pusher e ByteString
forall e. Pusher e ByteString
pushLazyByteString TypeSpec
"string" Text
"JSON representation"
StackIndex -> LuaE e ()
forall e. LuaError e => StackIndex -> LuaE e ()
rawset (CInt -> StackIndex
nth CInt
3)
StackIndex -> LuaE e ()
forall e. StackIndex -> LuaE e ()
setmetatable (CInt -> StackIndex
nth CInt
2)
{-# INLINABLE pushInlines #-}
peekInlineMetamethod :: LuaError e
=> Peeker e Inline
peekInlineMetamethod :: forall e. LuaError e => Peeker e Inline
peekInlineMetamethod StackIndex
idx = do
StackIndex
absidx <- LuaE e StackIndex -> Peek e StackIndex
forall e a. LuaE e a -> Peek e a
liftLua (LuaE e StackIndex -> Peek e StackIndex)
-> LuaE e StackIndex -> Peek e StackIndex
forall a b. (a -> b) -> a -> b
$ StackIndex -> LuaE e StackIndex
forall e. StackIndex -> LuaE e StackIndex
absindex StackIndex
idx
LuaE e Type -> Peek e Type
forall e a. LuaE e a -> Peek e a
liftLua (StackIndex -> Name -> LuaE e Type
forall e. StackIndex -> Name -> LuaE e Type
getmetafield StackIndex
absidx Name
"__toinline") Peek e Type -> (Type -> Peek e Inline) -> Peek e Inline
forall a b. Peek e a -> (a -> Peek e b) -> Peek e b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \case
Type
TypeNil -> ByteString -> Peek e Inline
forall a e. ByteString -> Peek e a
failPeek ByteString
"object has no __toinline metamethod"
Type
TypeFunction -> do
LuaE e () -> Peek e ()
forall e a. LuaE e a -> Peek e a
liftLua (StackIndex -> LuaE e ()
forall e. StackIndex -> LuaE e ()
pushvalue StackIndex
absidx)
LuaE e Status -> Peek e Status
forall e a. LuaE e a -> Peek e a
liftLua (NumArgs -> NumResults -> Maybe StackIndex -> LuaE e Status
forall e.
NumArgs -> NumResults -> Maybe StackIndex -> LuaE e Status
pcall NumArgs
1 NumResults
1 Maybe StackIndex
forall a. Maybe a
Nothing) Peek e Status -> (Status -> Peek e Inline) -> Peek e Inline
forall a b. Peek e a -> (a -> Peek e b) -> Peek e b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \case
Status
OK -> Peeker e Inline
forall e. LuaError e => Peeker e Inline
peekInline StackIndex
top Peek e Inline -> LuaE e () -> Peek e Inline
forall e a b. Peek e a -> LuaE e b -> Peek e a
`lastly` Int -> LuaE e ()
forall e. Int -> LuaE e ()
pop Int
1
Status
_err -> do
ByteString
msg <- Peeker e ByteString
forall e. Peeker e ByteString
peekByteString StackIndex
top Peek e ByteString -> LuaE e () -> Peek e ByteString
forall e a b. Peek e a -> LuaE e b -> Peek e a
`lastly` Int -> LuaE e ()
forall e. Int -> LuaE e ()
pop Int
1
ByteString -> Peek e Inline
forall a e. ByteString -> Peek e a
failPeek (ByteString -> Peek e Inline) -> ByteString -> Peek e Inline
forall a b. (a -> b) -> a -> b
$ ByteString
"failure in __toinline: " ByteString -> ByteString -> ByteString
forall a. Semigroup a => a -> a -> a
<> ByteString
msg
Type
_otherType -> do
LuaE e () -> Peek e ()
forall e a. LuaE e a -> Peek e a
liftLua (Int -> LuaE e ()
forall e. Int -> LuaE e ()
pop Int
1)
ByteString -> Peek e Inline
forall a e. ByteString -> Peek e a
failPeek ByteString
"__toinline metafield does not contain a function"
peekInlineFuzzy :: LuaError e => Peeker e Inline
peekInlineFuzzy :: forall e. LuaError e => Peeker e Inline
peekInlineFuzzy StackIndex
idx = Name -> Peek e Inline -> Peek e Inline
forall e a. Name -> Peek e a -> Peek e a
retrieving Name
"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 a b. Peek e a -> (a -> Peek e b) -> Peek e b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \case
Type
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
Type
TypeTable -> Peeker e Inline
forall e. LuaError e => Peeker e Inline
peekInlineMetamethod StackIndex
idx Peek e Inline -> Peek e Inline -> Peek e Inline
forall a. Peek e a -> Peek e a -> Peek e a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> Peeker e Inline
forall e. LuaError e => Peeker e Inline
peekInline StackIndex
idx
Type
_ -> Peeker e Inline
forall e. LuaError e => Peeker e Inline
peekInline StackIndex
idx Peek e Inline -> Peek e Inline -> Peek e Inline
forall a. Peek e a -> Peek e a -> Peek e a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> Peeker e Inline
forall e. LuaError e => Peeker e Inline
peekInlineMetamethod StackIndex
idx
{-# INLINABLE peekInlineFuzzy #-}
peekInlinesFuzzy :: LuaError e
=> Peeker e [Inline]
peekInlinesFuzzy :: forall e. LuaError e => Peeker e [Inline]
peekInlinesFuzzy 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 a b. Peek e a -> (a -> Peek e b) -> Peek e b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \case
Type
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
Type
_ -> 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 a. Peek e a -> Peek e a -> Peek e a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> (Inline -> [Inline]
forall a. a -> [a]
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 a. Peek e a -> Peek e a -> Peek e a
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 Name
"Inline, list of Inlines, or string" StackIndex
idx)
{-# INLINABLE peekInlinesFuzzy #-}
typeInline :: forall e. LuaError e => DocumentedType e Inline
typeInline :: forall e. LuaError e => 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 Name
"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 -> TypeSpec -> Text -> Text -> Parameter e Inline
forall e a. Peeker e a -> TypeSpec -> Text -> Text -> Parameter e a
parameter Peeker e Inline
forall e. LuaError e => Peeker e Inline
peekInline TypeSpec
"inline" Text
"Inline" Text
"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 -> TypeSpec -> Text -> FunctionResults e String
forall e a. Pusher e a -> TypeSpec -> Text -> FunctionResults e a
functionResult Pusher e String
forall e. String -> LuaE e ()
pushString TypeSpec
"string" Text
"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 Name
"__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)
-> TypeSpec -> Text -> Text -> Parameter e (Maybe Inline)
forall e a. Peeker e a -> TypeSpec -> 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) TypeSpec
"a" Text
"Inline" Text
""
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)
-> TypeSpec -> Text -> Text -> Parameter e (Maybe Inline)
forall e a. Peeker e a -> TypeSpec -> 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) TypeSpec
"b" Text
"Inline" Text
""
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 -> TypeSpec -> Text -> FunctionResults e Bool
forall e a. Pusher e a -> TypeSpec -> Text -> FunctionResults e a
functionResult Pusher e Bool
forall e. Pusher e Bool
pushBool TypeSpec
"boolean" Text
"whether the two are equal"
, Operation
-> DocumentedFunction e -> (Operation, DocumentedFunction e)
forall e.
Operation
-> DocumentedFunction e -> (Operation, DocumentedFunction e)
operation (Name -> Operation
CustomOperation Name
"__tojson") (DocumentedFunction e -> (Operation, DocumentedFunction e))
-> DocumentedFunction e -> (Operation, DocumentedFunction e)
forall a b. (a -> b) -> a -> b
$ (Inline -> LuaE e ByteString)
-> HsFnPrecursor e (Inline -> LuaE e ByteString)
forall a e. a -> HsFnPrecursor e a
lambda
### liftPure encode
HsFnPrecursor e (Inline -> LuaE e ByteString)
-> Parameter e Inline -> HsFnPrecursor e (LuaE e ByteString)
forall e a b.
HsFnPrecursor e (a -> b) -> Parameter e a -> HsFnPrecursor e b
<#> DocumentedType e Inline -> Text -> Text -> Parameter e Inline
forall e a itemtype.
LuaError e =>
DocumentedTypeWithList e a itemtype
-> Text -> Text -> Parameter e a
udparam DocumentedType e Inline
forall e. LuaError e => DocumentedType e Inline
typeInline Text
"self" Text
""
HsFnPrecursor e (LuaE e ByteString)
-> FunctionResults e ByteString -> DocumentedFunction e
forall e a.
HsFnPrecursor e (LuaE e a)
-> FunctionResults e a -> DocumentedFunction e
=#> Pusher e ByteString
-> TypeSpec -> Text -> FunctionResults e ByteString
forall e a. Pusher e a -> TypeSpec -> Text -> FunctionResults e a
functionResult Pusher e ByteString
forall e. Pusher e ByteString
pushLazyByteString TypeSpec
"string" Text
"JSON representation"
]
[ 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 Name
"attr" Text
"element attributes"
(Pusher e Attr
forall e. LuaError e => Pusher e Attr
pushAttr, \case
Code Attr
attr Text
_ -> Attr -> Possible Attr
forall a. a -> Possible a
Actual Attr
attr
Image Attr
attr [Inline]
_ Target
_ -> Attr -> Possible Attr
forall a. a -> Possible a
Actual Attr
attr
Link Attr
attr [Inline]
_ Target
_ -> Attr -> Possible Attr
forall a. a -> Possible a
Actual Attr
attr
Span Attr
attr [Inline]
_ -> Attr -> Possible Attr
forall a. a -> Possible a
Actual Attr
attr
Inline
_ -> Possible Attr
forall a. Possible a
Absent)
(Peeker e Attr
forall e. LuaError e => Peeker e Attr
peekAttr, \case
Code Attr
_ 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 Attr
_ [Inline]
cpt 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 -> [Inline] -> Target -> Inline
Image Attr
attr [Inline]
cpt Target
tgt
Link Attr
_ [Inline]
cpt 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 -> [Inline] -> Target -> Inline
Link Attr
attr [Inline]
cpt Target
tgt
Span Attr
_ [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)
Inline
_ -> 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 Name
"caption" Text
"image caption"
(Pusher e [Inline]
forall e. LuaError e => Pusher e [Inline]
pushInlines, \case
Image Attr
_ [Inline]
capt Target
_ -> [Inline] -> Possible [Inline]
forall a. a -> Possible a
Actual [Inline]
capt
Inline
_ -> Possible [Inline]
forall a. Possible a
Absent)
(Peeker e [Inline]
forall e. LuaError e => Peeker e [Inline]
peekInlinesFuzzy, \case
Image Attr
attr [Inline]
_ 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
. (\[Inline]
capt -> Attr -> [Inline] -> Target -> Inline
Image Attr
attr [Inline]
capt Target
target)
Inline
_ -> 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 Name
"citations" Text
"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 [Citation]
cs [Inline]
_ -> [Citation] -> Possible [Citation]
forall a. a -> Possible a
Actual [Citation]
cs
Inline
_ -> 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 [Citation]
_ [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)
Inline
_ -> 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 Name
"content" Text
"element contents"
(Pusher e Content
forall e. LuaError e => Pusher e Content
pushContent, \case
Cite [Citation]
_ [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 [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 Attr
_ [Inline]
inlns Target
_ -> 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 QuoteType
_ [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 [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 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
Strikeout [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 [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 [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 [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 [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 [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
Inline
_ -> 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 [Inline]
inlns -> [Inline]
inlns
Content
c -> e -> [Inline]
forall e a. (HasCallStack, Exception e) => e -> [a]
forall (m :: * -> *) e a.
(MonadThrow m, HasCallStack, Exception e) =>
e -> m a
throwM (e -> [Inline]) -> (String -> e) -> String -> [Inline]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. 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 [] -> []
Content
c -> e -> [Block]
forall e a. (HasCallStack, Exception e) => e -> [a]
forall (m :: * -> *) e a.
(MonadThrow m, HasCallStack, Exception e) =>
e -> m a
throwM (e -> [Block]) -> (String -> e) -> String -> [Block]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. 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
in \case
Cite [Citation]
cs [Inline]
_ -> 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]
_ -> 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 Attr
a [Inline]
_ 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
. (\[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 QuoteType
qt [Inline]
_ -> 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]
_ -> 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 [Inline]
_ -> 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]
_ -> 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]
_ -> 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]
_ -> 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]
_ -> 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]
_ -> 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 [Block]
_ -> 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
Inline
_ -> 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 Name
"format" Text
"format of raw text"
(Pusher e Format
forall e. Pusher e Format
pushFormat, \case
RawInline Format
fmt Text
_ -> Format -> Possible Format
forall a. a -> Possible a
Actual Format
fmt
Inline
_ -> Possible Format
forall a. Possible a
Absent)
(Peeker e Format
forall e. Peeker e Format
peekFormat, \case
RawInline Format
_ 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)
Inline
_ -> 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 Name
"mathtype" Text
"math rendering method"
(Pusher e MathType
forall e. Pusher e MathType
pushMathType, \case
Math MathType
mt Text
_ -> MathType -> Possible MathType
forall a. a -> Possible a
Actual MathType
mt
Inline
_ -> Possible MathType
forall a. Possible a
Absent)
(Peeker e MathType
forall e. Peeker e MathType
peekMathType, \case
Math MathType
_ 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)
Inline
_ -> 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 Name
"quotetype" Text
"type of quotes (single or double)"
(Pusher e QuoteType
forall e. Pusher e QuoteType
pushQuoteType, \case
Quoted QuoteType
qt [Inline]
_ -> QuoteType -> Possible QuoteType
forall a. a -> Possible a
Actual QuoteType
qt
Inline
_ -> Possible QuoteType
forall a. Possible a
Absent)
(Peeker e QuoteType
forall e. Peeker e QuoteType
peekQuoteType, \case
Quoted QuoteType
_ [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)
Inline
_ -> 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 Name
"src" Text
"image source"
(Pusher e Text
forall e. Pusher e Text
pushText, \case
Image Attr
_ [Inline]
_ (Text
src, Text
_) -> Text -> Possible Text
forall a. a -> Possible a
Actual Text
src
Inline
_ -> Possible Text
forall a. Possible a
Absent)
(Peeker e Text
forall e. Peeker e Text
peekText, \case
Image Attr
attr [Inline]
capt (Text
_, 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)
Inline
_ -> 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 Name
"target" Text
"link target URL"
(Pusher e Text
forall e. Pusher e Text
pushText, \case
Link Attr
_ [Inline]
_ (Text
tgt, Text
_) -> Text -> Possible Text
forall a. a -> Possible a
Actual Text
tgt
Inline
_ -> Possible Text
forall a. Possible a
Absent)
(Peeker e Text
forall e. Peeker e Text
peekText, \case
Link Attr
attr [Inline]
capt (Text
_, 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)
Inline
_ -> 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 Name
"title" Text
"title text"
(Pusher e Text
forall e. Pusher e Text
pushText, \case
Image Attr
_ [Inline]
_ (Text
_, Text
tit) -> Text -> Possible Text
forall a. a -> Possible a
Actual Text
tit
Link Attr
_ [Inline]
_ (Text
_, Text
tit) -> Text -> Possible Text
forall a. a -> Possible a
Actual Text
tit
Inline
_ -> Possible Text
forall a. Possible a
Absent)
(Peeker e Text
forall e. Peeker e Text
peekText, \case
Image Attr
attr [Inline]
capt (Text
src, Text
_) -> 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 [Inline]
capt (Text
src, Text
_) -> 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,)
Inline
_ -> 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 Name
"text" 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 Name
"tag" Text
"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 AliasIndex
"t" Text
"tag" [AliasIndex
"tag"]
, AliasIndex
-> Text -> [AliasIndex] -> Member e (DocumentedFunction e) Inline
forall e fn a. AliasIndex -> Text -> [AliasIndex] -> Member e fn a
alias AliasIndex
"c" Text
"content" [AliasIndex
"content"]
, AliasIndex
-> Text -> [AliasIndex] -> Member e (DocumentedFunction e) Inline
forall e fn a. AliasIndex -> Text -> [AliasIndex] -> Member e fn a
alias AliasIndex
"identifier" Text
"element identifier" [AliasIndex
"attr", AliasIndex
"identifier"]
, AliasIndex
-> Text -> [AliasIndex] -> Member e (DocumentedFunction e) Inline
forall e fn a. AliasIndex -> Text -> [AliasIndex] -> Member e fn a
alias AliasIndex
"classes" Text
"element classes" [AliasIndex
"attr", AliasIndex
"classes"]
, AliasIndex
-> Text -> [AliasIndex] -> Member e (DocumentedFunction e) Inline
forall e fn a. AliasIndex -> Text -> [AliasIndex] -> Member e fn a
alias AliasIndex
"attributes" Text
"other element attributes" [AliasIndex
"attr", AliasIndex
"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 Name
"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 -> TypeSpec -> Text -> Text -> Parameter e Inline
forall e a. Peeker e a -> TypeSpec -> Text -> Text -> Parameter e a
parameter Peeker e Inline
forall e. LuaError e => Peeker e Inline
peekInline TypeSpec
"inline" Text
"Inline" Text
"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 -> TypeSpec -> Text -> FunctionResults e Inline
forall e a. Pusher e a -> TypeSpec -> Text -> FunctionResults e a
functionResult Pusher e Inline
forall e. LuaError e => Pusher e Inline
pushInline TypeSpec
"Inline" Text
"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 Name
"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 -> TypeSpec -> Text -> Text -> Parameter e Inline
forall e a. Peeker e a -> TypeSpec -> Text -> Text -> Parameter e a
parameter Peeker e Inline
forall e. LuaError e => Peeker e Inline
peekInline TypeSpec
"Inline" Text
"self" Text
""
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 -> TypeSpec -> Text -> Text -> Parameter e Filter
forall e a. Peeker e a -> TypeSpec -> Text -> Text -> Parameter e a
parameter Peeker e Filter
forall e. LuaError e => Peeker e Filter
peekFilter TypeSpec
"Filter" Text
"lua_filter" Text
"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 -> TypeSpec -> Text -> FunctionResults e Inline
forall e a. Pusher e a -> TypeSpec -> Text -> FunctionResults e a
functionResult Pusher e Inline
forall e. LuaError e => Pusher e Inline
pushInline TypeSpec
"Inline" Text
"modified element"
]
getInlineText :: Inline -> Possible Text
getInlineText :: Inline -> Possible Text
getInlineText = \case
Code Attr
_ Text
lst -> Text -> Possible Text
forall a. a -> Possible a
Actual Text
lst
Math MathType
_ Text
str -> Text -> Possible Text
forall a. a -> Possible a
Actual Text
str
RawInline Format
_ Text
raw -> Text -> Possible Text
forall a. a -> Possible a
Actual Text
raw
Str Text
s -> Text -> Possible Text
forall a. a -> Possible a
Actual Text
s
Inline
_ -> Possible Text
forall a. Possible a
Absent
setInlineText :: Inline -> Text -> Possible Inline
setInlineText :: Inline -> Text -> Possible Inline
setInlineText = \case
Code Attr
attr Text
_ -> 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 MathType
mt Text
_ -> 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 Format
f Text
_ -> 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 Text
_ -> 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
Inline
_ -> 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 :: forall e. LuaError e => [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 Name
"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]
-> TypeSpec -> Text -> Text -> Parameter e [Inline]
forall e a. Peeker e a -> TypeSpec -> Text -> Text -> Parameter e a
parameter Peeker e [Inline]
forall e. LuaError e => Peeker e [Inline]
peekInlinesFuzzy TypeSpec
"content" Text
"Inlines" Text
"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]
-> TypeSpec -> Text -> Text -> Parameter e [Citation]
forall e a. Peeker e a -> TypeSpec -> 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) TypeSpec
"{Citation,...}" Text
"citations"
Text
"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 -> TypeSpec -> Text -> FunctionResults e Inline
forall e a. Pusher e a -> TypeSpec -> Text -> FunctionResults e a
functionResult Pusher e Inline
forall e. LuaError e => Pusher e Inline
pushInline TypeSpec
"Inline" Text
"cite element"
#? "Creates a Cite inline 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 Name
"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 Text
"code" Text
"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 -> TypeSpec -> Text -> Text -> Parameter e Attr
forall e a. Peeker e a -> TypeSpec -> Text -> Text -> Parameter e a
parameter Peeker e Attr
forall e. LuaError e => Peeker e Attr
peekAttr TypeSpec
"Attr" Text
"attr" Text
"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 -> TypeSpec -> Text -> FunctionResults e Inline
forall e a. Pusher e a -> TypeSpec -> Text -> FunctionResults e a
functionResult Pusher e Inline
forall e. LuaError e => Pusher e Inline
pushInline TypeSpec
"Inline" Text
"code element"
#? "Creates a Code inline element"
, Name -> ([Inline] -> Inline) -> DocumentedFunction e
forall {e}.
LuaError e =>
Name -> ([Inline] -> Inline) -> DocumentedFunction e
mkInlinesConstr Name
"Emph" [Inline] -> Inline
Emph
#? "Creates an inline element representing emphasized text."
, 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 Name
"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]
-> TypeSpec -> Text -> Text -> Parameter e [Inline]
forall e a. Peeker e a -> TypeSpec -> Text -> Text -> Parameter e a
parameter Peeker e [Inline]
forall e. LuaError e => Peeker e [Inline]
peekInlinesFuzzy TypeSpec
"Inlines" Text
"caption"
Text
"text used to describe the image"
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 Text
"src" Text
"path to 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 Text
"title" Text
"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 -> TypeSpec -> Text -> Text -> Parameter e Attr
forall e a. Peeker e a -> TypeSpec -> Text -> Text -> Parameter e a
parameter Peeker e Attr
forall e. LuaError e => Peeker e Attr
peekAttr TypeSpec
"Attr" Text
"attr" Text
"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 -> TypeSpec -> Text -> FunctionResults e Inline
forall e a. Pusher e a -> TypeSpec -> Text -> FunctionResults e a
functionResult Pusher e Inline
forall e. LuaError e => Pusher e Inline
pushInline TypeSpec
"Inline" Text
"Image element"
#? "Creates an Image element"
, Name -> LuaE e Inline -> HsFnPrecursor e (LuaE e Inline)
forall a e. Name -> a -> HsFnPrecursor e a
defun Name
"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 -> TypeSpec -> Text -> FunctionResults e Inline
forall e a. Pusher e a -> TypeSpec -> Text -> FunctionResults e a
functionResult Pusher e Inline
forall e. LuaError e => Pusher e Inline
pushInline TypeSpec
"Inline" Text
"line break"
#? "Create a LineBreak inline element"
, 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 Name
"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]
-> TypeSpec -> Text -> Text -> Parameter e [Inline]
forall e a. Peeker e a -> TypeSpec -> Text -> Text -> Parameter e a
parameter Peeker e [Inline]
forall e. LuaError e => Peeker e [Inline]
peekInlinesFuzzy TypeSpec
"Inlines" Text
"content" Text
"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 Text
"target" Text
"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 Text
"title" Text
"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 -> TypeSpec -> Text -> Text -> Parameter e Attr
forall e a. Peeker e a -> TypeSpec -> Text -> Text -> Parameter e a
parameter Peeker e Attr
forall e. LuaError e => Peeker e Attr
peekAttr TypeSpec
"Attr" Text
"attr" Text
"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 -> TypeSpec -> Text -> FunctionResults e Inline
forall e a. Pusher e a -> TypeSpec -> Text -> FunctionResults e a
functionResult Pusher e Inline
forall e. LuaError e => Pusher e Inline
pushInline TypeSpec
"Inline" Text
"link element"
#? "Creates a link inline element, usually a hyperlink."
, Name
-> (MathType -> Text -> LuaE e Inline)
-> HsFnPrecursor e (MathType -> Text -> LuaE e Inline)
forall a e. Name -> a -> HsFnPrecursor e a
defun Name
"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
-> TypeSpec -> Text -> Text -> Parameter e MathType
forall e a. Peeker e a -> TypeSpec -> Text -> Text -> Parameter e a
parameter Peeker e MathType
forall e. Peeker e MathType
peekMathType TypeSpec
"MathType" Text
"mathtype" Text
"rendering specifier"
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
"text" 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 -> TypeSpec -> Text -> FunctionResults e Inline
forall e a. Pusher e a -> TypeSpec -> Text -> FunctionResults e a
functionResult Pusher e Inline
forall e. LuaError e => Pusher e Inline
pushInline TypeSpec
"Inline" Text
"math element"
#? "Creates a Math element, either inline or displayed."
, Name
-> ([Block] -> LuaE e Inline)
-> HsFnPrecursor e ([Block] -> LuaE e Inline)
forall a e. Name -> a -> HsFnPrecursor e a
defun Name
"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] -> TypeSpec -> Text -> Text -> Parameter e [Block]
forall e a. Peeker e a -> TypeSpec -> Text -> Text -> Parameter e a
parameter Peeker e [Block]
forall e. LuaError e => Peeker e [Block]
peekBlocksFuzzy TypeSpec
"Blocks" Text
"content" Text
"footnote block 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 -> TypeSpec -> Text -> FunctionResults e Inline
forall e a. Pusher e a -> TypeSpec -> Text -> FunctionResults e a
functionResult Pusher e Inline
forall e. LuaError e => Pusher e Inline
pushInline TypeSpec
"Inline" Text
"note"
#? "Creates a Note inline element"
, Name
-> (QuoteType -> [Inline] -> LuaE e Inline)
-> HsFnPrecursor e (QuoteType -> [Inline] -> LuaE e Inline)
forall a e. Name -> a -> HsFnPrecursor e a
defun Name
"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
-> TypeSpec -> Text -> Text -> Parameter e QuoteType
forall e a. Peeker e a -> TypeSpec -> Text -> Text -> Parameter e a
parameter Peeker e QuoteType
forall e. Peeker e QuoteType
peekQuoteType TypeSpec
"QuoteType" Text
"quotetype" Text
"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]
-> TypeSpec -> Text -> Text -> Parameter e [Inline]
forall e a. Peeker e a -> TypeSpec -> Text -> Text -> Parameter e a
parameter Peeker e [Inline]
forall e. LuaError e => Peeker e [Inline]
peekInlinesFuzzy TypeSpec
"Inlines" Text
"content" Text
"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 -> TypeSpec -> Text -> FunctionResults e Inline
forall e a. Pusher e a -> TypeSpec -> Text -> FunctionResults e a
functionResult Pusher e Inline
forall e. LuaError e => Pusher e Inline
pushInline TypeSpec
"Inline" Text
"quoted element"
#? ("Creates a Quoted inline element given the quote type and " <>
"quoted content.")
, Name
-> (Format -> Text -> LuaE e Inline)
-> HsFnPrecursor e (Format -> Text -> LuaE e Inline)
forall a e. Name -> a -> HsFnPrecursor e a
defun Name
"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 -> TypeSpec -> Text -> Text -> Parameter e Format
forall e a. Peeker e a -> TypeSpec -> Text -> Text -> Parameter e a
parameter Peeker e Format
forall e. Peeker e Format
peekFormat TypeSpec
"string" Text
"format" Text
"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
"text" 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 -> TypeSpec -> Text -> FunctionResults e Inline
forall e a. Pusher e a -> TypeSpec -> Text -> FunctionResults e a
functionResult Pusher e Inline
forall e. LuaError e => Pusher e Inline
pushInline TypeSpec
"Inline" Text
"raw inline element"
#? "Creates a raw inline element"
, Name -> ([Inline] -> Inline) -> DocumentedFunction e
forall {e}.
LuaError e =>
Name -> ([Inline] -> Inline) -> DocumentedFunction e
mkInlinesConstr Name
"SmallCaps" [Inline] -> Inline
SmallCaps
#? "Creates text rendered in small caps"
, Name -> LuaE e Inline -> HsFnPrecursor e (LuaE e Inline)
forall a e. Name -> a -> HsFnPrecursor e a
defun Name
"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 -> TypeSpec -> Text -> FunctionResults e Inline
forall e a. Pusher e a -> TypeSpec -> Text -> FunctionResults e a
functionResult Pusher e Inline
forall e. LuaError e => Pusher e Inline
pushInline TypeSpec
"Inline" Text
"soft break"
#? "Creates a SoftBreak inline element."
, Name -> LuaE e Inline -> HsFnPrecursor e (LuaE e Inline)
forall a e. Name -> a -> HsFnPrecursor e a
defun Name
"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 -> TypeSpec -> Text -> FunctionResults e Inline
forall e a. Pusher e a -> TypeSpec -> Text -> FunctionResults e a
functionResult Pusher e Inline
forall e. LuaError e => Pusher e Inline
pushInline TypeSpec
"Inline" Text
"new space"
#? "Create a Space inline element"
, Name
-> ([Inline] -> Maybe Attr -> LuaE e Inline)
-> HsFnPrecursor e ([Inline] -> Maybe Attr -> LuaE e Inline)
forall a e. Name -> a -> HsFnPrecursor e a
defun Name
"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]
-> TypeSpec -> Text -> Text -> Parameter e [Inline]
forall e a. Peeker e a -> TypeSpec -> Text -> Text -> Parameter e a
parameter Peeker e [Inline]
forall e. LuaError e => Peeker e [Inline]
peekInlinesFuzzy TypeSpec
"Inlines" Text
"content" Text
"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 -> TypeSpec -> Text -> Text -> Parameter e Attr
forall e a. Peeker e a -> TypeSpec -> Text -> Text -> Parameter e a
parameter Peeker e Attr
forall e. LuaError e => Peeker e Attr
peekAttr TypeSpec
"Attr" Text
"attr" Text
"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 -> TypeSpec -> Text -> FunctionResults e Inline
forall e a. Pusher e a -> TypeSpec -> Text -> FunctionResults e a
functionResult Pusher e Inline
forall e. LuaError e => Pusher e Inline
pushInline TypeSpec
"Inline" Text
"[[Span]] object"
#? "Creates a Span inline element"
, Name
-> (Text -> LuaE e Inline)
-> HsFnPrecursor e (Text -> LuaE e Inline)
forall a e. Name -> a -> HsFnPrecursor e a
defun Name
"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
"text" 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 -> TypeSpec -> Text -> FunctionResults e Inline
forall e a. Pusher e a -> TypeSpec -> Text -> FunctionResults e a
functionResult Pusher e Inline
forall e. LuaError e => Pusher e Inline
pushInline TypeSpec
"Inline" Text
"[[Str]] object"
#? "Creates a Str inline element"
, Name -> ([Inline] -> Inline) -> DocumentedFunction e
forall {e}.
LuaError e =>
Name -> ([Inline] -> Inline) -> DocumentedFunction e
mkInlinesConstr Name
"Strikeout" [Inline] -> Inline
Strikeout
#? "Creates text which is struck out."
, Name -> ([Inline] -> Inline) -> DocumentedFunction e
forall {e}.
LuaError e =>
Name -> ([Inline] -> Inline) -> DocumentedFunction e
mkInlinesConstr Name
"Strong" [Inline] -> Inline
Strong
#? ("Creates a Strong element, whose text is usually displayed in " <>
"a bold font.")
, Name -> ([Inline] -> Inline) -> DocumentedFunction e
forall {e}.
LuaError e =>
Name -> ([Inline] -> Inline) -> DocumentedFunction e
mkInlinesConstr Name
"Subscript" [Inline] -> Inline
Subscript
#? "Creates a Subscript inline element"
, Name -> ([Inline] -> Inline) -> DocumentedFunction e
forall {e}.
LuaError e =>
Name -> ([Inline] -> Inline) -> DocumentedFunction e
mkInlinesConstr Name
"Superscript" [Inline] -> Inline
Superscript
#? "Creates a Superscript inline element"
, Name -> ([Inline] -> Inline) -> DocumentedFunction e
forall {e}.
LuaError e =>
Name -> ([Inline] -> Inline) -> DocumentedFunction e
mkInlinesConstr Name
"Underline" [Inline] -> Inline
Underline
#? "Creates an Underline inline element"
]
where
mkInlinesConstr :: Name -> ([Inline] -> Inline) -> DocumentedFunction e
mkInlinesConstr Name
name [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]
-> TypeSpec -> Text -> Text -> Parameter e [Inline]
forall e a. Peeker e a -> TypeSpec -> Text -> Text -> Parameter e a
parameter Peeker e [Inline]
forall e. LuaError e => Peeker e [Inline]
peekInlinesFuzzy TypeSpec
"Inlines" Text
"content" Text
"inline 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 -> TypeSpec -> Text -> FunctionResults e Inline
forall e a. Pusher e a -> TypeSpec -> Text -> FunctionResults e a
functionResult Pusher e Inline
forall e. LuaError e => Pusher e Inline
pushInline TypeSpec
"Inline" Text
"new object"
mkInlines :: LuaError e => DocumentedFunction e
mkInlines :: forall e. LuaError e => DocumentedFunction e
mkInlines = Name
-> ([Inline] -> LuaE e [Inline])
-> HsFnPrecursor e ([Inline] -> LuaE e [Inline])
forall a e. Name -> a -> HsFnPrecursor e a
defun Name
"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]
-> TypeSpec -> Text -> Text -> Parameter e [Inline]
forall e a. Peeker e a -> TypeSpec -> Text -> Text -> Parameter e a
parameter Peeker e [Inline]
forall e. LuaError e => Peeker e [Inline]
peekInlinesFuzzy TypeSpec
"Inlines" Text
"inline_like_elements"
(Text
"List where each element can be treated as an [[Inline]] " Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<>
Text
"value, or just a single such value.")
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] -> TypeSpec -> Text -> FunctionResults e [Inline]
forall e a. Pusher e a -> TypeSpec -> Text -> FunctionResults e a
functionResult Pusher e [Inline]
forall e. LuaError e => Pusher e [Inline]
pushInlines TypeSpec
"Inlines" Text
"list of inline elements"
#? T.unlines
[ "Converts its argument into an [[Inlines]] list:"
, ""
, "- copies a list of [[Inline]] elements into a fresh list; any"
, " string `s` within the list is treated as `pandoc.Str(s)`;"
, "- turns a single [[Inline]] into a singleton list;"
, "- splits a string into `Str`-wrapped words, treating"
, " interword spaces as `Space`s or `SoftBreak`s."
]
walkInlineSplicing :: (LuaError e, Walkable (SpliceList Inline) a)
=> Filter -> a -> LuaE e a
walkInlineSplicing :: forall e a.
(LuaError e, Walkable (SpliceList Inline) a) =>
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 :: forall e a.
(LuaError e, Walkable [Inline] a) =>
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 Name
"Inlines" Pusher e [Inline]
forall e. LuaError e => Pusher e [Inline]
pushInlines Peeker e [Inline]
forall e. LuaError e => Peeker e [Inline]
peekInlinesFuzzy