{-# LANGUAGE LambdaCase          #-}
{-# LANGUAGE OverloadedStrings   #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TypeApplications    #-}
{- |
   Module      : Text.Pandoc.Lua.Module.Utils
   Copyright   : Copyright © 2017-2021 Albert Krewinkel
   License     : GNU GPL, version 2 or above

   Maintainer  : Albert Krewinkel <tarleb+pandoc@moltkeplatz.de>
   Stability   : alpha

Utility module for Lua, exposing internal helper functions.
-}
module Text.Pandoc.Lua.Module.Utils
  ( documentedModule
  , sha1
  ) where

import Control.Applicative ((<|>))
import Control.Monad ((<$!>))
import Data.Data (showConstr, toConstr)
import Data.Default (def)
import Data.Version (Version)
import HsLua as Lua
import HsLua.Class.Peekable (PeekError)
import HsLua.Module.Version (peekVersionFuzzy, pushVersion)
import Text.Pandoc.Definition
import Text.Pandoc.Error (PandocError)
import Text.Pandoc.Lua.Marshaling ()
import Text.Pandoc.Lua.Marshaling.AST
  ( peekBlock, peekInline, peekPandoc, pushBlock, pushInline, pushPandoc
  , peekAttr, peekMeta, peekMetaValue)
import Text.Pandoc.Lua.Marshaling.ListAttributes (peekListAttributes)
import Text.Pandoc.Lua.Marshaling.List (pushPandocList)
import Text.Pandoc.Lua.Marshaling.SimpleTable
  ( SimpleTable (..), peekSimpleTable, pushSimpleTable )
import Text.Pandoc.Lua.PandocLua (PandocLua (unPandocLua))

import qualified Data.Digest.Pure.SHA as SHA
import qualified Data.ByteString.Lazy as BSL
import qualified Data.Text as T
import qualified Text.Pandoc.Builder as B
import qualified Text.Pandoc.Filter.JSON as JSONFilter
import qualified Text.Pandoc.Shared as Shared
import qualified Text.Pandoc.UTF8 as UTF8
import qualified Text.Pandoc.Writers.Shared as Shared

-- | Push the "pandoc.utils" module to the Lua stack.
documentedModule :: Module PandocError
documentedModule :: Module PandocError
documentedModule = Module :: forall e.
Name
-> Text
-> [Field e]
-> [DocumentedFunction e]
-> [(Operation, DocumentedFunction e)]
-> Module e
Module
  { moduleName :: Name
moduleName = Name
"pandoc.utils"
  , moduleDescription :: Text
moduleDescription = Text
"pandoc utility functions"
  , moduleFields :: [Field PandocError]
moduleFields = []
  , moduleOperations :: [(Operation, DocumentedFunction PandocError)]
moduleOperations = []
  , moduleFunctions :: [DocumentedFunction PandocError]
moduleFunctions =
    [ Name
-> ([Block] -> Maybe [Inline] -> LuaE PandocError [Inline])
-> HsFnPrecursor
     PandocError
     ([Block] -> Maybe [Inline] -> LuaE PandocError [Inline])
forall a e. Name -> a -> HsFnPrecursor e a
defun Name
"blocks_to_inlines"
      ### (\blks mSep -> do
              let sep = maybe Shared.defaultBlocksSeparator B.fromList mSep
              return $ B.toList (Shared.blocksToInlinesWithSep sep blks))
      HsFnPrecursor
  PandocError
  ([Block] -> Maybe [Inline] -> LuaE PandocError [Inline])
-> Parameter PandocError [Block]
-> HsFnPrecursor
     PandocError (Maybe [Inline] -> LuaE PandocError [Inline])
forall e a b.
HsFnPrecursor e (a -> b) -> Parameter e a -> HsFnPrecursor e b
<#> Peeker PandocError [Block]
-> Text -> Text -> Text -> Parameter PandocError [Block]
forall e a. Peeker e a -> Text -> Text -> Text -> Parameter e a
parameter (Peeker PandocError Block -> Peeker PandocError [Block]
forall a e. LuaError e => Peeker e a -> Peeker e [a]
peekList Peeker PandocError Block
forall e. LuaError e => Peeker e Block
peekBlock) Text
"list of blocks"
            Text
"blocks" Text
""
      HsFnPrecursor
  PandocError (Maybe [Inline] -> LuaE PandocError [Inline])
-> Parameter PandocError (Maybe [Inline])
-> HsFnPrecursor PandocError (LuaE PandocError [Inline])
forall e a b.
HsFnPrecursor e (a -> b) -> Parameter e a -> HsFnPrecursor e b
<#> Peeker PandocError [Inline]
-> Text -> Text -> Text -> Parameter PandocError (Maybe [Inline])
forall e a.
Peeker e a -> Text -> Text -> Text -> Parameter e (Maybe a)
optionalParameter (Peeker PandocError Inline -> Peeker PandocError [Inline]
forall a e. LuaError e => Peeker e a -> Peeker e [a]
peekList Peeker PandocError Inline
forall e. LuaError e => Peeker e Inline
peekInline) Text
"list of inlines"
            Text
"inline" Text
""
      HsFnPrecursor PandocError (LuaE PandocError [Inline])
-> FunctionResults PandocError [Inline]
-> DocumentedFunction PandocError
forall e a.
HsFnPrecursor e (LuaE e a)
-> FunctionResults e a -> DocumentedFunction e
=#> Pusher PandocError [Inline]
-> Text -> Text -> FunctionResults PandocError [Inline]
forall e a. Pusher e a -> Text -> Text -> FunctionResults e a
functionResult (Pusher PandocError Inline -> Pusher PandocError [Inline]
forall e a. LuaError e => Pusher e a -> Pusher e [a]
pushPandocList Pusher PandocError Inline
forall e. LuaError e => Inline -> LuaE e ()
pushInline) Text
"list of inlines" Text
""

    , Name
-> (AstElement -> AstElement -> LuaE PandocError Bool)
-> HsFnPrecursor
     PandocError (AstElement -> AstElement -> LuaE PandocError Bool)
forall a e. Name -> a -> HsFnPrecursor e a
defun Name
"equals"
      ### liftPure2 (==)
      HsFnPrecursor
  PandocError (AstElement -> AstElement -> LuaE PandocError Bool)
-> Parameter PandocError AstElement
-> HsFnPrecursor PandocError (AstElement -> LuaE PandocError Bool)
forall e a b.
HsFnPrecursor e (a -> b) -> Parameter e a -> HsFnPrecursor e b
<#> Peeker PandocError AstElement
-> Text -> Text -> Text -> Parameter PandocError AstElement
forall e a. Peeker e a -> Text -> Text -> Text -> Parameter e a
parameter Peeker PandocError AstElement
forall e. PeekError e => Peeker e AstElement
peekAstElement Text
"AST element" Text
"elem1" Text
""
      HsFnPrecursor PandocError (AstElement -> LuaE PandocError Bool)
-> Parameter PandocError AstElement
-> HsFnPrecursor PandocError (LuaE PandocError Bool)
forall e a b.
HsFnPrecursor e (a -> b) -> Parameter e a -> HsFnPrecursor e b
<#> Peeker PandocError AstElement
-> Text -> Text -> Text -> Parameter PandocError AstElement
forall e a. Peeker e a -> Text -> Text -> Text -> Parameter e a
parameter Peeker PandocError AstElement
forall e. PeekError e => Peeker e AstElement
peekAstElement Text
"AST element" Text
"elem2" Text
""
      HsFnPrecursor PandocError (LuaE PandocError Bool)
-> FunctionResults PandocError Bool
-> DocumentedFunction PandocError
forall e a.
HsFnPrecursor e (LuaE e a)
-> FunctionResults e a -> DocumentedFunction e
=#> Pusher PandocError Bool
-> Text -> Text -> FunctionResults PandocError Bool
forall e a. Pusher e a -> Text -> Text -> FunctionResults e a
functionResult Pusher PandocError Bool
forall e. Pusher e Bool
pushBool Text
"boolean" Text
"true iff elem1 == elem2"

    , Name
-> (Bool -> Maybe Int -> [Block] -> LuaE PandocError [Block])
-> HsFnPrecursor
     PandocError
     (Bool -> Maybe Int -> [Block] -> LuaE PandocError [Block])
forall a e. Name -> a -> HsFnPrecursor e a
defun Name
"make_sections"
      ### liftPure3 Shared.makeSections
      HsFnPrecursor
  PandocError
  (Bool -> Maybe Int -> [Block] -> LuaE PandocError [Block])
-> Parameter PandocError Bool
-> HsFnPrecursor
     PandocError (Maybe Int -> [Block] -> LuaE PandocError [Block])
forall e a b.
HsFnPrecursor e (a -> b) -> Parameter e a -> HsFnPrecursor e b
<#> Peeker PandocError Bool
-> Text -> Text -> Text -> Parameter PandocError Bool
forall e a. Peeker e a -> Text -> Text -> Text -> Parameter e a
parameter Peeker PandocError Bool
forall e. Peeker e Bool
peekBool Text
"boolean" Text
"numbering" Text
"add header numbers"
      HsFnPrecursor
  PandocError (Maybe Int -> [Block] -> LuaE PandocError [Block])
-> Parameter PandocError (Maybe Int)
-> HsFnPrecursor PandocError ([Block] -> LuaE PandocError [Block])
forall e a b.
HsFnPrecursor e (a -> b) -> Parameter e a -> HsFnPrecursor e b
<#> Peeker PandocError (Maybe Int)
-> Text -> Text -> Text -> Parameter PandocError (Maybe Int)
forall e a. Peeker e a -> Text -> Text -> Text -> Parameter e a
parameter (\StackIndex
i -> (Maybe Int
forall a. Maybe a
Nothing Maybe Int -> Peek PandocError () -> Peek PandocError (Maybe Int)
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ Peeker PandocError ()
forall e. Peeker e ()
peekNil StackIndex
i) Peek PandocError (Maybe Int)
-> Peek PandocError (Maybe Int) -> Peek PandocError (Maybe Int)
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> (Int -> Maybe Int
forall a. a -> Maybe a
Just (Int -> Maybe Int)
-> Peek PandocError Int -> Peek PandocError (Maybe Int)
forall (m :: * -> *) a b. Monad m => (a -> b) -> m a -> m b
<$!> Peeker PandocError Int
forall a e. (Integral a, Read a) => Peeker e a
peekIntegral StackIndex
i))
                    Text
"integer or nil" Text
"baselevel" Text
""
      HsFnPrecursor PandocError ([Block] -> LuaE PandocError [Block])
-> Parameter PandocError [Block]
-> HsFnPrecursor PandocError (LuaE PandocError [Block])
forall e a b.
HsFnPrecursor e (a -> b) -> Parameter e a -> HsFnPrecursor e b
<#> Peeker PandocError [Block]
-> Text -> Text -> Text -> Parameter PandocError [Block]
forall e a. Peeker e a -> Text -> Text -> Text -> Parameter e a
parameter (Peeker PandocError Block -> Peeker PandocError [Block]
forall a e. LuaError e => Peeker e a -> Peeker e [a]
peekList Peeker PandocError Block
forall e. LuaError e => Peeker e Block
peekBlock) Text
"list of blocks"
            Text
"blocks" Text
"document blocks to process"
      HsFnPrecursor PandocError (LuaE PandocError [Block])
-> FunctionResults PandocError [Block]
-> DocumentedFunction PandocError
forall e a.
HsFnPrecursor e (LuaE e a)
-> FunctionResults e a -> DocumentedFunction e
=#> Pusher PandocError [Block]
-> Text -> Text -> FunctionResults PandocError [Block]
forall e a. Pusher e a -> Text -> Text -> FunctionResults e a
functionResult (Pusher PandocError Block -> Pusher PandocError [Block]
forall e a. LuaError e => Pusher e a -> Pusher e [a]
pushPandocList Pusher PandocError Block
forall e. LuaError e => Block -> LuaE e ()
pushBlock) Text
"list of Blocks"
            Text
"processes blocks"

    , Name
-> (Text -> LuaE PandocError (Maybe Text))
-> HsFnPrecursor
     PandocError (Text -> LuaE PandocError (Maybe Text))
forall a e. Name -> a -> HsFnPrecursor e a
defun Name
"normalize_date"
      ### liftPure Shared.normalizeDate
      HsFnPrecursor PandocError (Text -> LuaE PandocError (Maybe Text))
-> Parameter PandocError Text
-> HsFnPrecursor PandocError (LuaE PandocError (Maybe Text))
forall e a b.
HsFnPrecursor e (a -> b) -> Parameter e a -> HsFnPrecursor e b
<#> Peeker PandocError Text
-> Text -> Text -> Text -> Parameter PandocError Text
forall e a. Peeker e a -> Text -> Text -> Text -> Parameter e a
parameter Peeker PandocError Text
forall e. Peeker e Text
peekText Text
"string" Text
"date" Text
"the date string"
      HsFnPrecursor PandocError (LuaE PandocError (Maybe Text))
-> FunctionResults PandocError (Maybe Text)
-> DocumentedFunction PandocError
forall e a.
HsFnPrecursor e (LuaE e a)
-> FunctionResults e a -> DocumentedFunction e
=#> Pusher PandocError (Maybe Text)
-> Text -> Text -> FunctionResults PandocError (Maybe Text)
forall e a. Pusher e a -> Text -> Text -> FunctionResults e a
functionResult (LuaE PandocError ()
-> (Text -> LuaE PandocError ()) -> Pusher PandocError (Maybe Text)
forall b a. b -> (a -> b) -> Maybe a -> b
maybe LuaE PandocError ()
forall e. LuaE e ()
pushnil Text -> LuaE PandocError ()
forall e. Pusher e Text
pushText) Text
"string or nil"
            Text
"normalized date, or nil if normalization failed."
      #? T.unwords
      [ "Parse a date and convert (if possible) to \"YYYY-MM-DD\" format. We"
      , "limit years to the range 1601-9999 (ISO 8601 accepts greater than"
      , "or equal to 1583, but MS Word only accepts dates starting 1601)."
      , "Returns nil instead of a string if the conversion failed."
      ]

    , DocumentedFunction PandocError
forall e. DocumentedFunction e
sha1

    , Name
-> (Version -> LuaE PandocError Version)
-> HsFnPrecursor PandocError (Version -> LuaE PandocError Version)
forall a e. Name -> a -> HsFnPrecursor e a
defun Name
"Version"
      ### liftPure (id @Version)
      HsFnPrecursor PandocError (Version -> LuaE PandocError Version)
-> Parameter PandocError Version
-> HsFnPrecursor PandocError (LuaE PandocError Version)
forall e a b.
HsFnPrecursor e (a -> b) -> Parameter e a -> HsFnPrecursor e b
<#> Peeker PandocError Version
-> Text -> Text -> Text -> Parameter PandocError Version
forall e a. Peeker e a -> Text -> Text -> Text -> Parameter e a
parameter Peeker PandocError Version
forall e. LuaError e => Peeker e Version
peekVersionFuzzy
            Text
"version string, list of integers, or integer"
            Text
"v" Text
"version description"
      HsFnPrecursor PandocError (LuaE PandocError Version)
-> FunctionResults PandocError Version
-> DocumentedFunction PandocError
forall e a.
HsFnPrecursor e (LuaE e a)
-> FunctionResults e a -> DocumentedFunction e
=#> Pusher PandocError Version
-> Text -> Text -> FunctionResults PandocError Version
forall e a. Pusher e a -> Text -> Text -> FunctionResults e a
functionResult Pusher PandocError Version
forall e. LuaError e => Pusher e Version
pushVersion Text
"Version" Text
"new Version object"
      #? "Creates a Version object."

    , Name
-> (Pandoc
    -> FilePath -> Maybe [FilePath] -> LuaE PandocError Pandoc)
-> HsFnPrecursor
     PandocError
     (Pandoc -> FilePath -> Maybe [FilePath] -> LuaE PandocError Pandoc)
forall a e. Name -> a -> HsFnPrecursor e a
defun Name
"run_json_filter"
      ### (\doc filterPath margs -> do
              args <- case margs of
                        Just xs -> return xs
                        Nothing -> do
                          Lua.getglobal "FORMAT"
                          (forcePeek ((:[]) <$!> peekString top) <* pop 1)
              JSONFilter.apply def args filterPath doc
          )
      HsFnPrecursor
  PandocError
  (Pandoc -> FilePath -> Maybe [FilePath] -> LuaE PandocError Pandoc)
-> Parameter PandocError Pandoc
-> HsFnPrecursor
     PandocError
     (FilePath -> Maybe [FilePath] -> LuaE PandocError Pandoc)
forall e a b.
HsFnPrecursor e (a -> b) -> Parameter e a -> HsFnPrecursor e b
<#> Peeker PandocError Pandoc
-> Text -> Text -> Text -> Parameter PandocError Pandoc
forall e a. Peeker e a -> Text -> Text -> Text -> Parameter e a
parameter Peeker PandocError Pandoc
forall e. LuaError e => Peeker e Pandoc
peekPandoc Text
"Pandoc" Text
"doc" Text
"input document"
      HsFnPrecursor
  PandocError
  (FilePath -> Maybe [FilePath] -> LuaE PandocError Pandoc)
-> Parameter PandocError FilePath
-> HsFnPrecursor
     PandocError (Maybe [FilePath] -> LuaE PandocError Pandoc)
forall e a b.
HsFnPrecursor e (a -> b) -> Parameter e a -> HsFnPrecursor e b
<#> Peeker PandocError FilePath
-> Text -> Text -> Text -> Parameter PandocError FilePath
forall e a. Peeker e a -> Text -> Text -> Text -> Parameter e a
parameter Peeker PandocError FilePath
forall e. Peeker e FilePath
peekString Text
"filepath" Text
"filter_path" Text
"path to filter"
      HsFnPrecursor
  PandocError (Maybe [FilePath] -> LuaE PandocError Pandoc)
-> Parameter PandocError (Maybe [FilePath])
-> HsFnPrecursor PandocError (LuaE PandocError Pandoc)
forall e a b.
HsFnPrecursor e (a -> b) -> Parameter e a -> HsFnPrecursor e b
<#> Peeker PandocError [FilePath]
-> Text -> Text -> Text -> Parameter PandocError (Maybe [FilePath])
forall e a.
Peeker e a -> Text -> Text -> Text -> Parameter e (Maybe a)
optionalParameter (Peeker PandocError FilePath -> Peeker PandocError [FilePath]
forall a e. LuaError e => Peeker e a -> Peeker e [a]
peekList Peeker PandocError FilePath
forall e. Peeker e FilePath
peekString) Text
"list of strings"
            Text
"args" Text
"arguments to pass to the filter"
      HsFnPrecursor PandocError (LuaE PandocError Pandoc)
-> FunctionResults PandocError Pandoc
-> DocumentedFunction PandocError
forall e a.
HsFnPrecursor e (LuaE e a)
-> FunctionResults e a -> DocumentedFunction e
=#> Pusher PandocError Pandoc
-> Text -> Text -> FunctionResults PandocError Pandoc
forall e a. Pusher e a -> Text -> Text -> FunctionResults e a
functionResult Pusher PandocError Pandoc
forall e. LuaError e => Pusher e Pandoc
pushPandoc Text
"Pandoc" Text
"filtered document"

    , Name
-> (AstElement -> LuaE PandocError Text)
-> HsFnPrecursor PandocError (AstElement -> LuaE PandocError Text)
forall a e. Name -> a -> HsFnPrecursor e a
defun Name
"stringify"
      ### unPandocLua . stringify
      HsFnPrecursor PandocError (AstElement -> LuaE PandocError Text)
-> Parameter PandocError AstElement
-> HsFnPrecursor PandocError (LuaE PandocError Text)
forall e a b.
HsFnPrecursor e (a -> b) -> Parameter e a -> HsFnPrecursor e b
<#> Peeker PandocError AstElement
-> Text -> Text -> Text -> Parameter PandocError AstElement
forall e a. Peeker e a -> Text -> Text -> Text -> Parameter e a
parameter Peeker PandocError AstElement
forall e. PeekError e => Peeker e AstElement
peekAstElement Text
"AST element" Text
"elem" Text
"some pandoc AST element"
      HsFnPrecursor PandocError (LuaE PandocError Text)
-> FunctionResults PandocError Text
-> DocumentedFunction PandocError
forall e a.
HsFnPrecursor e (LuaE e a)
-> FunctionResults e a -> DocumentedFunction e
=#> (Text -> LuaE PandocError ())
-> Text -> Text -> FunctionResults PandocError Text
forall e a. Pusher e a -> Text -> Text -> FunctionResults e a
functionResult Text -> LuaE PandocError ()
forall e. Pusher e Text
pushText Text
"string" Text
"stringified element"

    , Name
-> (SimpleTable -> LuaE PandocError NumResults)
-> HsFnPrecursor
     PandocError (SimpleTable -> LuaE PandocError NumResults)
forall a e. Name -> a -> HsFnPrecursor e a
defun Name
"from_simple_table"
      ### from_simple_table
      HsFnPrecursor
  PandocError (SimpleTable -> LuaE PandocError NumResults)
-> Parameter PandocError SimpleTable
-> HsFnPrecursor PandocError (LuaE PandocError NumResults)
forall e a b.
HsFnPrecursor e (a -> b) -> Parameter e a -> HsFnPrecursor e b
<#> Peeker PandocError SimpleTable
-> Text -> Text -> Text -> Parameter PandocError SimpleTable
forall e a. Peeker e a -> Text -> Text -> Text -> Parameter e a
parameter Peeker PandocError SimpleTable
forall e. LuaError e => Peeker e SimpleTable
peekSimpleTable Text
"SimpleTable" Text
"simple_tbl" Text
""
      HsFnPrecursor PandocError (LuaE PandocError NumResults)
-> Text -> DocumentedFunction PandocError
forall e.
HsFnPrecursor e (LuaE e NumResults) -> Text -> DocumentedFunction e
=?> Text
"Simple table"

    , Name
-> (Int -> LuaE PandocError Text)
-> HsFnPrecursor PandocError (Int -> LuaE PandocError Text)
forall a e. Name -> a -> HsFnPrecursor e a
defun Name
"to_roman_numeral"
      ### liftPure Shared.toRomanNumeral
      HsFnPrecursor PandocError (Int -> LuaE PandocError Text)
-> Parameter PandocError Int
-> HsFnPrecursor PandocError (LuaE PandocError Text)
forall e a b.
HsFnPrecursor e (a -> b) -> Parameter e a -> HsFnPrecursor e b
<#> Peeker PandocError Int
-> Text -> Text -> Text -> Parameter PandocError Int
forall e a. Peeker e a -> Text -> Text -> Text -> Parameter e a
parameter (forall e. (Integral Int, Read Int) => Peeker e Int
forall a e. (Integral a, Read a) => Peeker e a
peekIntegral @Int) Text
"integer" Text
"n" Text
"number smaller than 4000"
      HsFnPrecursor PandocError (LuaE PandocError Text)
-> FunctionResults PandocError Text
-> DocumentedFunction PandocError
forall e a.
HsFnPrecursor e (LuaE e a)
-> FunctionResults e a -> DocumentedFunction e
=#> (Text -> LuaE PandocError ())
-> Text -> Text -> FunctionResults PandocError Text
forall e a. Pusher e a -> Text -> Text -> FunctionResults e a
functionResult Text -> LuaE PandocError ()
forall e. Pusher e Text
pushText Text
"string" Text
"roman numeral"
      #? "Converts a number < 4000 to uppercase roman numeral."

    , Name
-> (Block -> LuaE PandocError SimpleTable)
-> HsFnPrecursor
     PandocError (Block -> LuaE PandocError SimpleTable)
forall a e. Name -> a -> HsFnPrecursor e a
defun Name
"to_simple_table"
      ### to_simple_table
      HsFnPrecursor PandocError (Block -> LuaE PandocError SimpleTable)
-> Parameter PandocError Block
-> HsFnPrecursor PandocError (LuaE PandocError SimpleTable)
forall e a b.
HsFnPrecursor e (a -> b) -> Parameter e a -> HsFnPrecursor e b
<#> Peeker PandocError Block
-> Text -> Text -> Text -> Parameter PandocError Block
forall e a. Peeker e a -> Text -> Text -> Text -> Parameter e a
parameter Peeker PandocError Block
forall e. LuaError e => Peeker e Block
peekTable Text
"Block" Text
"tbl" Text
"a table"
      HsFnPrecursor PandocError (LuaE PandocError SimpleTable)
-> FunctionResults PandocError SimpleTable
-> DocumentedFunction PandocError
forall e a.
HsFnPrecursor e (LuaE e a)
-> FunctionResults e a -> DocumentedFunction e
=#> Pusher PandocError SimpleTable
-> Text -> Text -> FunctionResults PandocError SimpleTable
forall e a. Pusher e a -> Text -> Text -> FunctionResults e a
functionResult Pusher PandocError SimpleTable
forall e. LuaError e => SimpleTable -> LuaE e ()
pushSimpleTable Text
"SimpleTable" Text
"SimpleTable object"
      #? "Converts a table into an old/simple table."
    ]
  }

