{-# LANGUAGE DeriveDataTypeable #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE UndecidableInstances #-}
module Text.Pandoc.Lua.Marshaling.List
( List (..)
) where
import Data.Data (Data)
import Foreign.Lua (Peekable, Pushable)
import Text.Pandoc.Walk (Walkable (..))
import Text.Pandoc.Lua.Util (defineHowTo, pushViaConstructor)
import qualified Foreign.Lua as Lua
newtype List a = List { fromList :: [a] }
deriving (Data, Eq, Show)
instance Pushable a => Pushable (List a) where
push (List xs) =
pushViaConstructor "List" xs
instance Peekable a => Peekable (List a) where
peek idx = defineHowTo "get List" $ do
xs <- Lua.peek idx
return $ List xs
instance Walkable [a] b => Walkable (List a) b where
walkM f = walkM (fmap fromList . f . List)
query f = query (f . List)