diff options
Diffstat (limited to 'src/Text/Pandoc/Lua')
-rw-r--r-- | src/Text/Pandoc/Lua/Marshaling.hs | 1 | ||||
-rw-r--r-- | src/Text/Pandoc/Lua/Marshaling/Context.hs | 31 |
2 files changed, 32 insertions, 0 deletions
diff --git a/src/Text/Pandoc/Lua/Marshaling.hs b/src/Text/Pandoc/Lua/Marshaling.hs index 8a1270ab7..c37f22b8d 100644 --- a/src/Text/Pandoc/Lua/Marshaling.hs +++ b/src/Text/Pandoc/Lua/Marshaling.hs @@ -14,4 +14,5 @@ module Text.Pandoc.Lua.Marshaling () where import Text.Pandoc.Lua.Marshaling.AST () import Text.Pandoc.Lua.Marshaling.CommonState () import Text.Pandoc.Lua.Marshaling.ReaderOptions () +import Text.Pandoc.Lua.Marshaling.Context () import Text.Pandoc.Lua.Marshaling.Version () diff --git a/src/Text/Pandoc/Lua/Marshaling/Context.hs b/src/Text/Pandoc/Lua/Marshaling/Context.hs new file mode 100644 index 000000000..a9cc7f38e --- /dev/null +++ b/src/Text/Pandoc/Lua/Marshaling/Context.hs @@ -0,0 +1,31 @@ +{-# LANGUAGE NoImplicitPrelude #-} +{-# LANGUAGE FlexibleInstances #-} +{-# LANGUAGE ScopedTypeVariables #-} +{-# LANGUAGE LambdaCase #-} +{-# OPTIONS_GHC -fno-warn-orphans #-} +{- | + Module : Text.Pandoc.Lua.Marshaling.Context + Copyright : © 2012-2019 John MacFarlane + © 2017-2019 Albert Krewinkel + License : GNU GPL, version 2 or above + + Maintainer : Albert Krewinkel <tarleb+pandoc@moltkeplatz.de> + Stability : alpha + +Marshaling instance for doctemplates Context and its components. +-} +module Text.Pandoc.Lua.Marshaling.Context () where + +import qualified Foreign.Lua as Lua +import Foreign.Lua (Pushable) +import Text.DocTemplates (Context(..), Val(..)) + +instance Pushable a => Pushable (Context a) where + push (Context m) = Lua.push m + +instance Pushable a => Pushable (Val a) where + push NullVal = Lua.push () + push (MapVal ctx) = Lua.push ctx + push (ListVal xs) = Lua.push xs + push (SimpleVal x) = Lua.push x + |