-- | Documented Lua function to compute the hash of a string.
sha1 :: DocumentedFunction e
sha1 :: DocumentedFunction e
sha1 = Name
-> (ByteString -> LuaE e FilePath)
-> HsFnPrecursor e (ByteString -> LuaE e FilePath)
forall a e. Name -> a -> HsFnPrecursor e a
defun Name
"sha1"
  ### liftPure (SHA.showDigest . SHA.sha1)
  HsFnPrecursor e (ByteString -> LuaE e FilePath)
-> Parameter e ByteString -> HsFnPrecursor e (LuaE e FilePath)
forall e a b.
HsFnPrecursor e (a -> b) -> Parameter e a -> HsFnPrecursor e b
<#> Peeker e ByteString
-> Text -> Text -> Text -> Parameter e ByteString
forall e a. Peeker e a -> Text -> Text -> Text -> Parameter e a
parameter ((ByteString -> ByteString)
-> Peek e ByteString -> Peek e ByteString
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ByteString -> ByteString
BSL.fromStrict (Peek e ByteString -> Peek e ByteString)
-> (StackIndex -> Peek e ByteString) -> Peeker e ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. StackIndex -> Peek e ByteString
forall e. Peeker e ByteString
peekByteString) Text
"string" Text
"input" Text
""
  HsFnPrecursor e (LuaE e FilePath)
