{- |
Copyright               : © 2021-2023 Albert Krewinkel
SPDX-License-Identifier : MIT
Maintainer              : Albert Krewinkel <tarleb+pandoc@moltkeplatz.de>

Marshaling/unmarshaling functions of 'Format' values.
-}
module Text.Pandoc.Lua.Marshal.Format
  ( peekFormat
  , pushFormat
  ) where

import Control.Monad ((<$!>))
import HsLua
import Text.Pandoc.Definition (Format (Format))

-- | Retrieves a 'Format' value from a string.
peekFormat :: Peeker e Format
peekFormat :: forall e. Peeker e Format
peekFormat StackIndex
idx = Text -> Format
Format forall (m :: * -> *) a b. Monad m => (a -> b) -> m a -> m b
<$!> forall e. Peeker e Text
peekText StackIndex
idx

-- | Pushes a 'Format' value as a string.
pushFormat :: Pusher e Format
pushFormat :: forall e. Pusher e Format
pushFormat (Format Text
f) = forall e. Pusher e Text
pushText Text
f