-> FunctionResults e FilePath -> DocumentedFunction e
forall e a.
HsFnPrecursor e (LuaE e a)
-> FunctionResults e a -> DocumentedFunction e
=#> Pusher e FilePath -> Text -> Text -> FunctionResults e FilePath
forall e a. Pusher e a -> Text -> Text -> FunctionResults e a
functionResult Pusher e FilePath
forall e. FilePath -> LuaE e ()
pushString Text
"string" Text
"hexadecimal hash value"
  #? "Compute the hash of the given string value."


-- | Convert pandoc structure to a string with formatting removed.
-- Footnotes are skipped (since we don't want their contents in link
-- labels).
stringify :: AstElement -> PandocLua T.Text
stringify :: AstElement -> PandocLua Text
stringify AstElement
el = Text -> PandocLua Text
forall (m :: * -> *) a. Monad m => a -> m a
return (Text -> PandocLua Text) -> Text -> PandocLua Text
forall a b. (a -> b) -> a -> b
$ case AstElement
el of
  PandocElement Pandoc
pd -> Pandoc -> Text
forall a. Walkable Inline a => a -> Text
Shared.stringify Pandoc
pd
  InlineElement Inline
i  -> Inline -> Text
forall a. Walkable Inline a => a -> Text
Shared.stringify Inline
i
  BlockElement Block
b   -> Block -> Text
forall a. Walkable Inline a => a -> Text
Shared.stringify Block
b
  MetaElement Meta
m    -> Meta -> Text
forall a. Walkable Inline a => a -> Text
Shared.stringify Meta
m
  CitationElement Citation
c  -> Citation -> Text
forall a. Walkable Inline a => a -> Text
Shared.stringify Citation
c
  MetaValueElement MetaValue
m -> MetaValue -> Text
stringifyMetaValue MetaValue
m
  AstElement
_                  -> Text
forall a. Monoid a => a
mempty

stringifyMetaValue :: MetaValue -> T.Text
stringifyMetaValue :: MetaValue -> Text
stringifyMetaValue MetaValue
mv = case MetaValue
mv of
  MetaBool Bool
b   -> Text -> Text
T.toLower (Text -> Text) -> Text -> Text
forall a b. (a -> b) -> a -> b
$ FilePath -> Text
T.pack (Bool -> FilePath
forall a. Show a => a -> FilePath
show Bool
b)
  MetaString Text
s -> Text
s
  MetaValue
_            -> MetaValue -> Text
forall a. Walkable Inline a => a -> Text
Shared.stringify MetaValue
mv

data AstElement
  = PandocElement Pandoc
  | MetaElement Meta
  | BlockElement Block
  | InlineElement Inline
  | MetaValueElement MetaValue
  | AttrElement Attr
  | ListAttributesElement ListAttributes
  | CitationElement Citation
  deriving (AstElement -> AstElement -> Bool
(AstElement -> AstElement -> Bool)
-> (AstElement -> AstElement -> Bool) -> Eq AstElement
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: AstElement -> AstElement -> Bool
$c/= :: AstElement -> AstElement -> Bool
== :: AstElement -> AstElement -> Bool
$c== :: AstElement -> AstElement -> Bool
Eq, Int -> AstElement -> ShowS
[AstElement] -> ShowS
AstElement -> FilePath
(Int -> AstElement -> ShowS)
-> (AstElement -> FilePath)
-> ([AstElement] -> ShowS)
-> Show AstElement
forall a.
(Int -> a -> ShowS) -> (a -> FilePath) -> ([a] -> ShowS) -> Show a
showList :: [AstElement] -> ShowS
$cshowList :: [AstElement] -> ShowS
show :: AstElement -> FilePath
$cshow :: AstElement -> FilePath
showsPrec :: Int -> AstElement -> ShowS
$cshowsPrec :: Int -> AstElement -> ShowS
Show)

peekAstElement :: PeekError e => Peeker e AstElement
peekAstElement :: Peeker e AstElement
peekAstElement = Name -> Peek e AstElement -> Peek e AstElement
forall e a. Name -> Peek e a -> Peek e a
retrieving Name
"pandoc AST element" (Peek e AstElement -> Peek e AstElement)
-> Peeker e AstElement -> Peeker e AstElement
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Peeker e AstElement] -> Peeker e AstElement
forall e a. LuaError e => [Peeker e a] -> Peeker e a
choice
  [ ((Pandoc -> AstElement) -> Peek e Pandoc -> Peek e AstElement
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Pandoc -> AstElement
PandocElement (Peek e Pandoc -> Peek e AstElement)
-> (StackIndex -> Peek e Pandoc) -> Peeker e AstElement
forall b c a. (b -> c) -> (a -> b) -> a -> c
. StackIndex -> Peek e Pandoc
forall e. LuaError e => Peeker e Pandoc
peekPandoc)
  , ((Inline -> AstElement) -> Peek e Inline -> Peek e AstElement
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Inline -> AstElement
InlineElement (Peek e Inline -> Peek e AstElement)
-> (StackIndex -> Peek e Inline) -> Peeker e AstElement
forall b c a. (b -> c) -> (a -> b) -> a -> c
. StackIndex -> Peek e Inline
forall e. LuaError e => Peeker e Inline
peekInline)
  , ((Block -> AstElement) -> Peek e Block -> Peek e AstElement
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Block -> AstElement
BlockElement (Peek e Block -> Peek e AstElement)
-> (StackIndex -> Peek e Block) -> Peeker e AstElement
forall b c a. (b -> c) -> (a -> b) -> a -> c
. StackIndex -> Peek e Block
forall e. LuaError e => Peeker e Block
peekBlock)
  , ((MetaValue -> AstElement) -> Peek e MetaValue -> Peek e AstElement
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap MetaValue -> AstElement
MetaValueElement (Peek e MetaValue -> Peek e AstElement)
-> (StackIndex -> Peek e MetaValue) -> Peeker e AstElement
forall b c a. (b -> c) -> (a -> b) -> a -> c
. StackIndex -> Peek e MetaValue
forall e. LuaError e => Peeker e MetaValue
peekMetaValue)
  , ((Attr -> AstElement) -> Peek e Attr -> Peek e AstElement
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Attr -> AstElement
AttrElement (Peek e Attr -> Peek e AstElement)
-> (StackIndex -> Peek e Attr) -> Peeker e AstElement
forall b c a. (b -> c) -> (a -> b) -> a -> c
. StackIndex -> Peek e Attr
forall e. LuaError e => Peeker e Attr
peekAttr)
  , ((ListAttributes -> AstElement)
-> Peek e ListAttributes -> Peek e AstElement
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ListAttributes -> AstElement
ListAttributesElement (Peek e ListAttributes -> Peek e AstElement)
-> (StackIndex -> Peek e ListAttributes) -> Peeker e AstElement
forall b c a. (b -> c) -> (a -> b) -> a -> c
. StackIndex -> Peek e ListAttributes
forall e. LuaError e => Peeker e ListAttributes
peekListAttributes)
  , ((Meta -> AstElement) -> Peek e Meta -> Peek e AstElement
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Meta -> AstElement
MetaElement (Peek e Meta -> Peek e AstElement)
-> (StackIndex -> Peek e Meta) -> Peeker e AstElement
forall b c a. (b -> c) -> (a -> b) -> a -> c
. StackIndex -> Peek e Meta
forall e. LuaError e => Peeker e Meta
peekMeta)
  ]

-- | Converts an old/simple table into a normal table block element.
from_simple_table :: SimpleTable -> LuaE PandocError NumResults
from_simple_table :: SimpleTable -> LuaE PandocError NumResults
from_simple_table (SimpleTable [Inline]
capt [Alignment]
aligns [Double]
widths [[Block]]
head' [[[Block]]]
body) = do
  Pusher PandocError Block
forall a e. (Pushable a, LuaError e) => a -> LuaE e ()
Lua.push Pusher PandocError Block -> Pusher PandocError Block
forall a b. (a -> b) -> a -> b
$ Attr
-> Caption
-> [ColSpec]
-> TableHead
-> [TableBody]
-> TableFoot
-> Block
Table
    Attr
nullAttr
    (Maybe [Inline] -> [Block] -> Caption
Caption Maybe [Inline]
forall a. Maybe a
Nothing [[Inline] -> Block
Plain [Inline]
capt])
    ((Alignment -> Double -> ColSpec)
-> [Alignment] -> [Double] -> [ColSpec]
forall a b c. (a -> b -> c) -> [a] -> [b] -> [c]
zipWith (\Alignment
a Double
w -> (Alignment
a, Double -> ColWidth
toColWidth Double
w)) [Alignment]
aligns [Double]
widths)
    (Attr -> [Row] -> TableHead
TableHead Attr
nullAttr [[[Block]] -> Row
blockListToRow [[Block]]
head' | Bool -> Bool
not ([[Block]] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [[Block]]
head') ])
    [Attr -> RowHeadColumns -> [Row] -> [Row] -> TableBody
TableBody Attr
nullAttr RowHeadColumns
0 [] ([Row] -> TableBody) -> [Row] -> TableBody
forall a b. (a -> b) -> a -> b
$ ([[Block]] -> Row) -> [[[Block]]] -> [Row]
forall a b. (a -> b) -> [a] -> [b]
map [[Block]] -> Row
blockListToRow [[[Block]]]
body]
    (Attr -> [Row] -> TableFoot
TableFoot Attr
nullAttr [])
  NumResults -> LuaE PandocError NumResults
forall (m :: * -> *) a. Monad m => a -> m a
return (CInt -> NumResults
NumResults CInt
1)
  where
    blockListToRow :: [[Block]] -> Row
    blockListToRow :: [[Block]] -> Row
blockListToRow = Attr -> [Cell] -> Row
Row Attr
nullAttr ([Cell] -> Row) -> ([[Block]] -> [Cell]) -> [[Block]] -> Row
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ([Block] -> Cell) -> [[Block]] -> [Cell]
forall a b. (a -> b) -> [a] -> [b]
map (Blocks -> Cell
B.simpleCell (Blocks -> Cell) -> ([Block] -> Blocks) -> [Block] -> Cell
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Block] -> Blocks
forall a. [a] -> Many a
B.fromList)

    toColWidth :: Double -> ColWidth
    toColWidth :: Double -> ColWidth
toColWidth Double
0 = ColWidth
ColWidthDefault
    toColWidth Double
w = Double -> ColWidth
ColWidth Double
w

-- | Converts a table into an old/simple table.
to_simple_table :: Block -> LuaE PandocError SimpleTable
to_simple_table :: Block -> LuaE PandocError SimpleTable
to_simple_table = \case
  Table Attr
_attr Caption
caption [ColSpec]
specs TableHead
thead [TableBody]
tbodies TableFoot
tfoot -> do
    let ([Inline]
capt, [Alignment]
aligns, [Double]
widths, [[Block]]
headers, [[[Block]]]
rows) =
          Caption
-> [ColSpec]
-> TableHead
-> [TableBody]
-> TableFoot
-> ([Inline], [Alignment], [Double], [[Block]], [[[Block]]])
Shared.toLegacyTable Caption
caption [ColSpec]
specs TableHead
thead [TableBody]
tbodies TableFoot
tfoot
    SimpleTable -> LuaE PandocError SimpleTable
forall (m :: * -> *) a. Monad m => a -> m a
return (SimpleTable -> LuaE PandocError SimpleTable)
-> SimpleTable -> LuaE PandocError SimpleTable
forall a b. (a -> b) -> a -> b
$ [Inline]
-> [Alignment]
-> [Double]
-> [[Block]]
-> [[[Block]]]
-> SimpleTable
SimpleTable [Inline]
capt [Alignment]
aligns [Double]
widths [[Block]]
headers [[[Block]]]
rows
  Block
blk -> FilePath -> LuaE PandocError SimpleTable
forall e a. LuaError e => FilePath -> LuaE e a
Lua.failLua (FilePath -> LuaE PandocError SimpleTable)
-> FilePath -> LuaE PandocError SimpleTable
forall a b. (a -> b) -> a -> b
$ [FilePath] -> FilePath
forall a. Monoid a => [a] -> a
mconcat
         [ FilePath
"Expected Table, got ", Constr -> FilePath
showConstr (Block -> Constr
forall a. Data a => a -> Constr
toConstr Block
blk), FilePath
"." ]

peekTable :: LuaError e => Peeker e Block
peekTable :: Peeker e Block
peekTable StackIndex
idx = Peeker e Block
forall e. LuaError e => Peeker e Block
peekBlock StackIndex
idx Peek e Block -> (Block -> Peek e Block) -> Peek e Block
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \case
  t :: Block
t@(Table {}) -> Block -> Peek e Block
forall (m :: * -> *) a. Monad m => a -> m a
return Block
t
  Block
b -> ByteString -> Peek e Block
forall a e. ByteString -> Peek e a
Lua.failPeek (ByteString -> Peek e Block) -> ByteString -> Peek e Block
forall a b. (a -> b) -> a -> b
$ [ByteString] -> ByteString
forall a. Monoid a => [a] -> a
mconcat
       [ ByteString
"Expected Table, got "
       , FilePath -> ByteString
UTF8.fromString (FilePath -> ByteString) -> FilePath -> ByteString
forall a b. (a -> b) -> a -> b
$ Constr -> FilePath
showConstr (Block -> Constr
forall a. Data a => a -> Constr
toConstr Block
b)
       , ByteString
"." ]